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

Last change on this file since 1015 was 1015, checked in by raasch, 12 years ago

Starting with changes required for GPU optimization. OpenACC statements for using NVIDIA GPUs added.
Adjustment of mixing length to the Prandtl mixing length at first grid point above ground removed.
mask array is set zero for ghost boundaries

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