source: palm/trunk/SOURCE/read_var_list.f90 @ 2566

Last change on this file since 2566 was 2563, checked in by Giersch, 7 years ago

Restart runs with the usage of the wind turbine model are possible now. Further small at reading/writing restart data

  • Property svn:keywords set to Id
File size: 39.7 KB
Line 
1!> @file read_var_list.f90
2!------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2017 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: read_var_list.f90 2563 2017-10-19 15:36:10Z raasch $
27! CALL stg_read_restart_data moved to synthetic_turbulence_generator_mod and
28! CALL flight_read_restart_data moved to virtual_flights_mod. Furthermore
29! *** end default *** marks the end of the standard parameter list of restart
30! files and *** end *** marks the end of all parameter including module
31! parameter. Therefore the call of flight_skip_var_list becomes unnecessary.
32!
33! 2372 2017-08-25 12:37:32Z sward
34! y_shift added to vars, version no. increased
35!
36! 2365 2017-08-21 14:59:59Z kanani
37! Vertical grid nesting implemented (SadiqHuq)
38!
39! 2339 2017-08-07 13:55:26Z gronemeier
40! corrected timestamp in header
41!
42! 2338 2017-08-07 12:15:38Z gronemeier
43! Modularize 1D model
44!
45! 2320 2017-07-21 12:47:43Z suehring
46! Formatting adjustment
47!
48! 2265 2017-06-08 16:58:28Z schwenkel
49! Unused variables removed.
50!
51! 2259 2017-06-08 09:09:11Z gronemeier
52! Implemented synthetic turbulence generator
53!
54! 2233 2017-05-30 18:08:54Z suehring
55!
56! 2232 2017-05-30 17:47:52Z suehring
57! Replace wall_qflux, wall_sflux by wall_humidityflux and wall_scalarflux; add
58! wall_salinityflux
59! +tunnel_height, tunnel_length, tunnel_width_x, tunnel_width_y,
60!  tunnel_wall_depth
61!
62! 2042 2016-11-02 13:47:31Z suehring
63! Bugfix, read restart data for wall_heatflux, wall_qflux and wall_sflux
64!
65! 2000 2016-08-20 18:09:15Z knoop
66! Forced header and separation lines into 80 columns
67!
68! 1992 2016-08-12 15:14:59Z suehring
69! top_scalarflux added
70!
71! 1960 2016-07-12 16:34:24Z suehring
72! Separate humidity and passive scalar
73! Remove unused variables from ONLY list
74!
75! 1957 2016-07-07 10:43:48Z suehring
76! flight module added
77!
78! 1849 2016-04-08 11:33:18Z hoffmann
79! Adapted for modularization of microphysics
80!
81! 1833 2016-04-07 14:23:03Z raasch
82! spectra_mod added
83!
84! 1831 2016-04-07 13:15:51Z hoffmann
85! turbulence renamed collision_turbulence, drizzle renamed
86! cloud_water_sedimentation
87!
88! 1808 2016-04-05 19:44:00Z raasch
89! test output removed
90!
91! 1783 2016-03-06 18:36:17Z raasch
92! netcdf module name changed + related changes
93!
94! 1699 2015-10-29 08:02:35Z maronga
95! Bugfix: update of binary version from 3.9b to 4.0 was missing
96!
97! 1691 2015-10-26 16:17:44Z maronga
98! Added output of most_method, constant_flux_layer, zeta_min, zeta_max. Removed
99! output of prandtl_layer and rif_min, rif_max.
100!
101! 1682 2015-10-07 23:56:08Z knoop
102! Code annotations made doxygen readable
103!
104! 1615 2015-07-08 18:49:19Z suehring
105! Enable turbulent inflow for passive_scalar and humidity
106!
107! 1585 2015-04-30 07:05:52Z maronga
108! Adapted for RRTMG
109!
110! 1560 2015-03-06 10:48:54Z keck
111! +recycling_yshift
112!
113! 1522 2015-01-14 10:53:12Z keck
114! added query for checking if the advection scheme in the restart run is the
115! same as the advection scheme in the corresponding initial run
116!
117! 1502 2014-12-03 18:22:31Z kanani
118! Canopy module and parameters removed (parameters are always read from
119! canopy_par NAMELIST for initial and restart runs)
120!
121! 1496 2014-12-02 17:25:50Z maronga
122! Renamed "radiation" -> "cloud_top_radiation"
123!
124! 1484 2014-10-21 10:53:05Z kanani
125! Changes in the course of the canopy-model modularization:
126!   parameters alpha_lad, beta_lad, lai_beta added,
127!   module plant_canopy_model_mod added,
128!   drag_coefficient, leaf_surface_concentration and scalar_exchange_coefficient
129!   renamed to canopy_drag_coeff, leaf_surface_conc and leaf_scalar_exch_coeff
130!
131! 1322 2014-03-20 16:38:49Z raasch
132! REAL functions provided with KIND-attribute
133!
134! 1320 2014-03-20 08:40:49Z raasch
135! ONLY-attribute added to USE-statements,
136! kind-parameters added to all INTEGER and REAL declaration statements,
137! kinds are defined in new module kinds,
138! old module precision_kind is removed,
139! revision history before 2012 removed,
140! comment fields (!:) to be used for variable explanations added to
141! all variable declaration statements
142!
143! 1308 2014-03-13 14:58:42Z fricke
144! +do2d_xy_time_count, do2d_xz_time_count, do2d_yz_time_count,
145! +do3d_time_count
146!
147! 1253 2013-11-07 10:48:12Z fricke
148! Bugfix: add ref_state to read_parts_of_var_list, otherwise ref_state
149! is zero for initializing_actions = 'cyclic_fill'
150!
151! 1241 2013-10-30 11:36:58Z heinze
152! +nudging
153! +large_scale_forcing
154!
155! 1195 2013-07-01 12:27:57Z heinze
156! Bugfix: allocate ref_state
157!
158! 1179 2013-06-14 05:57:58Z raasch
159! +ref_state
160!
161! 1115 2013-03-26 18:16:16Z hoffmann
162! unused variables removed
163!
164! 1092 2013-02-02 11:24:22Z raasch
165! unused variables removed
166!
167! 1065 2012-11-22 17:42:36Z hoffmann
168! +nc, c_sedimentation, limiter_sedimentation, turbulence
169! -mu_constant, mu_constant_value
170!
171! 1053 2012-11-13 17:11:03Z hoffmann
172! necessary expansions according to the two new prognostic equations (nr, qr)
173! of the two-moment cloud physics scheme:
174! +bc_*_b, +bc_*_t, +bc_*_t_val, *_init, *_surface, *_surface_initial_change,
175! +*_vertical_gradient, +*_vertical_gradient_level, *_vertical_gradient_level_ind,
176! +surface_waterflux_*
177!
178! in addition, steering parameters parameters of the two-moment cloud physics
179! scheme:
180! +cloud_scheme, +drizzle, +mu_constant, +mu_constant_value, +ventilation_effect
181!
182! 1036 2012-10-22 13:43:42Z raasch
183! code put under GPL (PALM 3.9)
184!
185! 1015 2012-09-27 09:23:24Z raasch
186! -adjust_mixing_length
187!
188! 1003 2012-09-14 14:35:53Z raasch
189! -grid_matching
190!
191! 1001 2012-09-13 14:08:46Z raasch
192! -cut_spline_overshoot, dt_fixed, last_dt_change, long_filter_factor,
193! overshoot_limit_*, ups_limit_*
194!
195! 978 2012-08-09 08:28:32Z fricke
196! -km_damp_max, outflow_damping_width
197! +pt_damping_factor, pt_damping_width
198! +z0h_factor
199!
200! 940 2012-07-09 14:31:00Z raasch
201! +neutral
202!
203! 927 2012-06-06 19:15:04Z raasch
204! +masking_method
205!
206! 849 2012-03-15 10:35:09Z raasch
207! first_call_advec_particles renamed first_call_lpm
208!
209! 824 2012-02-17 09:09:57Z raasch
210! +curvature_solution_effects
211!
212! Revision 1.1  1998/03/18 20:18:48  raasch
213! Initial revision
214!
215!
216! Description:
217! ------------
218!> Reading values of global control variables from restart-file (binary format)
219!------------------------------------------------------------------------------!
220 SUBROUTINE read_var_list
221
222
223    USE arrays_3d,                                                             &
224        ONLY:  inflow_damping_factor, mean_inflow_profiles, pt_init,           &
225               q_init, ref_state, s_init, sa_init, u_init, ug, v_init, vg
226
227    USE control_parameters
228
229    USE grid_variables,                                                        &
230        ONLY:  dx, dy
231
232    USE indices,                                                               &
233        ONLY:  nz, nx, nx_on_file, ny, ny_on_file
234
235    USE microphysics_mod,                                                      &
236        ONLY:  c_sedimentation, collision_turbulence,                          &
237               cloud_water_sedimentation, limiter_sedimentation,               &
238               nc_const, ventilation_effect
239
240    USE model_1d_mod,                                                          &
241        ONLY:  damp_level_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
242
243    USE netcdf_interface,                                                      &
244        ONLY:  netcdf_precision, output_for_t0
245
246    USE particle_attributes,                                                   &
247        ONLY:  curvature_solution_effects
248
249    USE pegrid
250
251    USE radiation_model_mod,                                                   &
252        ONLY:  time_radiation
253
254    USE spectra_mod,                                                           &
255        ONLY:  average_count_sp
256
257    USE statistics,                                                            &
258        ONLY:  statistic_regions, hom, hom_sum, pr_palm, u_max, u_max_ijk,     &
259               v_max, v_max_ijk, w_max, w_max_ijk
260
261    USE vertical_nesting_mod,                                                  &
262        ONLY:  vnest_init
263
264    IMPLICIT NONE
265
266    CHARACTER (LEN=10) ::  binary_version, version_on_file
267    CHARACTER (LEN=30) ::  variable_chr
268
269
270    CALL check_open( 13 )
271
272!
273!-- Make version number check first
274    READ ( 13 )  version_on_file
275    binary_version = '4.3'
276    IF ( TRIM( version_on_file ) /= TRIM( binary_version ) )  THEN
277       WRITE( message_string, * ) 'version mismatch concerning control ', &
278                                  'variables',                            &
279                                  '&version on file    = "',              &
280                                  TRIM( version_on_file ), '"',           &
281                                  '&version on program = "',              &
282                                  TRIM( binary_version ), '"'
283       CALL message( 'read_var_list', 'PA0296', 1, 2, 0, 6, 0 )
284    ENDIF
285
286!
287!-- Read number of PEs and horizontal index bounds of all PEs used in previous
288!-- run
289    READ ( 13 )  variable_chr
290    IF ( TRIM( variable_chr ) /= 'numprocs' )  THEN
291       WRITE( message_string, * ) 'numprocs not found in data from prior ', &
292                                  'run on PE ', myid
293       CALL message( 'read_var_list', 'PA0297', 1, 2, 0, 6, 0 )
294    ENDIF
295    READ ( 13 )  numprocs_previous_run
296
297    IF ( .NOT. ALLOCATED( hor_index_bounds_previous_run ) )  THEN
298       ALLOCATE( hor_index_bounds_previous_run(4,0:numprocs_previous_run-1) )
299    ENDIF
300
301    READ ( 13 )  variable_chr
302    IF ( TRIM( variable_chr ) /= 'hor_index_bounds' )  THEN
303       WRITE( message_string, * ) 'hor_index_bounds not found in data from ', &
304                                  'prior run on PE ', myid
305       CALL message( 'read_var_list', 'PA0298', 1, 2, 0, 6, 0 )
306    ENDIF
307    READ ( 13 )  hor_index_bounds_previous_run
308
309!
310!-- Read vertical number of gridpoints and number of different areas used
311!-- for computing statistics. Allocate arrays depending on these values,
312!-- which are needed for the following read instructions.
313    READ ( 13 )  variable_chr
314    IF ( TRIM( variable_chr ) /= 'nz' )  THEN
315       WRITE( message_string, * ) 'nz not found in data from prior run on PE ',&
316                                  myid
317       CALL message( 'read_var_list', 'PA0299', 1, 2, 0, 6, 0 )
318    ENDIF
319    READ ( 13 )  nz
320
321    READ ( 13 )  variable_chr
322    IF ( TRIM( variable_chr ) /= 'max_pr_user' )  THEN
323       WRITE( message_string, * ) 'max_pr_user not found in data from ', &
324                    'prior run on PE ', myid
325       CALL message( 'read_var_list', 'PA0300', 1, 2, 0, 6, 0 )
326    ENDIF
327    READ ( 13 )  max_pr_user    ! This value is checked against the number of
328                                ! user profiles given for the current run
329                                ! in routine user_parin (it has to match)
330
331    READ ( 13 )  variable_chr
332    IF ( TRIM( variable_chr ) /= 'statistic_regions' )  THEN
333       WRITE( message_string, * ) 'statistic_regions not found in data from ', &
334                    'prior run on PE ', myid
335       CALL message( 'read_var_list', 'PA0301', 1, 2, 0, 6, 0 )
336    ENDIF
337    READ ( 13 )  statistic_regions
338    IF ( .NOT. ALLOCATED( ug ) )  THEN
339       ALLOCATE( ug(0:nz+1), u_init(0:nz+1), vg(0:nz+1),                       &
340                 v_init(0:nz+1), pt_init(0:nz+1), q_init(0:nz+1),              &
341                 ref_state(0:nz+1), s_init(0:nz+1), sa_init(0:nz+1),           &
342                 hom(0:nz+1,2,pr_palm+max_pr_user,0:statistic_regions),        &
343                 hom_sum(0:nz+1,pr_palm+max_pr_user,0:statistic_regions) )
344    ENDIF
345
346!
347!-- Now read all control parameters:
348!-- Caution: When the following read instructions have been changed, the
349!-- -------  version number stored in the variable binary_version has to be
350!--          increased. The same changes must also be done in write_var_list.
351    READ ( 13 )  variable_chr
352    DO  WHILE ( TRIM( variable_chr ) /= '*** end default ***' )
353
354       SELECT CASE ( TRIM( variable_chr ) )
355
356          CASE ( 'advected_distance_x' )
357             READ ( 13 )  advected_distance_x
358          CASE ( 'advected_distance_y' )
359             READ ( 13 )  advected_distance_y
360          CASE ( 'alpha_surface' )
361             READ ( 13 )  alpha_surface
362          CASE ( 'average_count_pr' )
363             READ ( 13 )  average_count_pr
364          CASE ( 'average_count_sp' )
365             READ ( 13 )  average_count_sp
366          CASE ( 'average_count_3d' )
367             READ ( 13 )  average_count_3d
368          CASE ( 'bc_e_b' )
369             READ ( 13 )  bc_e_b
370          CASE ( 'bc_lr' )
371             READ ( 13 )  bc_lr
372          CASE ( 'bc_ns' )
373             READ ( 13 )  bc_ns
374          CASE ( 'bc_p_b' )
375             READ ( 13 )  bc_p_b
376          CASE ( 'bc_p_t' )
377             READ ( 13 )  bc_p_t
378          CASE ( 'bc_pt_b' )
379             READ ( 13 )  bc_pt_b
380          CASE ( 'bc_pt_t' )
381             READ ( 13 )  bc_pt_t
382          CASE ( 'bc_pt_t_val' )
383             READ ( 13 )  bc_pt_t_val
384          CASE ( 'bc_q_b' )
385             READ ( 13 )  bc_q_b
386          CASE ( 'bc_q_t' )
387             READ ( 13 )  bc_q_t
388          CASE ( 'bc_q_t_val' )
389             READ ( 13 )  bc_q_t_val
390          CASE ( 'bc_s_b' )
391             READ ( 13 )  bc_s_b
392          CASE ( 'bc_s_t' )
393             READ ( 13 )  bc_s_t
394          CASE ( 'bc_sa_t' )
395             READ ( 13 )  bc_sa_t
396          CASE ( 'bc_uv_b' )
397             READ ( 13 )  bc_uv_b
398          CASE ( 'bc_uv_t' )
399             READ ( 13 )  bc_uv_t
400          CASE ( 'bottom_salinityflux' )
401             READ ( 13 )  bottom_salinityflux
402          CASE ( 'building_height' )
403             READ ( 13 )  building_height
404          CASE ( 'building_length_x' )
405             READ ( 13 )  building_length_x
406          CASE ( 'building_length_y' )
407             READ ( 13 )  building_length_y
408          CASE ( 'building_wall_left' )
409             READ ( 13 )  building_wall_left
410          CASE ( 'building_wall_south' )
411             READ ( 13 )  building_wall_south
412          CASE ( 'call_psolver_at_all_substeps' )
413             READ ( 13 )  call_psolver_at_all_substeps
414          CASE ( 'canyon_height' )
415             READ ( 13 )  canyon_height
416          CASE ( 'canyon_width_x' )
417             READ ( 13 )  canyon_width_x
418          CASE ( 'canyon_width_y' )
419             READ ( 13 )  canyon_width_y
420          CASE ( 'canyon_wall_left' )
421             READ ( 13 )  canyon_wall_left
422          CASE ( 'canyon_wall_south' )
423             READ ( 13 )  canyon_wall_south
424          CASE ( 'c_sedimentation' )
425             READ ( 13 )  c_sedimentation
426          CASE ( 'cfl_factor' )
427             READ ( 13 )  cfl_factor
428          CASE ( 'cloud_droplets' )
429             READ ( 13 )  cloud_droplets
430          CASE ( 'cloud_physics' )
431             READ ( 13 )  cloud_physics
432          CASE ( 'cloud_scheme' )
433             READ ( 13 )  cloud_scheme
434          CASE ( 'collective_wait' )
435             READ ( 13 )  collective_wait
436          CASE ( 'conserve_volume_flow' )
437             READ ( 13 )  conserve_volume_flow
438          CASE ( 'conserve_volume_flow_mode' )
439             READ ( 13 )  conserve_volume_flow_mode
440          CASE ( 'constant_flux_layer' )
441             READ ( 13 )  constant_flux_layer
442          CASE ( 'coupling_start_time' )
443             READ ( 13 )  coupling_start_time
444          CASE ( 'current_timestep_number' )
445             READ ( 13 )  current_timestep_number
446          CASE ( 'curvature_solution_effects' )
447             READ ( 13 )  curvature_solution_effects
448          CASE ( 'cycle_mg' )
449             READ ( 13 )  cycle_mg
450          CASE ( 'damp_level_1d' )
451             READ ( 13 )  damp_level_1d
452          CASE ( 'dissipation_1d' )
453             READ ( 13 )  dissipation_1d
454          CASE ( 'do2d_xy_time_count' )
455             READ ( 13 )  do2d_xy_time_count
456          CASE ( 'do2d_xz_time_count' )
457             READ ( 13 )  do2d_xz_time_count
458          CASE ( 'do2d_yz_time_count' )
459             READ ( 13 )  do2d_yz_time_count
460          CASE ( 'do3d_time_count' )
461             READ ( 13 )  do3d_time_count
462          CASE ( 'dp_external' )
463             READ ( 13 )  dp_external
464          CASE ( 'dp_level_b' )
465             READ ( 13 )  dp_level_b
466          CASE ( 'dp_smooth' )
467             READ ( 13 )  dp_smooth
468          CASE ( 'dpdxy' )
469             READ ( 13 )  dpdxy
470          CASE ( 'cloud_water_sedimentation' )
471             READ ( 13 )  cloud_water_sedimentation
472          CASE ( 'dt_pr_1d' )
473             READ ( 13 )  dt_pr_1d
474          CASE ( 'dt_run_control_1d' )
475             READ ( 13 )  dt_run_control_1d
476          CASE ( 'dt_3d' )
477             READ ( 13 )  dt_3d
478          CASE ( 'dvrp_filecount' )
479             READ ( 13 )  dvrp_filecount
480          CASE ( 'dx' )
481             READ ( 13 )  dx
482          CASE ( 'dy' )
483             READ ( 13 )  dy
484          CASE ( 'dz' )
485             READ ( 13 )  dz
486          CASE ( 'dz_max' )
487             READ ( 13 )  dz_max
488          CASE ( 'dz_stretch_factor' )
489             READ ( 13 )  dz_stretch_factor
490          CASE ( 'dz_stretch_level' )
491             READ ( 13 )  dz_stretch_level
492          CASE ( 'e_min' )
493             READ ( 13 )  e_min
494          CASE ( 'end_time_1d' )
495             READ ( 13 )  end_time_1d
496          CASE ( 'fft_method' )
497             READ ( 13 )  fft_method
498          CASE ( 'first_call_lpm' )
499             READ ( 13 )  first_call_lpm
500          CASE ( 'galilei_transformation' )
501             READ ( 13 )  galilei_transformation
502          CASE ( 'hom' )
503             READ ( 13 )  hom
504          CASE ( 'hom_sum' )
505             READ ( 13 )  hom_sum
506          CASE ( 'humidity' )
507             READ ( 13 )  humidity
508          CASE ( 'inflow_damping_factor' )
509             IF ( .NOT. ALLOCATED( inflow_damping_factor ) )  THEN
510                ALLOCATE( inflow_damping_factor(0:nz+1) )
511             ENDIF
512             READ ( 13 )  inflow_damping_factor
513          CASE ( 'inflow_damping_height' )
514             READ ( 13 )  inflow_damping_height
515          CASE ( 'inflow_damping_width' )
516             READ ( 13 )  inflow_damping_width
517          CASE ( 'inflow_disturbance_begin' )
518             READ ( 13 )  inflow_disturbance_begin
519          CASE ( 'inflow_disturbance_end' )
520             READ ( 13 )  inflow_disturbance_end
521          CASE ( 'km_constant' )
522             READ ( 13 )  km_constant
523          CASE ( 'large_scale_forcing' )
524             READ ( 13 )  large_scale_forcing
525          CASE ( 'large_scale_subsidence' )
526             READ ( 13 )  large_scale_subsidence
527          CASE ( 'limiter_sedimentation' )
528             READ ( 13 )  limiter_sedimentation
529          CASE ( 'loop_optimization' )
530             READ ( 13 )  loop_optimization
531          CASE ( 'masking_method' )
532             READ ( 13 )  masking_method
533          CASE ( 'mean_inflow_profiles' )
534             IF ( .NOT. ALLOCATED( mean_inflow_profiles ) )  THEN
535                ALLOCATE( mean_inflow_profiles(0:nz+1,7) )
536             ENDIF
537             READ ( 13 )  mean_inflow_profiles
538          CASE ( 'mg_cycles' )
539             READ ( 13 )  mg_cycles
540          CASE ( 'mg_switch_to_pe0_level' )
541             READ ( 13 )  mg_switch_to_pe0_level
542          CASE ( 'mixing_length_1d' )
543             READ ( 13 )  mixing_length_1d
544          CASE ( 'momentum_advec' )
545             READ ( 13 )  momentum_advec
546          CASE ( 'most_method' )
547             READ ( 13 )  most_method
548          CASE ( 'nc_const' )
549             READ ( 13 )  nc_const
550          CASE ( 'netcdf_precision' )
551             READ ( 13 )  netcdf_precision
552          CASE ( 'neutral' )
553             READ ( 13 )  neutral
554          CASE ( 'ngsrb' )
555             READ ( 13 )  ngsrb
556          CASE ( 'nsor' )
557             READ ( 13 )  nsor
558          CASE ( 'nsor_ini' )
559             READ ( 13 )  nsor_ini
560          CASE ( 'nudging' )
561             READ ( 13 )  nudging
562          CASE ( 'num_leg' )
563             READ ( 13 )  num_leg
564          CASE ( 'nx' )
565             READ ( 13 )  nx
566             nx_on_file = nx
567          CASE ( 'ny' )
568             READ ( 13 )  ny
569             ny_on_file = ny
570          CASE ( 'ocean' )
571             READ ( 13 )  ocean
572          CASE ( 'old_dt' )
573             READ ( 13 )  old_dt
574          CASE ( 'omega' )
575             READ ( 13 )  omega
576          CASE ( 'omega_sor' )
577             READ ( 13 )  omega_sor
578          CASE ( 'output_for_t0' )
579             READ (13)    output_for_t0
580          CASE ( 'passive_scalar' )
581             READ ( 13 )  passive_scalar
582          CASE ( 'phi' )
583             READ ( 13 )  phi
584          CASE ( 'prandtl_number' )
585             READ ( 13 )  prandtl_number
586          CASE ( 'precipitation' )
587             READ ( 13 ) precipitation
588          CASE ( 'psolver' )
589             READ ( 13 )  psolver
590          CASE ( 'pt_damping_factor' )
591             READ ( 13 )  pt_damping_factor
592          CASE ( 'pt_damping_width' )
593             READ ( 13 )  pt_damping_width
594          CASE ( 'pt_init' )
595             READ ( 13 )  pt_init
596          CASE ( 'pt_reference' )
597             READ ( 13 )  pt_reference
598          CASE ( 'pt_surface' )
599             READ ( 13 )  pt_surface
600          CASE ( 'pt_surface_initial_change' )
601             READ ( 13 )  pt_surface_initial_change
602          CASE ( 'pt_vertical_gradient' )
603             READ ( 13 )  pt_vertical_gradient
604          CASE ( 'pt_vertical_gradient_level' )
605             READ ( 13 )  pt_vertical_gradient_level
606          CASE ( 'pt_vertical_gradient_level_ind' )
607             READ ( 13 )  pt_vertical_gradient_level_ind
608          CASE ( 'q_init' )
609             READ ( 13 )  q_init
610          CASE ( 'q_surface' )
611             READ ( 13 )  q_surface
612          CASE ( 'q_surface_initial_change' )
613             READ ( 13 )  q_surface_initial_change
614          CASE ( 'q_vertical_gradient' )
615             READ ( 13 )  q_vertical_gradient
616          CASE ( 'q_vertical_gradient_level' )
617             READ ( 13 )  q_vertical_gradient_level
618          CASE ( 'q_vertical_gradient_level_ind' )
619             READ ( 13 )  q_vertical_gradient_level_ind
620          CASE ( 'cloud_top_radiation' )
621             READ ( 13 )  cloud_top_radiation
622          CASE ( 'random_generator' )
623             READ ( 13 )  random_generator
624          CASE ( 'random_heatflux' )
625             READ ( 13 )  random_heatflux
626          CASE ( 'rayleigh_damping_factor' )
627             READ ( 13 )  rayleigh_damping_factor
628          CASE ( 'rayleigh_damping_height' )
629             READ ( 13 )  rayleigh_damping_height
630          CASE ( 'recycling_width' )
631             READ ( 13 )  recycling_width
632          CASE ( 'recycling_yshift' )
633             READ ( 13 ) recycling_yshift
634          CASE ( 'reference_state' )
635             READ ( 13 )  reference_state
636          CASE ( 'ref_state' )
637             READ ( 13 )  ref_state
638          CASE ( 'residual_limit' )
639             READ ( 13 )  residual_limit
640          CASE ( 'roughness_length' )
641             READ ( 13 )  roughness_length
642          CASE ( 'runnr' )
643             READ ( 13 )  runnr
644          CASE ( 'run_coupled' )
645             READ ( 13 )  run_coupled
646          CASE ( 's_init' )
647             READ ( 13 )  s_init
648          CASE ( 's_surface' )
649             READ ( 13 )  s_surface
650          CASE ( 's_surface_initial_change' )
651             READ ( 13 )  s_surface_initial_change
652          CASE ( 's_vertical_gradient' )
653             READ ( 13 )  s_vertical_gradient
654          CASE ( 's_vertical_gradient_level' )
655             READ ( 13 )  s_vertical_gradient_level
656          CASE ( 's_vertical_gradient_level_ind' )
657             READ ( 13 )  s_vertical_gradient_level_ind
658          CASE ( 'sa_init' )
659             READ ( 13 )  sa_init
660          CASE ( 'sa_surface' )
661             READ ( 13 )  sa_surface
662          CASE ( 'sa_vertical_gradient' )
663             READ ( 13 )  sa_vertical_gradient
664          CASE ( 'sa_vertical_gradient_level' )
665             READ ( 13 )  sa_vertical_gradient_level
666          CASE ( 'scalar_advec' )
667             READ ( 13 )  scalar_advec
668          CASE ( 'simulated_time' )
669             READ ( 13 )  simulated_time
670          CASE ( 'surface_heatflux' )
671             READ ( 13 )  surface_heatflux
672          CASE ( 'surface_pressure' )
673             READ ( 13 )  surface_pressure
674          CASE ( 'surface_scalarflux' )
675             READ ( 13 )  surface_scalarflux
676          CASE ( 'surface_waterflux' )
677             READ ( 13 )  surface_waterflux
678          CASE ( 'time_coupling' )
679             READ ( 13 )  time_coupling
680          CASE ( 'time_disturb' )
681             READ ( 13 )  time_disturb
682          CASE ( 'time_dopr' )
683             READ ( 13 )  time_dopr
684          CASE ( 'time_domask' )
685             READ ( 13 )  time_domask
686          CASE ( 'time_dopr_av' )
687             READ ( 13 )  time_dopr_av
688          CASE ( 'time_dopr_listing' )
689             READ ( 13 )  time_dopr_listing
690          CASE ( 'time_dopts' )
691             READ ( 13 )  time_dopts
692          CASE ( 'time_dosp' )
693             READ ( 13 )  time_dosp
694          CASE ( 'time_dots' )
695             READ ( 13 )  time_dots
696          CASE ( 'time_do2d_xy' )
697             READ ( 13 )  time_do2d_xy
698          CASE ( 'time_do2d_xz' )
699             READ ( 13 )  time_do2d_xz
700          CASE ( 'time_do2d_yz' )
701             READ ( 13 )  time_do2d_yz
702          CASE ( 'time_do3d' )
703             READ ( 13 )  time_do3d
704          CASE ( 'time_do_av' )
705             READ ( 13 )  time_do_av
706          CASE ( 'time_do_sla' )
707             READ ( 13 )  time_do_sla
708          CASE ( 'time_dvrp' )
709             READ ( 13 )  time_dvrp
710          CASE ( 'time_radiation' )
711             READ ( 13 )  time_radiation
712          CASE ( 'time_restart' )
713             READ ( 13 )  time_restart
714          CASE ( 'time_run_control' )
715             READ ( 13 )  time_run_control
716          CASE ( 'time_since_reference_point' )
717             READ ( 13 )  time_since_reference_point
718          CASE ( 'timestep_scheme' )
719             READ ( 13 )  timestep_scheme
720          CASE ( 'topography' )
721             READ ( 13 )  topography
722          CASE ( 'topography_grid_convention' )
723             READ ( 13 )  topography_grid_convention
724          CASE ( 'top_heatflux' )
725             READ ( 13 )  top_heatflux
726          CASE ( 'top_momentumflux_u' )
727             READ ( 13 )  top_momentumflux_u
728          CASE ( 'top_momentumflux_v' )
729             READ ( 13 )  top_momentumflux_v
730          CASE ( 'top_salinityflux' )
731             READ ( 13 )  top_salinityflux
732          CASE ( 'top_scalarflux' )
733             READ ( 13 )  top_scalarflux
734          CASE ( 'tsc' )
735             READ ( 13 )  tsc
736          CASE ( 'collision_turbulence' )
737             READ ( 13 )  collision_turbulence
738          CASE ( 'tunnel_height' )
739             READ ( 13 )  tunnel_height
740          CASE ( 'tunnel_length' )
741             READ ( 13 )  tunnel_length
742          CASE ( 'tunnel_width_x' )
743             READ ( 13 )  tunnel_width_x
744          CASE ( 'tunnel_width_y' )
745             READ ( 13 )  tunnel_width_y
746          CASE ( 'tunnel_wall_depth' )
747             READ ( 13 )  tunnel_wall_depth
748          CASE ( 'turbulent_inflow' )
749             READ ( 13 )  turbulent_inflow
750          CASE ( 'u_bulk' )
751             READ ( 13 )  u_bulk
752          CASE ( 'u_init' )
753             READ ( 13 )  u_init
754          CASE ( 'u_max' )
755             READ ( 13 )  u_max
756          CASE ( 'u_max_ijk' )
757             READ ( 13 )  u_max_ijk
758          CASE ( 'ug' )
759             READ ( 13 )  ug
760          CASE ( 'ug_surface' )
761             READ ( 13 )  ug_surface
762          CASE ( 'ug_vertical_gradient' )
763             READ ( 13 )  ug_vertical_gradient
764          CASE ( 'ug_vertical_gradient_level' )
765             READ ( 13 )  ug_vertical_gradient_level
766          CASE ( 'ug_vertical_gradient_level_ind' )
767             READ ( 13 )  ug_vertical_gradient_level_ind
768          CASE ( 'use_surface_fluxes' )
769             READ ( 13 )  use_surface_fluxes
770          CASE ( 'use_top_fluxes' )
771             READ ( 13 )  use_top_fluxes
772          CASE ( 'use_ug_for_galilei_tr' )
773             READ ( 13 )  use_ug_for_galilei_tr
774          CASE ( 'use_upstream_for_tke' )
775             READ ( 13 )  use_upstream_for_tke
776          CASE ( 'v_bulk' )
777             READ ( 13 )  v_bulk
778          CASE ( 'v_init' )
779             READ ( 13 )  v_init
780          CASE ( 'v_max' )
781             READ ( 13 )  v_max
782          CASE ( 'v_max_ijk' )
783             READ ( 13 )  v_max_ijk
784          CASE ( 'ventilation_effect' )
785             READ ( 13 )  ventilation_effect
786          CASE ( 'vg' )
787             READ ( 13 )  vg
788          CASE ( 'vg_surface' )
789             READ ( 13 )  vg_surface
790          CASE ( 'vg_vertical_gradient' )
791             READ ( 13 )  vg_vertical_gradient
792          CASE ( 'vg_vertical_gradient_level' )
793             READ ( 13 )  vg_vertical_gradient_level
794          CASE ( 'vg_vertical_gradient_level_ind' )
795             READ ( 13 )  vg_vertical_gradient_level_ind
796          CASE ( 'virtual_flight' )
797             READ ( 13 )  virtual_flight
798          CASE ( 'vnest_init' )
799             READ ( 13 )  vnest_init
800          CASE ( 'volume_flow_area' )
801             READ ( 13 )  volume_flow_area
802          CASE ( 'volume_flow_initial' )
803             READ ( 13 )  volume_flow_initial
804          CASE ( 'wall_adjustment' )
805             READ ( 13 )  wall_adjustment
806          CASE ( 'subs_vertical_gradient' )
807             READ ( 13 )  subs_vertical_gradient
808          CASE ( 'subs_vertical_gradient_level' )
809             READ ( 13 )  subs_vertical_gradient_level
810          CASE ( 'subs_vertical_gradient_level_i' )
811             READ ( 13 )  subs_vertical_gradient_level_i
812          CASE ( 'wall_heatflux' )
813             READ ( 13 )  wall_heatflux
814          CASE ( 'wall_humidityflux' )
815             READ ( 13 )  wall_humidityflux
816          CASE ( 'wall_scalarflux' )
817             READ ( 13 )  wall_scalarflux
818          CASE ( 'wall_salinityflux' )
819             READ ( 13 )  wall_salinityflux
820          CASE ( 'w_max' )
821             READ ( 13 )  w_max
822          CASE ( 'w_max_ijk' )
823             READ ( 13 )  w_max_ijk
824          CASE ( 'y_shift' )
825             READ ( 13 )  y_shift
826          CASE ( 'zeta_max' )
827             READ ( 13 )  zeta_max
828          CASE ( 'zeta_min' )
829             READ ( 13 )  zeta_min
830          CASE ( 'z0h_factor' )
831             READ ( 13 )  z0h_factor
832
833          CASE DEFAULT
834             WRITE( message_string, * ) 'unknown variable named "',         &
835                                        TRIM( variable_chr ), '" found in', &
836                                        ' data from prior run on PE ', myid
837             CALL message( 'read_var_list', 'PA0302', 1, 2, 0, 6, 0 )
838        END SELECT
839!
840!--    Read next string
841       READ ( 13 )  variable_chr
842
843    ENDDO
844
845
846 END SUBROUTINE read_var_list
847
848
849
850!------------------------------------------------------------------------------!
851! Description:
852! ------------
853!> Skipping the global control variables from restart-file (binary format)
854!> except some information needed when reading restart data from a previous
855!> run which used a smaller total domain or/and a different domain decomposition.
856!------------------------------------------------------------------------------!
857
858 SUBROUTINE read_parts_of_var_list
859
860
861    USE arrays_3d,                                                             &
862        ONLY:  inflow_damping_factor, mean_inflow_profiles, ref_state, ug, vg
863
864    USE control_parameters
865
866    USE indices,                                                               &
867        ONLY:  nz, nx, nx_on_file, ny, ny_on_file
868
869    USE kinds
870
871    USE pegrid
872
873    USE statistics,                                                            &
874        ONLY:  statistic_regions, hom, hom_sum, pr_palm, u_max, u_max_ijk,     &
875               v_max, v_max_ijk, w_max, w_max_ijk
876
877    IMPLICIT NONE
878
879    CHARACTER (LEN=10) ::  version_on_file
880    CHARACTER (LEN=20) ::  momentum_advec_check
881    CHARACTER (LEN=20) ::  scalar_advec_check
882    CHARACTER (LEN=30) ::  variable_chr
883    CHARACTER (LEN=1)  ::  cdum
884
885    INTEGER(iwp) ::  max_pr_user_on_file
886    INTEGER(iwp) ::  nz_on_file
887    INTEGER(iwp) ::  statistic_regions_on_file
888    INTEGER(iwp) ::  tmp_mpru
889    INTEGER(iwp) ::  tmp_sr
890
891    REAL(wp), DIMENSION(:,:,:),   ALLOCATABLE ::  hom_sum_on_file
892    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  hom_on_file
893
894
895    CALL check_open( 13 )
896
897    READ ( 13 )  version_on_file
898
899
900!
901!-- Read number of PEs and horizontal index bounds of all PEs used in previous
902!-- run
903    READ ( 13 )  variable_chr
904    IF ( TRIM( variable_chr ) /= 'numprocs' )  THEN
905       WRITE( message_string, * ) 'numprocs not found in data from prior ', &
906                                  'run on PE ', myid
907       CALL message( 'read_parts_of_var_list', 'PA0297', 1, 2, 0, 6, 0 )
908    ENDIF
909    READ ( 13 )  numprocs_previous_run
910
911    IF ( .NOT. ALLOCATED( hor_index_bounds_previous_run ) )  THEN
912       ALLOCATE( hor_index_bounds_previous_run(4,0:numprocs_previous_run-1) )
913    ENDIF
914
915    READ ( 13 )  variable_chr
916    IF ( TRIM( variable_chr ) /= 'hor_index_bounds' )  THEN
917       WRITE( message_string, * ) 'hor_index_bounds not found in data from ', &
918                                  'prior run on PE ', myid
919       CALL message( 'read_parts_of_var_list', 'PA0298', 1, 2, 0, 6, 0 )
920    ENDIF
921    READ ( 13 )  hor_index_bounds_previous_run
922
923!
924!-- Read vertical number of gridpoints and number of different areas used
925!-- for computing statistics. Allocate arrays depending on these values,
926!-- which are needed for the following read instructions.
927    READ ( 13 )  variable_chr
928    IF ( TRIM( variable_chr ) /= 'nz' )  THEN
929       message_string = 'nz not found in restart data file'
930       CALL message( 'read_parts_of_var_list', 'PA0303', 1, 2, 0, 6, 0 )
931    ENDIF
932    READ ( 13 )  nz_on_file
933    IF ( nz_on_file /= nz )  THEN
934       WRITE( message_string, * ) 'mismatch concerning number of ',      &
935                                  'gridpoints along z',                  &
936                                  '&nz on file    = "', nz_on_file, '"', &
937                                  '&nz from run   = "', nz, '"'
938       CALL message( 'read_parts_of_var_list', 'PA0304', 1, 2, 0, 6, 0 )
939    ENDIF
940
941    READ ( 13 )  variable_chr
942    IF ( TRIM( variable_chr ) /= 'max_pr_user' )  THEN
943       message_string = 'max_pr_user not found in restart data file'
944       CALL message( 'read_parts_of_var_list', 'PA0305', 1, 2, 0, 6, 0 )
945    ENDIF
946    READ ( 13 )  max_pr_user_on_file
947    IF ( max_pr_user_on_file /= max_pr_user )  THEN
948       WRITE( message_string, * ) 'number of user profiles on res',           &
949                                  'tart data file differs from the current ', &
950                                  'run&max_pr_user on file    = "',           &
951                                  max_pr_user_on_file, '"',                   &
952                                  '&max_pr_user from run   = "',              &
953                                  max_pr_user, '"'
954       CALL message( 'read_parts_of_var_list', 'PA0306', 0, 0, 0, 6, 0 )
955       tmp_mpru = MIN( max_pr_user_on_file, max_pr_user )
956    ELSE
957       tmp_mpru = max_pr_user
958    ENDIF
959
960    READ ( 13 )  variable_chr
961    IF ( TRIM( variable_chr ) /= 'statistic_regions' )  THEN
962       message_string = 'statistic_regions not found in restart data file'
963       CALL message( 'read_parts_of_var_list', 'PA0307', 1, 2, 0, 6, 0 )
964    ENDIF
965    READ ( 13 )  statistic_regions_on_file
966    IF ( statistic_regions_on_file /= statistic_regions )  THEN
967       WRITE( message_string, * ) 'statistic regions on restart data file ',&
968                                  'differ from the current run',            &
969                                  '&statistic regions on file    = "',      &
970                                  statistic_regions_on_file, '"',           &
971                                  '&statistic regions from run   = "',      &
972                                   statistic_regions, '"',                  &
973                                  '&statistic data may be lost!'
974       CALL message( 'read_parts_of_var_list', 'PA0308', 0, 1, 0, 6, 0 )
975       tmp_sr = MIN( statistic_regions_on_file, statistic_regions )
976    ELSE
977       tmp_sr = statistic_regions
978    ENDIF
979
980!
981!-- Now read and check some control parameters and skip the rest
982    READ ( 13 )  variable_chr
983
984    DO  WHILE ( TRIM( variable_chr ) /= '*** end default ***' )
985
986       SELECT CASE ( TRIM( variable_chr ) )
987
988          CASE ( 'average_count_pr' )
989             READ ( 13 )  average_count_pr
990             IF ( average_count_pr /= 0 )  THEN
991                WRITE( message_string, * ) 'inflow profiles not temporally ',  &
992                               'averaged. &Averaging will be done now using ', &
993                               average_count_pr, ' samples.'
994                CALL message( 'read_parts_of_var_list', 'PA0309', &
995                                                                 0, 1, 0, 6, 0 )
996             ENDIF
997
998          CASE ( 'hom' )
999             ALLOCATE( hom_on_file(0:nz+1,2,pr_palm+max_pr_user_on_file, &
1000                       0:statistic_regions_on_file) )
1001             READ ( 13 )  hom_on_file
1002             hom(:,:,1:pr_palm+tmp_mpru,0:tmp_sr) = &
1003                          hom_on_file(:,:,1:pr_palm+tmp_mpru,0:tmp_sr)
1004             DEALLOCATE( hom_on_file )
1005
1006          CASE ( 'hom_sum' )
1007             ALLOCATE( hom_sum_on_file(0:nz+1,pr_palm+max_pr_user_on_file, &
1008                       0:statistic_regions_on_file) )
1009             READ ( 13 )  hom_sum_on_file
1010             hom_sum(:,1:pr_palm+tmp_mpru,0:tmp_sr) = &
1011                          hom_sum_on_file(:,1:pr_palm+tmp_mpru,0:tmp_sr)
1012             DEALLOCATE( hom_sum_on_file )
1013
1014          CASE ( 'momentum_advec' )
1015             momentum_advec_check = momentum_advec
1016             READ ( 13 )  momentum_advec
1017             IF ( TRIM( momentum_advec_check ) /= TRIM( momentum_advec ) )  THEN
1018                WRITE( message_string, * ) 'momentum_advec of the restart run ',&
1019                               'differs from momentum_advec of the initial run.'
1020                CALL message( 'read_parts_of_var_list', 'PA0100', &
1021                                                                 1, 2, 0, 6, 0 )
1022             END IF
1023
1024          CASE ( 'nx' )
1025             READ ( 13 )  nx_on_file
1026
1027          CASE ( 'ny' )
1028             READ ( 13 )  ny_on_file
1029
1030          CASE ( 'ref_state' )
1031             READ ( 13 )  ref_state
1032
1033          CASE ( 'scalar_advec' )
1034             scalar_advec_check = scalar_advec
1035             READ ( 13 )  scalar_advec
1036             IF ( TRIM( scalar_advec_check ) /= TRIM( scalar_advec ) )  THEN
1037                WRITE( message_string, * ) 'scalar_advec of the restart run ', &
1038                               'differs from scalar_advec of the initial run.'
1039                CALL message( 'read_parts_of_var_list', 'PA0101', &
1040                                                                 1, 2, 0, 6, 0 )
1041             END IF
1042
1043          CASE DEFAULT
1044
1045             READ ( 13 )  cdum
1046
1047       END SELECT
1048
1049       READ ( 13 )  variable_chr
1050
1051    ENDDO
1052
1053!
1054!-- Calculate the temporal average of vertical profiles, if neccessary
1055    IF ( average_count_pr /= 0 )  THEN
1056       hom_sum = hom_sum / REAL( average_count_pr, KIND=wp )
1057    ENDIF
1058
1059
1060 END SUBROUTINE read_parts_of_var_list
1061
1062
1063
1064!------------------------------------------------------------------------------!
1065! Description:
1066! ------------
1067!> Skipping the global control variables from restart-file (binary format)
1068!------------------------------------------------------------------------------!
1069
1070 SUBROUTINE skip_var_list
1071
1072
1073    IMPLICIT NONE
1074
1075    CHARACTER (LEN=10) ::  version_on_file
1076    CHARACTER (LEN=30) ::  variable_chr
1077
1078    CHARACTER (LEN=1) ::  cdum
1079
1080
1081    READ ( 13 )  version_on_file
1082
1083    READ ( 13 )  variable_chr
1084
1085    DO  WHILE ( TRIM( variable_chr ) /= '*** end ***' )
1086
1087       READ ( 13 )  cdum
1088       READ ( 13 )  variable_chr
1089
1090    ENDDO
1091
1092
1093 END SUBROUTINE skip_var_list
Note: See TracBrowser for help on using the repository browser.