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

Last change on this file since 1958 was 1958, checked in by suehring, 8 years ago

last commit documented

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