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

Last change on this file since 1682 was 1682, checked in by knoop, 9 years ago

Code annotations made doxygen readable

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