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

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

modularized 1d model

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