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

Last change on this file since 2776 was 2776, checked in by Giersch, 6 years ago

Skipping of module related restart data changed + adapting synthetic turbulence generator to current restart procedure

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