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

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

Implemented synthetic turbulence generator

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