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

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

NetCDF routines modularized; new parameter netcdf_deflate; further changes in the pmc

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