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

Last change on this file since 2331 was 2320, checked in by suehring, 7 years ago

large-scale forcing and nudging modularized

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