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

Last change on this file since 367 was 345, checked in by heinze, 15 years ago

In case of restart runs without extension, initial profiles are not written to NetCDF-file anymore.

  • Property svn:keywords set to Id
File size: 30.4 KB
Line 
1 SUBROUTINE read_var_list
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6! +output_for_t0
7! dt_fixed is read into a dummy variable.
8! Output of messages replaced by message handling routine.
9! +canyon_height, canyon_width_x, canyon_width_y, canyon_wall_left,
10! canyon_wall_south, conserve_volume_flow_mode, coupling_start_time,
11! dp_external, dp_level_b, dp_smooth, dpdxy, run_coupled,
12! time_since_reference_point, topography_grid_convention, u_bulk, v_bulk
13!
14! Former revisions:
15! -----------------
16! $Id: read_var_list.f90 345 2009-07-01 14:37:56Z maronga $
17!
18! 216 2008-11-25 07:12:43Z raasch
19! limitations for nx_on_file, ny_on_file removed (read_parts_of_var_list)
20!
21! 173 2008-05-23 20:39:38Z raasch
22! +cthf, leaf_surface_concentration, scalar_exchange_coefficient
23! +numprocs_previous_run, hor_index_bounds_previous_run, inflow_damping_factor,
24! inflow_damping_height, inflow_damping_width, mean_inflow_profiles,
25! recycling_width, turbulent_inflow,
26! -cross_ts_*, npex, npey,
27! hom_sum, volume_flow_area, volume_flow_initial moved from
28! read_3d_binary to here,
29! routines read_parts_of_var_list and skip_var_list added at the end
30!
31! 138 2007-11-28 10:03:58Z letzel
32! +canopy_mode, drag_coefficient, lad, lad_surface, lad_vertical_gradient,
33! lad_vertical_gradient_level, lad_vertical_gradient_level_ind, pch_index,
34! plant_canopy, time_sort_particles
35!
36! 102 2007-07-27 09:09:17Z raasch
37! +time_coupling, top_momentumflux_u|v
38!
39! 95 2007-06-02 16:48:38Z raasch
40! +bc_sa_t, ocean, sa_init, sa_surface, sa_vertical_gradient,
41! sa_vertical_gradient_level, bottom/top_salinity_flux
42!
43! 87 2007-05-22 15:46:47Z raasch
44! +max_pr_user (version 3.1), var_hom renamed pr_palm
45!
46! 75 2007-03-22 09:54:05Z raasch
47! +loop_optimization, pt_reference, moisture renamed humidity
48!
49! 20 2007-02-26 00:12:32Z raasch
50! +top_heatflux, use_top_fluxes
51!
52! RCS Log replace by Id keyword, revision history cleaned up
53!
54! Revision 1.34  2006/08/22 14:14:27  raasch
55! +dz_max
56!
57! Revision 1.1  1998/03/18 20:18:48  raasch
58! Initial revision
59!
60!
61! Description:
62! ------------
63! Reading values of global control variables from restart-file (binary format)
64!------------------------------------------------------------------------------!
65
66    USE arrays_3d
67    USE averaging
68    USE control_parameters
69    USE grid_variables
70    USE indices
71    USE model_1d
72    USE netcdf_control
73    USE particle_attributes
74    USE pegrid
75    USE profil_parameter
76    USE statistics
77
78    IMPLICIT NONE
79
80    CHARACTER (LEN=10) ::  binary_version, version_on_file
81    CHARACTER (LEN=30) ::  variable_chr
82
83    LOGICAL ::  ldum
84
85
86    CALL check_open( 13 )
87
88!
89!-- Make version number check first
90    READ ( 13 )  version_on_file
91    binary_version = '3.4'
92    IF ( TRIM( version_on_file ) /= TRIM( binary_version ) )  THEN
93       WRITE( message_string, * ) 'version mismatch concerning control ', &
94                                  'variables',                            &
95                                  '&version on file    = "',              &
96                                  TRIM( version_on_file ), '"',           &
97                                  '&version on program = "',              &
98                                  TRIM( binary_version ), '"'
99       CALL message( 'read_var_list', 'PA0296', 1, 2, 0, 6, 0 )
100    ENDIF
101
102!
103!-- Read number of PEs and horizontal index bounds of all PEs used in previous
104!-- run
105    READ ( 13 )  variable_chr
106    IF ( TRIM( variable_chr ) /= 'numprocs' )  THEN
107       WRITE( message_string, * ) 'numprocs not found in data from prior ', &
108                                  'run on PE ', myid
109       CALL message( 'read_var_list', 'PA0297', 1, 2, 0, 6, 0 )
110    ENDIF
111    READ ( 13 )  numprocs_previous_run
112
113    IF ( .NOT. ALLOCATED( hor_index_bounds_previous_run ) )  THEN
114       ALLOCATE( hor_index_bounds_previous_run(4,0:numprocs_previous_run-1) )
115    ENDIF
116
117    READ ( 13 )  variable_chr
118    IF ( TRIM( variable_chr ) /= 'hor_index_bounds' )  THEN
119       WRITE( message_string, * ) 'hor_index_bounds not found in data from ', &
120                                  'prior run on PE ', myid
121       CALL message( 'read_var_list', 'PA0298', 1, 2, 0, 6, 0 )
122    ENDIF
123    READ ( 13 )  hor_index_bounds_previous_run
124
125!
126!-- Read vertical number of gridpoints and number of different areas used
127!-- for computing statistics. Allocate arrays depending on these values,
128!-- which are needed for the following read instructions.
129    READ ( 13 )  variable_chr
130    IF ( TRIM( variable_chr ) /= 'nz' )  THEN
131       WRITE( message_string, * ) 'nz not found in data from prior run on PE ',&
132                                  myid
133       CALL message( 'read_var_list', 'PA0299', 1, 2, 0, 6, 0 )
134    ENDIF
135    READ ( 13 )  nz
136
137    READ ( 13 )  variable_chr
138    IF ( TRIM( variable_chr ) /= 'max_pr_user' )  THEN
139       WRITE( message_string, * ) 'max_pr_user not found in data from ', &
140                    'prior run on PE ', myid
141       CALL message( 'read_var_list', 'PA0300', 1, 2, 0, 6, 0 )
142    ENDIF
143    READ ( 13 )  max_pr_user    ! This value is checked against the number of
144                                ! user profiles given for the current run
145                                ! in routine user_parin (it has to match)
146
147    READ ( 13 )  variable_chr
148    IF ( TRIM( variable_chr ) /= 'statistic_regions' )  THEN
149       WRITE( message_string, * ) 'statistic_regions not found in data from ', &
150                    'prior run on PE ', myid
151       CALL message( 'read_var_list', 'PA0301', 1, 2, 0, 6, 0 )
152    ENDIF
153    READ ( 13 )  statistic_regions
154    IF ( .NOT. ALLOCATED( ug ) )  THEN
155       ALLOCATE( lad(0:nz+1), ug(0:nz+1), u_init(0:nz+1), vg(0:nz+1),    &
156                 v_init(0:nz+1), pt_init(0:nz+1), q_init(0:nz+1),        &
157                 sa_init(0:nz+1),                                        &
158                 hom(0:nz+1,2,pr_palm+max_pr_user,0:statistic_regions),  &
159                 hom_sum(0:nz+1,pr_palm+max_pr_user,0:statistic_regions) )
160    ENDIF
161
162!
163!-- Now read all control parameters:
164!-- Caution: When the following read instructions have been changed, the
165!-- -------  version number stored in the variable binary_version has to be
166!--          increased. The same changes must also be done in write_var_list.
167    READ ( 13 )  variable_chr
168    DO  WHILE ( TRIM( variable_chr ) /= '*** end ***' )
169
170       SELECT CASE ( TRIM( variable_chr ) )
171
172          CASE ( 'adjust_mixing_length' )
173             READ ( 13 )  adjust_mixing_length
174          CASE ( 'advected_distance_x' )
175             READ ( 13 )  advected_distance_x
176          CASE ( 'advected_distance_y' )
177             READ ( 13 )  advected_distance_y
178          CASE ( 'alpha_surface' )
179             READ ( 13 )  alpha_surface
180          CASE ( 'average_count_pr' )
181             READ ( 13 )  average_count_pr
182          CASE ( 'average_count_sp' )
183             READ ( 13 )  average_count_sp
184          CASE ( 'average_count_3d' )
185             READ ( 13 )  average_count_3d
186          CASE ( 'bc_e_b' )
187             READ ( 13 )  bc_e_b
188          CASE ( 'bc_lr' )
189             READ ( 13 )  bc_lr
190          CASE ( 'bc_ns' )
191             READ ( 13 )  bc_ns
192          CASE ( 'bc_p_b' )
193             READ ( 13 )  bc_p_b
194          CASE ( 'bc_p_t' )
195             READ ( 13 )  bc_p_t
196          CASE ( 'bc_pt_b' )
197             READ ( 13 )  bc_pt_b
198          CASE ( 'bc_pt_t' )
199             READ ( 13 )  bc_pt_t
200          CASE ( 'bc_pt_t_val' )
201             READ ( 13 )  bc_pt_t_val
202          CASE ( 'bc_q_b' )
203             READ ( 13 )  bc_q_b
204          CASE ( 'bc_q_t' )
205             READ ( 13 )  bc_q_t
206          CASE ( 'bc_q_t_val' )
207             READ ( 13 )  bc_q_t_val
208          CASE ( 'bc_s_b' )
209             READ ( 13 )  bc_s_b
210          CASE ( 'bc_s_t' )
211             READ ( 13 )  bc_s_t
212          CASE ( 'bc_sa_t' )
213             READ ( 13 )  bc_sa_t
214          CASE ( 'bc_uv_b' )
215             READ ( 13 )  bc_uv_b
216          CASE ( 'bc_uv_t' )
217             READ ( 13 )  bc_uv_t
218          CASE ( 'bottom_salinityflux' )
219             READ ( 13 )  bottom_salinityflux
220          CASE ( 'building_height' )
221             READ ( 13 )  building_height
222          CASE ( 'building_length_x' )
223             READ ( 13 )  building_length_x
224          CASE ( 'building_length_y' )
225             READ ( 13 )  building_length_y
226          CASE ( 'building_wall_left' )
227             READ ( 13 )  building_wall_left
228          CASE ( 'building_wall_south' )
229             READ ( 13 )  building_wall_south
230          CASE ( 'canopy_mode' )
231             READ ( 13 )  canopy_mode
232          CASE ( 'canyon_height' )
233             READ ( 13 )  canyon_height
234          CASE ( 'canyon_width_x' )
235             READ ( 13 )  canyon_width_x
236          CASE ( 'canyon_width_y' )
237             READ ( 13 )  canyon_width_y
238          CASE ( 'canyon_wall_left' )
239             READ ( 13 )  canyon_wall_left
240          CASE ( 'canyon_wall_south' )
241             READ ( 13 )  canyon_wall_south
242          CASE ( 'cloud_droplets' )
243             READ ( 13 )  cloud_droplets
244          CASE ( 'cloud_physics' )
245             READ ( 13 )  cloud_physics
246          CASE ( 'conserve_volume_flow' )
247             READ ( 13 )  conserve_volume_flow
248          CASE ( 'conserve_volume_flow_mode' )
249             READ ( 13 )  conserve_volume_flow_mode
250          CASE ( 'coupling_start_time' )
251             READ ( 13 )  coupling_start_time
252          CASE ( 'cthf' )
253             READ ( 13 )  cthf
254          CASE ( 'current_timestep_number' )
255             READ ( 13 )  current_timestep_number
256          CASE ( 'cut_spline_overshoot' )
257             READ ( 13 )  cut_spline_overshoot
258          CASE ( 'damp_level_1d' )
259             READ ( 13 )  damp_level_1d
260          CASE ( 'dissipation_1d' )
261             READ ( 13 )  dissipation_1d
262          CASE ( 'dp_external' )
263             READ ( 13 )  dp_external
264          CASE ( 'dp_level_b' )
265             READ ( 13 )  dp_level_b
266          CASE ( 'dp_smooth' )
267             READ ( 13 )  dp_smooth
268          CASE ( 'dpdxy' )
269             READ ( 13 )  dpdxy
270          CASE ( 'drag_coefficient' )
271             READ ( 13 )  drag_coefficient
272          CASE ( 'dt_fixed' )
273             READ ( 13 )  ldum   ! restart files created before rev 333
274                                 ! contained dt_fixed by mistake; it is still
275                                 ! read here in order to allow usage of these
276                                 ! older restart files; can be removed in a
277                                 ! later version
278          CASE ( 'dt_pr_1d' )
279             READ ( 13 )  dt_pr_1d
280          CASE ( 'dt_run_control_1d' )
281             READ ( 13 )  dt_run_control_1d
282          CASE ( 'dt_3d' )
283             READ ( 13 )  dt_3d
284          CASE ( 'dvrp_filecount' )
285             READ ( 13 )  dvrp_filecount
286          CASE ( 'dx' )
287             READ ( 13 )  dx
288          CASE ( 'dy' )
289             READ ( 13 )  dy
290          CASE ( 'dz' )
291             READ ( 13 )  dz
292          CASE ( 'dz_max' )
293             READ ( 13 )  dz_max
294          CASE ( 'dz_stretch_factor' )
295             READ ( 13 )  dz_stretch_factor
296          CASE ( 'dz_stretch_level' )
297             READ ( 13 )  dz_stretch_level
298          CASE ( 'e_min' )
299             READ ( 13 )  e_min
300          CASE ( 'end_time_1d' )
301             READ ( 13 )  end_time_1d
302          CASE ( 'fft_method' )
303             READ ( 13 )  fft_method
304          CASE ( 'first_call_advec_particles' )
305             READ ( 13 )  first_call_advec_particles
306          CASE ( 'galilei_transformation' )
307             READ ( 13 )  galilei_transformation
308          CASE ( 'grid_matching' )
309             READ ( 13 )  grid_matching
310          CASE ( 'hom' )
311             READ ( 13 )  hom
312          CASE ( 'hom_sum' )
313             READ ( 13 )  hom_sum
314          CASE ( 'humidity' )
315             READ ( 13 )  humidity
316          CASE ( 'inflow_damping_factor' )
317             IF ( .NOT. ALLOCATED( inflow_damping_factor ) )  THEN
318                ALLOCATE( inflow_damping_factor(0:nz+1) )
319             ENDIF
320             READ ( 13 )  inflow_damping_factor
321          CASE ( 'inflow_damping_height' )
322             READ ( 13 )  inflow_damping_height
323          CASE ( 'inflow_damping_width' )
324             READ ( 13 )  inflow_damping_width
325          CASE ( 'inflow_disturbance_begin' )
326             READ ( 13 )  inflow_disturbance_begin
327          CASE ( 'inflow_disturbance_end' )
328             READ ( 13 )  inflow_disturbance_end
329          CASE ( 'km_constant' )
330             READ ( 13 )  km_constant
331          CASE ( 'km_damp_max' )
332             READ ( 13 )  km_damp_max
333          CASE ( 'lad' )
334             READ ( 13 )  lad
335          CASE ( 'lad_surface' )
336             READ ( 13 )  lad_surface
337          CASE ( 'lad_vertical_gradient' )
338             READ ( 13 )  lad_vertical_gradient
339          CASE ( 'lad_vertical_gradient_level' )
340             READ ( 13 )  lad_vertical_gradient_level
341          CASE ( 'lad_vertical_gradient_level_in' )
342             READ ( 13 )  lad_vertical_gradient_level_ind
343          CASE ( 'last_dt_change' )
344             READ ( 13 )  last_dt_change
345          CASE ( 'leaf_surface_concentration' )
346             READ ( 13 )  leaf_surface_concentration
347          CASE ( 'long_filter_factor' )
348             READ ( 13 )  long_filter_factor
349          CASE ( 'loop_optimization' )
350             READ ( 13 )  loop_optimization
351          CASE ( 'mean_inflow_profiles' )
352             IF ( .NOT. ALLOCATED( mean_inflow_profiles ) )  THEN
353                ALLOCATE( mean_inflow_profiles(0:nz+1,5) )
354             ENDIF
355             READ ( 13 )  mean_inflow_profiles
356          CASE ( 'mixing_length_1d' )
357             READ ( 13 )  mixing_length_1d
358          CASE ( 'momentum_advec' )
359             READ ( 13 )  momentum_advec
360          CASE ( 'netcdf_precision' )
361             READ ( 13 )  netcdf_precision
362          CASE ( 'nsor_ini' )
363             READ ( 13 )  nsor_ini
364          CASE ( 'nx' )
365             READ ( 13 )  nx
366             nx_on_file = nx
367          CASE ( 'ny' )
368             READ ( 13 )  ny
369             ny_on_file = ny
370          CASE ( 'ocean' )
371             READ ( 13 )  ocean
372          CASE ( 'old_dt' )
373             READ ( 13 )  old_dt
374          CASE ( 'omega' )
375             READ ( 13 )  omega
376          CASE ( 'outflow_damping_width' )
377             READ ( 13 )  outflow_damping_width
378          CASE ( 'output_for_t0' )
379             READ (13)    output_for_t0
380          CASE ( 'overshoot_limit_e' )
381             READ ( 13 )  overshoot_limit_e
382          CASE ( 'overshoot_limit_pt' )
383             READ ( 13 )  overshoot_limit_pt
384          CASE ( 'overshoot_limit_u' )
385             READ ( 13 )  overshoot_limit_u
386          CASE ( 'overshoot_limit_v' )
387             READ ( 13 )  overshoot_limit_v
388          CASE ( 'overshoot_limit_w' )
389             READ ( 13 )  overshoot_limit_w
390          CASE ( 'passive_scalar' )
391             READ ( 13 )  passive_scalar
392          CASE ( 'pch_index' )
393             READ ( 13 )  pch_index
394          CASE ( 'phi' )
395             READ ( 13 )  phi
396          CASE ( 'plant_canopy' )
397             READ ( 13 )  plant_canopy
398          CASE ( 'prandtl_layer' )
399             READ ( 13 )  prandtl_layer
400          CASE ( 'precipitation' )
401             READ ( 13 ) precipitation
402          CASE ( 'pt_init' )
403             READ ( 13 )  pt_init
404          CASE ( 'pt_reference' )
405             READ ( 13 )  pt_reference
406          CASE ( 'pt_surface' )
407             READ ( 13 )  pt_surface
408          CASE ( 'pt_surface_initial_change' )
409             READ ( 13 )  pt_surface_initial_change
410          CASE ( 'pt_vertical_gradient' )
411             READ ( 13 )  pt_vertical_gradient
412          CASE ( 'pt_vertical_gradient_level' )
413             READ ( 13 )  pt_vertical_gradient_level
414          CASE ( 'pt_vertical_gradient_level_ind' )
415             READ ( 13 )  pt_vertical_gradient_level_ind
416          CASE ( 'q_init' )
417             READ ( 13 )  q_init
418          CASE ( 'q_surface' )
419             READ ( 13 )  q_surface
420          CASE ( 'q_surface_initial_change' )
421             READ ( 13 )  q_surface_initial_change
422          CASE ( 'q_vertical_gradient' )
423             READ ( 13 )  q_vertical_gradient
424          CASE ( 'q_vertical_gradient_level' )
425             READ ( 13 )  q_vertical_gradient_level
426          CASE ( 'q_vertical_gradient_level_ind' )
427             READ ( 13 )  q_vertical_gradient_level_ind
428          CASE ( 'radiation' )
429             READ ( 13 )  radiation
430          CASE ( 'random_generator' )
431             READ ( 13 )  random_generator
432          CASE ( 'random_heatflux' )
433             READ ( 13 )  random_heatflux
434          CASE ( 'recycling_width' )
435             READ ( 13 )  recycling_width
436          CASE ( 'rif_max' )
437             READ ( 13 )  rif_max
438          CASE ( 'rif_min' )
439             READ ( 13 )  rif_min
440          CASE ( 'roughness_length' )
441             READ ( 13 )  roughness_length
442          CASE ( 'runnr' )
443             READ ( 13 )  runnr
444          CASE ( 'run_coupled' )
445             READ ( 13 )  run_coupled
446          CASE ( 'sa_init' )
447             READ ( 13 )  sa_init
448          CASE ( 'sa_surface' )
449             READ ( 13 )  sa_surface
450          CASE ( 'sa_vertical_gradient' )
451             READ ( 13 )  sa_vertical_gradient
452          CASE ( 'sa_vertical_gradient_level' )
453             READ ( 13 )  sa_vertical_gradient_level
454          CASE ( 'scalar_advec' )
455             READ ( 13 )  scalar_advec
456          CASE ( 'scalar_exchange_coefficient' )
457             READ ( 13 )  scalar_exchange_coefficient
458          CASE ( 'simulated_time' )
459             READ ( 13 )  simulated_time
460          CASE ( 'surface_heatflux' )
461             READ ( 13 )  surface_heatflux
462          CASE ( 'surface_pressure' )
463             READ ( 13 )  surface_pressure
464          CASE ( 'surface_scalarflux' )
465             READ ( 13 )  surface_scalarflux             
466          CASE ( 'surface_waterflux' )
467             READ ( 13 )  surface_waterflux             
468          CASE ( 's_surface' )
469             READ ( 13 )  s_surface
470          CASE ( 's_surface_initial_change' )
471             READ ( 13 )  s_surface_initial_change
472          CASE ( 's_vertical_gradient' )
473             READ ( 13 )  s_vertical_gradient
474          CASE ( 's_vertical_gradient_level' )
475             READ ( 13 )  s_vertical_gradient_level
476          CASE ( 'time_coupling' )
477             READ ( 13 )  time_coupling
478          CASE ( 'time_disturb' )
479             READ ( 13 )  time_disturb
480          CASE ( 'time_dopr' )
481             READ ( 13 )  time_dopr
482          CASE ( 'time_dopr_av' )
483             READ ( 13 )  time_dopr_av
484          CASE ( 'time_dopr_listing' )
485             READ ( 13 )  time_dopr_listing
486          CASE ( 'time_dopts' )
487             READ ( 13 )  time_dopts
488          CASE ( 'time_dosp' )
489             READ ( 13 )  time_dosp
490          CASE ( 'time_dots' )
491             READ ( 13 )  time_dots
492          CASE ( 'time_do2d_xy' )
493             READ ( 13 )  time_do2d_xy
494          CASE ( 'time_do2d_xz' )
495             READ ( 13 )  time_do2d_xz
496          CASE ( 'time_do2d_yz' )
497             READ ( 13 )  time_do2d_yz
498          CASE ( 'time_do3d' )
499             READ ( 13 )  time_do3d
500          CASE ( 'time_do_av' )
501             READ ( 13 )  time_do_av
502          CASE ( 'time_do_sla' )
503             READ ( 13 )  time_do_sla
504          CASE ( 'time_dvrp' )
505             READ ( 13 )  time_dvrp
506          CASE ( 'time_restart' )
507             READ ( 13 )  time_restart
508          CASE ( 'time_run_control' )
509             READ ( 13 )  time_run_control
510          CASE ( 'time_since_reference_point' )
511             READ ( 13 )  time_since_reference_point
512          CASE ( 'time_sort_particles' )
513             READ ( 13 )  time_sort_particles
514          CASE ( 'timestep_scheme' )
515             READ ( 13 )  timestep_scheme
516          CASE ( 'topography' )
517             READ ( 13 )  topography
518          CASE ( 'topography_grid_convention' )
519             READ ( 13 )  topography_grid_convention
520          CASE ( 'top_heatflux' )
521             READ ( 13 )  top_heatflux
522          CASE ( 'top_momentumflux_u' )
523             READ ( 13 )  top_momentumflux_u
524          CASE ( 'top_momentumflux_v' )
525             READ ( 13 )  top_momentumflux_v
526          CASE ( 'top_salinityflux' )
527             READ ( 13 )  top_salinityflux
528          CASE ( 'tsc' )
529             READ ( 13 )  tsc
530          CASE ( 'turbulent_inflow' )
531             READ ( 13 )  turbulent_inflow
532          CASE ( 'u_bulk' )
533             READ ( 13 )  u_bulk
534          CASE ( 'u_init' )
535             READ ( 13 )  u_init
536          CASE ( 'u_max' )
537             READ ( 13 )  u_max
538          CASE ( 'u_max_ijk' )
539             READ ( 13 )  u_max_ijk
540          CASE ( 'ug' )
541             READ ( 13 )  ug
542          CASE ( 'ug_surface' )
543             READ ( 13 )  ug_surface
544          CASE ( 'ug_vertical_gradient' )
545             READ ( 13 )  ug_vertical_gradient
546          CASE ( 'ug_vertical_gradient_level' )
547             READ ( 13 )  ug_vertical_gradient_level
548          CASE ( 'ug_vertical_gradient_level_ind' )
549             READ ( 13 )  ug_vertical_gradient_level_ind
550          CASE ( 'ups_limit_e' )
551             READ ( 13 )  ups_limit_e
552          CASE ( 'ups_limit_pt' )
553             READ ( 13 )  ups_limit_pt
554          CASE ( 'ups_limit_u' )
555             READ ( 13 )  ups_limit_u
556          CASE ( 'ups_limit_v' )
557             READ ( 13 )  ups_limit_v
558          CASE ( 'ups_limit_w' )
559             READ ( 13 )  ups_limit_w
560          CASE ( 'use_surface_fluxes' )
561             READ ( 13 )  use_surface_fluxes
562          CASE ( 'use_top_fluxes' )
563             READ ( 13 )  use_top_fluxes
564          CASE ( 'use_ug_for_galilei_tr' )
565             READ ( 13 )  use_ug_for_galilei_tr
566          CASE ( 'use_upstream_for_tke' )
567             READ ( 13 )  use_upstream_for_tke
568          CASE ( 'v_bulk' )
569             READ ( 13 )  v_bulk
570          CASE ( 'v_init' )
571             READ ( 13 )  v_init
572          CASE ( 'v_max' )
573             READ ( 13 )  v_max
574          CASE ( 'v_max_ijk' )
575             READ ( 13 )  v_max_ijk
576          CASE ( 'vg' )
577             READ ( 13 )  vg
578          CASE ( 'vg_surface' )
579             READ ( 13 )  vg_surface
580          CASE ( 'vg_vertical_gradient' )
581             READ ( 13 )  vg_vertical_gradient
582          CASE ( 'vg_vertical_gradient_level' )
583             READ ( 13 )  vg_vertical_gradient_level
584          CASE ( 'vg_vertical_gradient_level_ind' )
585             READ ( 13 )  vg_vertical_gradient_level_ind
586          CASE ( 'volume_flow_area' )
587             READ ( 13 )  volume_flow_area
588          CASE ( 'volume_flow_initial' )
589             READ ( 13 )  volume_flow_initial
590          CASE ( 'wall_adjustment' )
591             READ ( 13 )  wall_adjustment
592          CASE ( 'w_max' )
593             READ ( 13 )  w_max
594          CASE ( 'w_max_ijk' )
595             READ ( 13 )  w_max_ijk
596
597          CASE DEFAULT
598             WRITE( message_string, * ) 'unknown variable named "',         &
599                                        TRIM( variable_chr ), '" found in', &
600                                        ' data from prior run on PE ', myid 
601             CALL message( 'read_var_list', 'PA0302', 1, 2, 0, 6, 0 )
602        END SELECT
603!
604!--    Read next string
605       READ ( 13 )  variable_chr
606
607    ENDDO
608
609
610 END SUBROUTINE read_var_list
611
612
613
614 SUBROUTINE read_parts_of_var_list
615
616!------------------------------------------------------------------------------!
617! Description:
618! ------------
619! Skipping the global control variables from restart-file (binary format)
620! except some informations needed when reading restart data from a previous
621! run which used a smaller total domain or/and a different domain decomposition.
622!------------------------------------------------------------------------------!
623
624    USE arrays_3d
625    USE control_parameters
626    USE indices
627    USE pegrid
628    USE statistics
629
630    IMPLICIT NONE
631
632    CHARACTER (LEN=10) ::  version_on_file
633    CHARACTER (LEN=30) ::  variable_chr
634
635    INTEGER ::  idum, max_pr_user_on_file, nz_on_file, &
636                statistic_regions_on_file, tmp_mpru, tmp_sr
637
638    REAL, DIMENSION(:,:,:),   ALLOCATABLE ::  hom_sum_on_file
639    REAL, DIMENSION(:,:,:,:), ALLOCATABLE ::  hom_on_file
640
641
642    CALL check_open( 13 )
643
644    WRITE (9,*) 'rpovl: after check open 13'
645    CALL local_flush( 9 )
646    READ ( 13 )  version_on_file
647
648!
649!-- Read number of PEs and horizontal index bounds of all PEs used in previous
650!-- run
651    READ ( 13 )  variable_chr
652    IF ( TRIM( variable_chr ) /= 'numprocs' )  THEN
653       WRITE( message_string, * ) 'numprocs not found in data from prior ', &
654                                  'run on PE ', myid
655       CALL message( 'read_parts_of_var_list', 'PA0297', 1, 2, 0, 6, 0 )
656    ENDIF
657    READ ( 13 )  numprocs_previous_run
658
659    IF ( .NOT. ALLOCATED( hor_index_bounds_previous_run ) )  THEN
660       ALLOCATE( hor_index_bounds_previous_run(4,0:numprocs_previous_run-1) )
661    ENDIF
662
663    READ ( 13 )  variable_chr
664    IF ( TRIM( variable_chr ) /= 'hor_index_bounds' )  THEN
665       WRITE( message_string, * ) 'hor_index_bounds not found in data from ', &
666                                  'prior run on PE ', myid
667       CALL message( 'read_parts_of_var_list', 'PA0298', 1, 2, 0, 6, 0 )
668    ENDIF
669    READ ( 13 )  hor_index_bounds_previous_run
670
671!
672!-- Read vertical number of gridpoints and number of different areas used
673!-- for computing statistics. Allocate arrays depending on these values,
674!-- which are needed for the following read instructions.
675    READ ( 13 )  variable_chr
676    IF ( TRIM( variable_chr ) /= 'nz' )  THEN
677       message_string = 'nz not found in restart data file'
678       CALL message( 'read_parts_of_var_list', 'PA0303', 1, 2, 0, 6, 0 )
679    ENDIF
680    READ ( 13 )  nz_on_file
681    IF ( nz_on_file /= nz )  THEN
682       WRITE( message_string, * ) 'mismatch concerning number of ',      &
683                                  'gridpoints along z',                  &
684                                  '&nz on file    = "', nz_on_file, '"', &
685                                  '&nz from run   = "', nz, '"'
686       CALL message( 'read_parts_of_var_list', 'PA0304', 1, 2, 0, 6, 0 )
687    ENDIF
688
689    READ ( 13 )  variable_chr
690    IF ( TRIM( variable_chr ) /= 'max_pr_user' )  THEN
691       message_string = 'max_pr_user not found in restart data file'
692       CALL message( 'read_parts_of_var_list', 'PA0305', 1, 2, 0, 6, 0 )
693    ENDIF
694    READ ( 13 )  max_pr_user_on_file
695    IF ( max_pr_user_on_file /= max_pr_user )  THEN
696       WRITE( message_string, * ) 'number of user profiles on res',           &
697                                  'tart data file differs from the current ', &
698                                  'run&max_pr_user on file    = "',           &
699                                  max_pr_user_on_file, '"',                   &
700                                  '&max_pr_user from run   = "',              &
701                                  max_pr_user, '"'
702       CALL message( 'read_parts_of_var_list', 'PA0306', 0, 0, 0, 6, 0 )
703       tmp_mpru = MIN( max_pr_user_on_file, max_pr_user )
704    ELSE
705       tmp_mpru = max_pr_user
706    ENDIF
707
708    READ ( 13 )  variable_chr
709    IF ( TRIM( variable_chr ) /= 'statistic_regions' )  THEN
710       message_string = 'statistic_regions not found in restart data file'
711       CALL message( 'read_parts_of_var_list', 'PA0307', 1, 2, 0, 6, 0 )
712    ENDIF
713    READ ( 13 )  statistic_regions_on_file
714    IF ( statistic_regions_on_file /= statistic_regions )  THEN
715       WRITE( message_string, * ) 'statistic regions on restart data file ',& 
716                                  'differ from the current run',            &
717                                  '&statistic regions on file    = "',      &
718                                  statistic_regions_on_file, '"',           &
719                                  '&statistic regions from run   = "',      &
720                                   statistic_regions, '"',                  &
721                                  '&statistic data may be lost!'
722       CALL message( 'read_parts_of_var_list', 'PA0308', 0, 1, 0, 6, 0 )
723       tmp_sr = MIN( statistic_regions_on_file, statistic_regions )
724    ELSE
725       tmp_sr = statistic_regions
726    ENDIF
727
728
729!
730!-- Now read and check some control parameters and skip the rest
731    WRITE (9,*) 'wpovl: begin reading variables'
732    CALL local_flush( 9 )
733    READ ( 13 )  variable_chr
734
735    DO  WHILE ( TRIM( variable_chr ) /= '*** end ***' )
736
737       SELECT CASE ( TRIM( variable_chr ) )
738
739          CASE ( 'average_count_pr' )
740             READ ( 13 )  average_count_pr
741             IF ( average_count_pr /= 0 )  THEN
742                WRITE( message_string, * ) 'inflow profiles not temporally ',  &
743                               'averaged. &Averaging will be done now using ', &
744                               average_count_pr, ' samples.'
745                CALL message( 'read_parts_of_var_list', 'PA0309', &
746                                                                 0, 1, 0, 6, 0 )
747             ENDIF
748
749          CASE ( 'hom' )
750             ALLOCATE( hom_on_file(0:nz+1,2,pr_palm+max_pr_user_on_file, &
751                       0:statistic_regions_on_file) )
752             READ ( 13 )  hom_on_file
753             hom(:,:,1:pr_palm+tmp_mpru,0:tmp_sr) = &
754                          hom_on_file(:,:,1:pr_palm+tmp_mpru,0:tmp_sr)
755             DEALLOCATE( hom_on_file )
756
757          CASE ( 'hom_sum' )
758             ALLOCATE( hom_sum_on_file(0:nz+1,pr_palm+max_pr_user_on_file, &
759                       0:statistic_regions_on_file) )
760             READ ( 13 )  hom_sum_on_file
761             hom_sum(:,1:pr_palm+tmp_mpru,0:tmp_sr) = &
762                          hom_sum_on_file(:,1:pr_palm+tmp_mpru,0:tmp_sr)
763             DEALLOCATE( hom_sum_on_file )
764
765          CASE ( 'nx' )
766             READ ( 13 )  nx_on_file
767
768          CASE ( 'ny' )
769             READ ( 13 )  ny_on_file
770
771
772          CASE DEFAULT
773
774             READ ( 13 )  idum
775
776       END SELECT
777
778       READ ( 13 )  variable_chr
779
780    ENDDO
781
782!
783!-- Calculate the temporal average of vertical profiles, if neccessary
784    IF ( average_count_pr /= 0 )  THEN
785       hom_sum = hom_sum / REAL( average_count_pr )
786    ENDIF
787
788
789 END SUBROUTINE read_parts_of_var_list
790
791
792
793 SUBROUTINE skip_var_list
794
795!------------------------------------------------------------------------------!
796! Description:
797! ------------
798! Skipping the global control variables from restart-file (binary format)
799!------------------------------------------------------------------------------!
800
801    IMPLICIT NONE
802
803    CHARACTER (LEN=10) ::  version_on_file
804    CHARACTER (LEN=30) ::  variable_chr
805
806    INTEGER ::  idum
807
808
809    WRITE (9,*) 'skipvl #1'
810    CALL local_flush( 9 )
811    READ ( 13 )  version_on_file
812
813    WRITE (9,*) 'skipvl before variable_chr'
814    CALL local_flush( 9 )
815    READ ( 13 )  variable_chr
816    WRITE (9,*) 'skipvl after variable_chr'
817    CALL local_flush( 9 )
818
819    DO  WHILE ( TRIM( variable_chr ) /= '*** end ***' )
820
821    WRITE (9,*) 'skipvl chr = ', variable_chr
822    CALL local_flush( 9 )
823       READ ( 13 )  idum
824       READ ( 13 )  variable_chr
825
826    ENDDO
827    WRITE (9,*) 'skipvl last'
828    CALL local_flush( 9 )
829
830
831 END SUBROUTINE skip_var_list
Note: See TracBrowser for help on using the repository browser.