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

Last change on this file since 2365 was 2365, checked in by kanani, 7 years ago

Vertical nesting implemented (SadiqHuq?)

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