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

Last change on this file since 1805 was 1784, checked in by raasch, 8 years ago

last commit documented

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