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

Last change on this file since 2512 was 2372, checked in by sward, 7 years ago

y_shift for periodic boundary conditions

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