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

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

last commit documented

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