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

Last change on this file since 2000 was 2000, checked in by knoop, 8 years ago

Forced header and separation lines into 80 columns

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