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

Last change on this file since 1763 was 1700, checked in by maronga, 8 years ago

last commit documented

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