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

Last change on this file since 1575 was 1561, checked in by keck, 9 years ago

last commit documented

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