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

Last change on this file since 2575 was 2575, checked in by maronga, 6 years ago

bugfix in radiation model and improvements in land surface scheme

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