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

Last change on this file since 2316 was 2265, checked in by schwenkel, 7 years ago

unused variables removed

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