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

Last change on this file since 1691 was 1691, checked in by maronga, 9 years ago

various bugfixes and modifications of the atmosphere-land-surface-radiation interaction. Completely re-written routine to calculate surface fluxes (surface_layer_fluxes.f90) that replaces prandtl_fluxes. Minor formatting corrections and renamings

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