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

Last change on this file since 1832 was 1832, checked in by hoffmann, 8 years ago

last commit documented

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