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

Last change on this file since 2350 was 2339, checked in by gronemeier, 7 years ago

corrected timestamp in header

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