source: palm/trunk/SOURCE/read_restart_data_mod.f90 @ 3003

Last change on this file since 3003 was 3003, checked in by Giersch, 6 years ago

Bugfix: W* and Z_I in the first line of the run control file of restarts correspond now to the values in the last run control output line of the previous run

  • Property svn:keywords set to Id
File size: 87.5 KB
Line 
1!> @file read_restart_data_mod.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! 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-2018 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: read_restart_data_mod.f90 3003 2018-04-23 10:22:58Z Giersch $
27! z_i is also read to use the last known inversion height from the
28! initial run as the first inversion height which is written into the
29! run control file
30!
31! 2956 2018-04-10 11:01:03Z Giersch
32! spectrum_x and spectrum_y have been moved to global data
33!
34! 2921 2018-03-22 15:05:23Z Giersch
35! spinup_time, day_of_year_init and time_utc_init are also read now
36!
37! 2912 2018-03-20 13:00:05Z knoop
38! Added gust module interface calls
39!
40! 2894 2018-03-15 09:17:58Z Giersch
41! Initial revision
42!
43!
44! Description:
45! ------------
46!> Reads restart data from restart-file(s) (binary format).
47!------------------------------------------------------------------------------!
48 MODULE read_restart_data_mod
49
50
51    USE control_parameters
52     
53
54    IMPLICIT NONE
55
56
57    INTERFACE rrd_global
58       MODULE PROCEDURE rrd_global
59    END INTERFACE rrd_global
60
61    INTERFACE rrd_read_parts_of_global
62       MODULE PROCEDURE rrd_read_parts_of_global
63    END INTERFACE rrd_read_parts_of_global
64
65    INTERFACE rrd_local
66       MODULE PROCEDURE rrd_local
67    END INTERFACE rrd_local
68
69    INTERFACE rrd_skip_global
70       MODULE PROCEDURE rrd_skip_global
71    END INTERFACE rrd_skip_global
72
73
74    PUBLIC rrd_global, rrd_read_parts_of_global, rrd_local,      & 
75           rrd_skip_global
76
77
78 CONTAINS
79
80! Description:
81! ------------
82!> Reads values of global control variables from restart-file (binary format)
83!> created by PE0 of the previous run
84!------------------------------------------------------------------------------!
85    SUBROUTINE rrd_global
86
87
88       USE arrays_3d,                                                          &
89           ONLY:  inflow_damping_factor, mean_inflow_profiles, pt_init,        &
90                  q_init, ref_state, s_init, sa_init, u_init, ug, v_init, vg
91
92       USE date_and_time_mod,                                                  &
93           ONLY:  day_of_year_init, time_utc_init
94
95       USE flight_mod,                                                         &
96           ONLY: flight_rrd_global
97
98       USE grid_variables,                                                     &
99           ONLY:  dx, dy
100
101       USE gust_mod,                                                           &
102           ONLY :  gust_rrd_global
103
104       USE indices,                                                            &
105           ONLY:  nz, nx, nx_on_file, ny, ny_on_file
106
107       USE microphysics_mod,                                                   &
108           ONLY:  c_sedimentation, collision_turbulence,                       &
109                  cloud_water_sedimentation, limiter_sedimentation,            &
110                  nc_const, ventilation_effect
111
112       USE model_1d_mod,                                                       &
113           ONLY:  damp_level_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
114
115       USE netcdf_interface,                                                   &
116           ONLY:  netcdf_precision, output_for_t0
117
118       USE particle_attributes,                                                &
119           ONLY:  curvature_solution_effects
120
121       USE pegrid
122
123       USE radiation_model_mod,                                                &
124           ONLY:  time_radiation
125
126       USE spectra_mod,                                                        &
127           ONLY:  average_count_sp, spectrum_x, spectrum_y
128
129       USE statistics,                                                         &
130           ONLY:  statistic_regions, hom, hom_sum, pr_palm, u_max, u_max_ijk,  &
131                  v_max, v_max_ijk, w_max, w_max_ijk, z_i
132
133       USE synthetic_turbulence_generator_mod,                                 &
134           ONLY: stg_rrd_global
135
136       USE user_read_restart_data_mod,                                         &
137           ONLY:  user_rrd_global 
138
139       USE vertical_nesting_mod,                                               &
140           ONLY:  vnest_init
141
142       USE wind_turbine_model_mod,                                             &
143           ONLY: wtm_rrd_global
144
145
146       IMPLICIT NONE
147
148       CHARACTER (LEN=10) ::  binary_version_global, version_on_file
149
150       LOGICAL ::  found 
151
152
153       CALL check_open( 13 )
154
155!
156!-- Make version number check first
157       READ ( 13 )  length
158       READ ( 13 )  restart_string(1:length)
159       READ ( 13 )  version_on_file
160
161       binary_version_global = '4.7'
162       IF ( TRIM( version_on_file ) /= TRIM( binary_version_global ) )  THEN
163          WRITE( message_string, * ) 'version mismatch concerning control ',   &
164                                     'variables',                              &
165                                     '&version on file    = "',                &
166                                     TRIM( version_on_file ), '"',             &
167                                     '&version on program = "',                &
168                                     TRIM( binary_version_global ), '"'
169          CALL message( 'rrd_global', 'PA0296', 1, 2, 0, 6, 0 )
170       ENDIF
171
172!
173!-- Read number of PEs and horizontal index bounds of all PEs used in previous
174!-- run
175       READ ( 13 )  length
176       READ ( 13 )  restart_string(1:length)
177
178       IF ( TRIM( restart_string(1:length) ) /= 'numprocs' )  THEN
179          WRITE( message_string, * ) 'numprocs not found in data from prior ', &
180                                     'run on PE ', myid
181          CALL message( 'rrd_global', 'PA0297', 1, 2, 0, 6, 0 )
182       ENDIF
183       READ ( 13 )  numprocs_previous_run
184
185       IF ( .NOT. ALLOCATED( hor_index_bounds_previous_run ) )  THEN
186          ALLOCATE( hor_index_bounds_previous_run(4,0:numprocs_previous_run-1) )
187       ENDIF
188
189       READ ( 13 )  length
190       READ ( 13 )  restart_string(1:length)
191
192       IF ( restart_string(1:length) /= 'hor_index_bounds' )  THEN
193          WRITE( message_string, * ) 'hor_index_bounds not found in data ',    &
194                                     'from prior run on PE ', myid
195          CALL message( 'rrd_global', 'PA0298', 1, 2, 0, 6, 0 )
196       ENDIF
197       READ ( 13 )  hor_index_bounds_previous_run
198
199!
200!-- Read vertical number of gridpoints and number of different areas used
201!-- for computing statistics. Allocate arrays depending on these values,
202!-- which are needed for the following read instructions.
203       READ ( 13 )  length
204       READ ( 13 )  restart_string(1:length)
205
206       IF ( restart_string(1:length) /= 'nz' )  THEN
207          WRITE( message_string, * ) 'nz not found in data from prior run ',   &
208                                     'on PE ', myid
209          CALL message( 'rrd_global', 'PA0299', 1, 2, 0, 6, 0 )
210       ENDIF
211       READ ( 13 )  nz
212
213       READ ( 13 )  length
214       READ ( 13 )  restart_string(1:length)
215
216       IF ( restart_string(1:length) /= 'max_pr_user' )  THEN
217          WRITE( message_string, * ) 'max_pr_user not found in data from ',    &
218                                     'prior run on PE ', myid
219          CALL message( 'rrd_global', 'PA0300', 1, 2, 0, 6, 0 )
220       ENDIF
221       READ ( 13 )  max_pr_user    ! This value is checked against the number of
222                                   ! user profiles given for the current run
223                                   ! in routine user_parin (it has to match)
224
225       READ ( 13 )  length
226       READ ( 13 )  restart_string(1:length)
227
228       IF ( restart_string(1:length) /= 'statistic_regions' )  THEN
229          WRITE( message_string, * ) 'statistic_regions not found in data ',   &
230                                     'from prior run on PE ', myid
231          CALL message( 'rrd_global', 'PA0301', 1, 2, 0, 6, 0 )
232       ENDIF
233       READ ( 13 )  statistic_regions
234       IF ( .NOT. ALLOCATED( ug ) )  THEN
235          ALLOCATE( ug(0:nz+1), u_init(0:nz+1), vg(0:nz+1),                    &
236                    v_init(0:nz+1), pt_init(0:nz+1), q_init(0:nz+1),           &
237                    ref_state(0:nz+1), s_init(0:nz+1), sa_init(0:nz+1),        &
238                    hom(0:nz+1,2,pr_palm+max_pr_user,0:statistic_regions),     &
239                    hom_sum(0:nz+1,pr_palm+max_pr_user,0:statistic_regions) )
240       ENDIF
241
242!
243!-- Now read all control parameters:
244!-- Caution: When the following read instructions have been changed, the
245!-- -------  version number stored in the variable binary_version_global has to
246!--          be increased. The same changes must also be done in
247!--          wrd_write_global.
248       READ ( 13 )  length
249       READ ( 13 )  restart_string(1:length)
250
251       DO WHILE ( restart_string(1:length) /= 'binary_version_local' )
252
253          found = .FALSE.
254
255          SELECT CASE ( restart_string(1:length) )
256
257             CASE ( 'advected_distance_x' )
258                READ ( 13 )  advected_distance_x
259             CASE ( 'advected_distance_y' )
260                READ ( 13 )  advected_distance_y
261             CASE ( 'alpha_surface' )
262                READ ( 13 )  alpha_surface
263             CASE ( 'average_count_pr' )
264                READ ( 13 )  average_count_pr
265             CASE ( 'average_count_sp' )
266                READ ( 13 )  average_count_sp
267             CASE ( 'average_count_3d' )
268                READ ( 13 )  average_count_3d
269             CASE ( 'bc_e_b' )
270                READ ( 13 )  bc_e_b
271             CASE ( 'bc_lr' )
272                READ ( 13 )  bc_lr
273             CASE ( 'bc_ns' )
274                READ ( 13 )  bc_ns
275             CASE ( 'bc_p_b' )
276                READ ( 13 )  bc_p_b
277             CASE ( 'bc_p_t' )
278                READ ( 13 )  bc_p_t
279             CASE ( 'bc_pt_b' )
280                READ ( 13 )  bc_pt_b
281             CASE ( 'bc_pt_t' )
282                READ ( 13 )  bc_pt_t
283             CASE ( 'bc_pt_t_val' )
284                READ ( 13 )  bc_pt_t_val
285             CASE ( 'bc_q_b' )
286                READ ( 13 )  bc_q_b
287             CASE ( 'bc_q_t' )
288                READ ( 13 )  bc_q_t
289             CASE ( 'bc_q_t_val' )
290                READ ( 13 )  bc_q_t_val
291             CASE ( 'bc_s_b' )
292                READ ( 13 )  bc_s_b
293             CASE ( 'bc_s_t' )
294                READ ( 13 )  bc_s_t
295             CASE ( 'bc_sa_t' )
296                READ ( 13 )  bc_sa_t
297             CASE ( 'bc_uv_b' )
298                READ ( 13 )  bc_uv_b
299             CASE ( 'bc_uv_t' )
300                READ ( 13 )  bc_uv_t
301             CASE ( 'bottom_salinityflux' )
302                READ ( 13 )  bottom_salinityflux
303             CASE ( 'building_height' )
304                READ ( 13 )  building_height
305             CASE ( 'building_length_x' )
306                READ ( 13 )  building_length_x
307             CASE ( 'building_length_y' )
308                READ ( 13 )  building_length_y
309             CASE ( 'building_wall_left' )
310                READ ( 13 )  building_wall_left
311             CASE ( 'building_wall_south' )
312                READ ( 13 )  building_wall_south
313             CASE ( 'c_sedimentation' )
314                READ ( 13 )  c_sedimentation
315             CASE ( 'call_psolver_at_all_substeps' )
316                READ ( 13 )  call_psolver_at_all_substeps
317             CASE ( 'canyon_height' )
318                READ ( 13 )  canyon_height
319             CASE ( 'canyon_wall_left' )
320                READ ( 13 )  canyon_wall_left
321             CASE ( 'canyon_wall_south' )
322                READ ( 13 )  canyon_wall_south
323             CASE ( 'canyon_width_x' )
324                READ ( 13 )  canyon_width_x
325             CASE ( 'canyon_width_y' )
326                READ ( 13 )  canyon_width_y
327             CASE ( 'cfl_factor' )
328                READ ( 13 )  cfl_factor
329             CASE ( 'cloud_droplets' )
330                READ ( 13 )  cloud_droplets
331             CASE ( 'cloud_physics' )
332                READ ( 13 )  cloud_physics
333             CASE ( 'cloud_scheme' )
334                READ ( 13 )  cloud_scheme
335             CASE ( 'cloud_top_radiation' )
336                READ ( 13 )  cloud_top_radiation
337             CASE ( 'cloud_water_sedimentation' )
338                READ ( 13 )  cloud_water_sedimentation
339             CASE ( 'collective_wait' )
340                READ ( 13 )  collective_wait
341             CASE ( 'collision_turbulence' )
342                READ ( 13 )  collision_turbulence
343             CASE ( 'conserve_volume_flow' )
344                READ ( 13 )  conserve_volume_flow
345             CASE ( 'conserve_volume_flow_mode' )
346                READ ( 13 )  conserve_volume_flow_mode
347             CASE ( 'constant_flux_layer' )
348                READ ( 13 )  constant_flux_layer
349             CASE ( 'coupling_start_time' )
350                READ ( 13 )  coupling_start_time
351             CASE ( 'current_timestep_number' )
352                READ ( 13 )  current_timestep_number
353             CASE ( 'curvature_solution_effects' )
354                READ ( 13 )  curvature_solution_effects
355             CASE ( 'cycle_mg' )
356                READ ( 13 )  cycle_mg
357             CASE ( 'damp_level_1d' )
358                READ ( 13 )  damp_level_1d
359             CASE ( 'day_of_year_init' )
360                READ ( 13 )  day_of_year_init
361             CASE ( 'dissipation_1d' )
362                READ ( 13 )  dissipation_1d
363             CASE ( 'do2d_xy_time_count' )
364                READ ( 13 )  do2d_xy_time_count
365             CASE ( 'do2d_xz_time_count' )
366                READ ( 13 )  do2d_xz_time_count
367             CASE ( 'do2d_yz_time_count' )
368                READ ( 13 )  do2d_yz_time_count
369             CASE ( 'do3d_time_count' )
370                READ ( 13 )  do3d_time_count
371             CASE ( 'dp_external' )
372                READ ( 13 )  dp_external
373             CASE ( 'dp_level_b' )
374                READ ( 13 )  dp_level_b
375             CASE ( 'dp_smooth' )
376                READ ( 13 )  dp_smooth
377             CASE ( 'dpdxy' )
378                READ ( 13 )  dpdxy
379             CASE ( 'dt_3d' )
380                READ ( 13 )  dt_3d
381             CASE ( 'dt_pr_1d' )
382                READ ( 13 )  dt_pr_1d
383             CASE ( 'dt_run_control_1d' )
384                READ ( 13 )  dt_run_control_1d
385             CASE ( 'dvrp_filecount' )
386                READ ( 13 )  dvrp_filecount
387             CASE ( 'dx' )
388                READ ( 13 )  dx
389             CASE ( 'dy' )
390                READ ( 13 )  dy
391             CASE ( 'dz' )
392                READ ( 13 )  dz
393             CASE ( 'dz_max' )
394                READ ( 13 )  dz_max
395             CASE ( 'dz_stretch_factor' )
396                READ ( 13 )  dz_stretch_factor
397             CASE ( 'dz_stretch_level' )
398                READ ( 13 )  dz_stretch_level
399             CASE ( 'e_min' )
400                READ ( 13 )  e_min
401             CASE ( 'end_time_1d' )
402                READ ( 13 )  end_time_1d
403             CASE ( 'fft_method' )
404                READ ( 13 )  fft_method
405             CASE ( 'first_call_lpm' )
406                READ ( 13 )  first_call_lpm
407             CASE ( 'galilei_transformation' )
408                READ ( 13 )  galilei_transformation
409             CASE ( 'hom' )
410                READ ( 13 )  hom
411             CASE ( 'hom_sum' )
412                READ ( 13 )  hom_sum
413             CASE ( 'humidity' )
414                READ ( 13 )  humidity
415             CASE ( 'inflow_damping_factor' )
416                IF ( .NOT. ALLOCATED( inflow_damping_factor ) )  THEN
417                   ALLOCATE( inflow_damping_factor(0:nz+1) )
418                ENDIF
419                READ ( 13 )  inflow_damping_factor
420             CASE ( 'inflow_damping_height' )
421                READ ( 13 )  inflow_damping_height
422             CASE ( 'inflow_damping_width' )
423                READ ( 13 )  inflow_damping_width
424             CASE ( 'inflow_disturbance_begin' )
425                READ ( 13 )  inflow_disturbance_begin
426             CASE ( 'inflow_disturbance_end' )
427                READ ( 13 )  inflow_disturbance_end
428             CASE ( 'km_constant' )
429                READ ( 13 )  km_constant
430             CASE ( 'large_scale_forcing' )
431                READ ( 13 )  large_scale_forcing
432             CASE ( 'large_scale_subsidence' )
433                READ ( 13 )  large_scale_subsidence
434             CASE ( 'latitude' )
435                READ ( 13 )  latitude
436             CASE ( 'limiter_sedimentation' )
437                READ ( 13 )  limiter_sedimentation
438             CASE ( 'longitude' )
439                READ ( 13 )  longitude
440             CASE ( 'loop_optimization' )
441                READ ( 13 )  loop_optimization
442             CASE ( 'masking_method' )
443                READ ( 13 )  masking_method
444             CASE ( 'mean_inflow_profiles' )
445                IF ( .NOT. ALLOCATED( mean_inflow_profiles ) )  THEN
446                   ALLOCATE( mean_inflow_profiles(0:nz+1,7) )
447                ENDIF
448                READ ( 13 )  mean_inflow_profiles
449             CASE ( 'mg_cycles' )
450                READ ( 13 )  mg_cycles
451             CASE ( 'mg_switch_to_pe0_level' )
452                READ ( 13 )  mg_switch_to_pe0_level
453             CASE ( 'mixing_length_1d' )
454                READ ( 13 )  mixing_length_1d
455             CASE ( 'momentum_advec' )
456                READ ( 13 )  momentum_advec
457             CASE ( 'most_method' )
458                READ ( 13 )  most_method
459             CASE ( 'nc_const' )
460                READ ( 13 )  nc_const
461             CASE ( 'netcdf_precision' )
462                READ ( 13 )  netcdf_precision
463             CASE ( 'neutral' )
464                READ ( 13 )  neutral
465             CASE ( 'ngsrb' )
466                READ ( 13 )  ngsrb
467             CASE ( 'nsor' )
468                READ ( 13 )  nsor
469             CASE ( 'nsor_ini' )
470                READ ( 13 )  nsor_ini
471             CASE ( 'nudging' )
472                READ ( 13 )  nudging
473             CASE ( 'num_leg' )
474                READ ( 13 )  num_leg
475             CASE ( 'nx' )
476                READ ( 13 )  nx
477                nx_on_file = nx
478             CASE ( 'ny' )
479                READ ( 13 )  ny
480                ny_on_file = ny
481             CASE ( 'ocean' )
482                READ ( 13 )  ocean
483             CASE ( 'old_dt' )
484                READ ( 13 )  old_dt
485             CASE ( 'omega' )
486                READ ( 13 )  omega
487             CASE ( 'omega_sor' )
488                READ ( 13 )  omega_sor
489             CASE ( 'output_for_t0' )
490                READ (13)    output_for_t0
491             CASE ( 'passive_scalar' )
492                READ ( 13 )  passive_scalar
493             CASE ( 'prandtl_number' )
494                READ ( 13 )  prandtl_number
495             CASE ( 'precipitation' )
496                READ ( 13 ) precipitation
497             CASE ( 'psolver' )
498                READ ( 13 )  psolver
499             CASE ( 'pt_damping_factor' )
500                READ ( 13 )  pt_damping_factor
501             CASE ( 'pt_damping_width' )
502                READ ( 13 )  pt_damping_width
503             CASE ( 'pt_init' )
504                READ ( 13 )  pt_init
505             CASE ( 'pt_reference' )
506                READ ( 13 )  pt_reference
507             CASE ( 'pt_surface' )
508                READ ( 13 )  pt_surface
509             CASE ( 'pt_surface_initial_change' )
510                READ ( 13 )  pt_surface_initial_change
511             CASE ( 'pt_vertical_gradient' )
512                READ ( 13 )  pt_vertical_gradient
513             CASE ( 'pt_vertical_gradient_level' )
514                READ ( 13 )  pt_vertical_gradient_level
515             CASE ( 'pt_vertical_gradient_level_ind' )
516                READ ( 13 )  pt_vertical_gradient_level_ind
517             CASE ( 'q_init' )
518                READ ( 13 )  q_init
519             CASE ( 'q_surface' )
520                READ ( 13 )  q_surface
521             CASE ( 'q_surface_initial_change' )
522                READ ( 13 )  q_surface_initial_change
523             CASE ( 'q_vertical_gradient' )
524                READ ( 13 )  q_vertical_gradient
525             CASE ( 'q_vertical_gradient_level' )
526                READ ( 13 )  q_vertical_gradient_level
527             CASE ( 'q_vertical_gradient_level_ind' )
528                READ ( 13 )  q_vertical_gradient_level_ind
529             CASE ( 'random_generator' )
530                READ ( 13 )  random_generator
531             CASE ( 'random_heatflux' )
532                READ ( 13 )  random_heatflux
533             CASE ( 'rans_mode' )
534                READ ( 13 )  rans_mode
535             CASE ( 'rayleigh_damping_factor' )
536                READ ( 13 )  rayleigh_damping_factor
537             CASE ( 'rayleigh_damping_height' )
538                READ ( 13 )  rayleigh_damping_height
539             CASE ( 'recycling_width' )
540                READ ( 13 )  recycling_width
541             CASE ( 'recycling_yshift' )
542                READ ( 13 ) recycling_yshift
543             CASE ( 'ref_state' )
544                READ ( 13 )  ref_state
545             CASE ( 'reference_state' )
546                READ ( 13 )  reference_state
547             CASE ( 'residual_limit' )
548                READ ( 13 )  residual_limit
549             CASE ( 'roughness_length' )
550                READ ( 13 )  roughness_length
551             CASE ( 'run_coupled' )
552                READ ( 13 )  run_coupled
553             CASE ( 'runnr' )
554                READ ( 13 )  runnr
555             CASE ( 's_init' )
556                READ ( 13 )  s_init
557             CASE ( 's_surface' )
558                READ ( 13 )  s_surface
559             CASE ( 's_surface_initial_change' )
560                READ ( 13 )  s_surface_initial_change
561             CASE ( 's_vertical_gradient' )
562                READ ( 13 )  s_vertical_gradient
563             CASE ( 's_vertical_gradient_level' )
564                READ ( 13 )  s_vertical_gradient_level
565             CASE ( 's_vertical_gradient_level_ind' )
566                READ ( 13 )  s_vertical_gradient_level_ind
567             CASE ( 'sa_init' )
568                READ ( 13 )  sa_init
569             CASE ( 'sa_surface' )
570                READ ( 13 )  sa_surface
571             CASE ( 'sa_vertical_gradient' )
572                READ ( 13 )  sa_vertical_gradient
573             CASE ( 'sa_vertical_gradient_level' )
574                READ ( 13 )  sa_vertical_gradient_level
575             CASE ( 'scalar_advec' )
576                READ ( 13 )  scalar_advec
577             CASE ( 'simulated_time' )
578                READ ( 13 )  simulated_time
579             CASE ( 'spectrum_x' )
580                IF ( .NOT. ALLOCATED( spectrum_x ) )  THEN
581                   ALLOCATE( spectrum_x( 1:nx/2, 1:100, 1:10 ) )
582                ENDIF
583                READ ( 13 )  spectrum_x
584             CASE ( 'spectrum_y' )
585                IF ( .NOT. ALLOCATED( spectrum_y ) )  THEN
586                   ALLOCATE( spectrum_y( 1:ny/2, 1:100, 1:10 ) )
587                ENDIF
588                READ ( 13 )  spectrum_y
589             CASE ( 'spinup_time' )
590                READ ( 13 )  spinup_time
591             CASE ( 'surface_heatflux' )
592                READ ( 13 )  surface_heatflux
593             CASE ( 'surface_pressure' )
594                READ ( 13 )  surface_pressure
595             CASE ( 'surface_scalarflux' )
596                READ ( 13 )  surface_scalarflux
597             CASE ( 'surface_waterflux' )
598                READ ( 13 )  surface_waterflux
599             CASE ( 'time_coupling' )
600                READ ( 13 )  time_coupling
601             CASE ( 'time_disturb' )
602                READ ( 13 )  time_disturb
603             CASE ( 'time_do2d_xy' )
604                READ ( 13 )  time_do2d_xy
605             CASE ( 'time_do2d_xz' )
606                READ ( 13 )  time_do2d_xz
607             CASE ( 'time_do2d_yz' )
608                READ ( 13 )  time_do2d_yz
609             CASE ( 'time_do3d' )
610                READ ( 13 )  time_do3d
611             CASE ( 'time_do_av' )
612                READ ( 13 )  time_do_av
613             CASE ( 'time_do_sla' )
614                READ ( 13 )  time_do_sla
615             CASE ( 'time_domask' )
616                READ ( 13 )  time_domask
617             CASE ( 'time_dopr' )
618                READ ( 13 )  time_dopr
619             CASE ( 'time_dopr_av' )
620                READ ( 13 )  time_dopr_av
621             CASE ( 'time_dopr_listing' )
622                READ ( 13 )  time_dopr_listing
623             CASE ( 'time_dopts' )
624                READ ( 13 )  time_dopts
625             CASE ( 'time_dosp' )
626                READ ( 13 )  time_dosp
627             CASE ( 'time_dots' )
628                READ ( 13 )  time_dots
629             CASE ( 'time_dvrp' )
630                READ ( 13 )  time_dvrp
631             CASE ( 'time_radiation' )
632                READ ( 13 )  time_radiation
633             CASE ( 'time_restart' )
634                READ ( 13 )  time_restart
635             CASE ( 'time_run_control' )
636                READ ( 13 )  time_run_control
637             CASE ( 'time_since_reference_point' )
638                READ ( 13 )  time_since_reference_point
639             CASE ( 'time_utc_init' )
640                READ ( 13 )  time_utc_init
641             CASE ( 'timestep_scheme' )
642                READ ( 13 )  timestep_scheme
643             CASE ( 'top_heatflux' )
644                READ ( 13 )  top_heatflux
645             CASE ( 'top_momentumflux_u' )
646                READ ( 13 )  top_momentumflux_u
647             CASE ( 'top_momentumflux_v' )
648                READ ( 13 )  top_momentumflux_v
649             CASE ( 'top_salinityflux' )
650                READ ( 13 )  top_salinityflux
651             CASE ( 'top_scalarflux' )
652                READ ( 13 )  top_scalarflux
653             CASE ( 'topography' )
654                READ ( 13 )  topography
655             CASE ( 'topography_grid_convention' )
656                READ ( 13 )  topography_grid_convention
657             CASE ( 'tsc' )
658                READ ( 13 )  tsc
659             CASE ( 'tunnel_height' )
660                READ ( 13 )  tunnel_height
661             CASE ( 'tunnel_length' )
662                READ ( 13 )  tunnel_length
663             CASE ( 'tunnel_wall_depth' )
664                READ ( 13 )  tunnel_wall_depth
665             CASE ( 'tunnel_width_x' )
666                READ ( 13 )  tunnel_width_x
667             CASE ( 'tunnel_width_y' )
668                READ ( 13 )  tunnel_width_y
669             CASE ( 'turbulence_closure' )
670                READ ( 13 )  turbulence_closure
671             CASE ( 'turbulent_inflow' )
672                READ ( 13 )  turbulent_inflow
673             CASE ( 'u_bulk' )
674                READ ( 13 )  u_bulk
675             CASE ( 'u_init' )
676                READ ( 13 )  u_init
677             CASE ( 'u_max' )
678                READ ( 13 )  u_max
679             CASE ( 'u_max_ijk' )
680                READ ( 13 )  u_max_ijk
681             CASE ( 'ug' )
682                READ ( 13 )  ug
683             CASE ( 'ug_surface' )
684                READ ( 13 )  ug_surface
685             CASE ( 'ug_vertical_gradient' )
686                READ ( 13 )  ug_vertical_gradient
687             CASE ( 'ug_vertical_gradient_level' )
688                READ ( 13 )  ug_vertical_gradient_level
689             CASE ( 'ug_vertical_gradient_level_ind' )
690                READ ( 13 )  ug_vertical_gradient_level_ind
691             CASE ( 'use_surface_fluxes' )
692                READ ( 13 )  use_surface_fluxes
693             CASE ( 'use_top_fluxes' )
694                READ ( 13 )  use_top_fluxes
695             CASE ( 'use_ug_for_galilei_tr' )
696                READ ( 13 )  use_ug_for_galilei_tr
697             CASE ( 'use_upstream_for_tke' )
698                READ ( 13 )  use_upstream_for_tke
699             CASE ( 'v_bulk' )
700                READ ( 13 )  v_bulk
701             CASE ( 'v_init' )
702                READ ( 13 )  v_init
703             CASE ( 'v_max' )
704                READ ( 13 )  v_max
705             CASE ( 'v_max_ijk' )
706                READ ( 13 )  v_max_ijk
707             CASE ( 'ventilation_effect' )
708                READ ( 13 )  ventilation_effect
709             CASE ( 'vg' )
710                READ ( 13 )  vg
711             CASE ( 'vg_surface' )
712                READ ( 13 )  vg_surface
713             CASE ( 'vg_vertical_gradient' )
714                READ ( 13 )  vg_vertical_gradient
715             CASE ( 'vg_vertical_gradient_level' )
716                READ ( 13 )  vg_vertical_gradient_level
717             CASE ( 'vg_vertical_gradient_level_ind' )
718                READ ( 13 )  vg_vertical_gradient_level_ind
719             CASE ( 'virtual_flight' )
720                READ ( 13 )  virtual_flight
721             CASE ( 'vnest_init' )
722                READ ( 13 )  vnest_init
723             CASE ( 'volume_flow_area' )
724                READ ( 13 )  volume_flow_area
725             CASE ( 'volume_flow_initial' )
726                READ ( 13 )  volume_flow_initial
727             CASE ( 'subs_vertical_gradient' )
728                READ ( 13 )  subs_vertical_gradient
729             CASE ( 'subs_vertical_gradient_level' )
730                READ ( 13 )  subs_vertical_gradient_level
731             CASE ( 'subs_vertical_gradient_level_i' )
732                READ ( 13 )  subs_vertical_gradient_level_i
733             CASE ( 'w_max' )
734                READ ( 13 )  w_max
735             CASE ( 'w_max_ijk' )
736                READ ( 13 )  w_max_ijk
737             CASE ( 'wall_adjustment' )
738                READ ( 13 )  wall_adjustment
739             CASE ( 'wall_heatflux' )
740                READ ( 13 )  wall_heatflux
741             CASE ( 'wall_humidityflux' )
742                READ ( 13 )  wall_humidityflux
743             CASE ( 'wall_salinityflux' )
744                READ ( 13 )  wall_salinityflux
745             CASE ( 'wall_scalarflux' )
746                READ ( 13 )  wall_scalarflux
747             CASE ( 'y_shift' )
748                READ ( 13 )  y_shift
749             CASE ( 'z0h_factor' )
750                READ ( 13 )  z0h_factor
751             CASE ( 'zeta_max' )
752                READ ( 13 )  zeta_max
753             CASE ( 'zeta_min' )
754                READ ( 13 )  zeta_min
755             CASE ( 'z_i' )
756                READ ( 13 )  z_i
757
758
759             CASE DEFAULT
760
761                IF ( .NOT. found ) CALL wtm_rrd_global( found )
762
763                IF ( .NOT. found ) CALL flight_rrd_global( found )
764
765                IF ( .NOT. found ) CALL stg_rrd_global ( found )
766
767                IF ( .NOT. found ) CALL gust_rrd_global( found )
768
769                IF ( .NOT. found ) CALL user_rrd_global( found )
770
771                IF ( .NOT. found )  THEN
772                   WRITE( message_string, * ) 'unknown variable named "',      &
773                                           restart_string(1:length),           &
774                                          '" found in global data from ',      & 
775                                          'prior run on PE ', myid
776                CALL message( 'rrd_global', 'PA0302', 1, 2, 0, 6, 0 )
777 
778                ENDIF
779
780          END SELECT
781!
782!--       Read next string
783          READ ( 13 )  length
784          READ ( 13 )  restart_string(1:length)   
785
786       ENDDO
787 
788
789    CALL close_file( 13 )
790
791   
792    END SUBROUTINE rrd_global
793
794
795
796!------------------------------------------------------------------------------!
797! Description:
798! ------------
799!> Skipping the global control variables from restart-file (binary format)
800!> except some information needed when reading restart data from a previous
801!> run which used a smaller total domain or/and a different domain decomposition
802!> (initializing_actions  == 'cyclic_fill').
803!------------------------------------------------------------------------------!
804
805    SUBROUTINE rrd_read_parts_of_global
806
807
808       USE arrays_3d,                                                             &
809           ONLY:  inflow_damping_factor, mean_inflow_profiles, ref_state, ug, vg
810
811       USE indices,                                                               &
812           ONLY:  nz, nx, nx_on_file, ny, ny_on_file
813
814       USE kinds
815
816       USE pegrid
817
818       USE statistics,                                                            &
819           ONLY:  statistic_regions, hom, hom_sum, pr_palm, u_max, u_max_ijk,     &
820                  v_max, v_max_ijk, w_max, w_max_ijk
821
822       IMPLICIT NONE
823
824       CHARACTER (LEN=10) ::  version_on_file
825       CHARACTER (LEN=20) ::  momentum_advec_check
826       CHARACTER (LEN=20) ::  scalar_advec_check
827       CHARACTER (LEN=1)  ::  cdum
828
829       INTEGER(iwp) ::  max_pr_user_on_file
830       INTEGER(iwp) ::  nz_on_file
831       INTEGER(iwp) ::  statistic_regions_on_file
832       INTEGER(iwp) ::  tmp_mpru
833       INTEGER(iwp) ::  tmp_sr
834
835       REAL(wp), DIMENSION(:,:,:),   ALLOCATABLE ::  hom_sum_on_file
836       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  hom_on_file
837
838
839       CALL check_open( 13 )
840
841       READ ( 13 )  length
842       READ ( 13 )  restart_string(1:length)
843       READ ( 13 )  version_on_file
844
845!
846!-- Read number of PEs and horizontal index bounds of all PEs used in previous
847!-- run
848       READ ( 13 )  length
849       READ ( 13 )  restart_string(1:length)
850
851       IF ( restart_string(1:length) /= 'numprocs' )  THEN
852          WRITE( message_string, * ) 'numprocs not found in data from prior ', &
853                                     'run on PE ', myid
854          CALL message( 'rrd_read_parts_of_global', 'PA0297', 1, 2, 0, 6, 0 )
855       ENDIF
856       READ ( 13 )  numprocs_previous_run
857
858       IF ( .NOT. ALLOCATED( hor_index_bounds_previous_run ) )  THEN
859          ALLOCATE( hor_index_bounds_previous_run(4,0:numprocs_previous_run-1) )
860       ENDIF
861
862       READ ( 13 )  length
863       READ ( 13 )  restart_string(1:length)
864
865       IF ( restart_string(1:length) /= 'hor_index_bounds' )  THEN
866          WRITE( message_string, * ) 'hor_index_bounds not found in data ',    &
867                                     'from prior run on PE ', myid
868          CALL message( 'rrd_read_parts_of_global', 'PA0298', 1, 2, 0, 6, 0 )
869       ENDIF
870       READ ( 13 )  hor_index_bounds_previous_run
871
872!
873!-- Read vertical number of gridpoints and number of different areas used
874!-- for computing statistics. Allocate arrays depending on these values,
875!-- which are needed for the following read instructions.
876       READ ( 13 )  length
877       READ ( 13 )  restart_string(1:length)
878
879       IF ( restart_string(1:length) /= 'nz' )  THEN
880          message_string = 'nz not found in restart data file'
881          CALL message( 'rrd_read_parts_of_global', 'PA0303', 1, 2, 0, 6, 0 )
882       ENDIF
883       READ ( 13 )  nz_on_file
884       IF ( nz_on_file /= nz )  THEN
885          WRITE( message_string, * ) 'mismatch concerning number of ',         &
886                                     'gridpoints along z',                     &
887                                     '&nz on file    = "', nz_on_file, '"',    &
888                                     '&nz from run   = "', nz, '"'
889          CALL message( 'rrd_read_parts_of_global', 'PA0304', 1, 2, 0, 6, 0 )
890       ENDIF
891
892       READ ( 13 )  length
893       READ ( 13 )  restart_string(1:length)
894
895       IF ( restart_string(1:length) /= 'max_pr_user' )  THEN
896          message_string = 'max_pr_user not found in restart data file'
897          CALL message( 'rrd_read_parts_of_global', 'PA0305', 1, 2, 0, 6, 0 )
898       ENDIF
899       READ ( 13 )  max_pr_user_on_file
900       IF ( max_pr_user_on_file /= max_pr_user )  THEN
901          WRITE( message_string, * ) 'number of user profiles on res',         &
902                                     'tart data file differs from the ',       &
903                                     'current run&max_pr_user on file    = "', &
904                                     max_pr_user_on_file, '"',                 &
905                                     '&max_pr_user from run   = "',            &
906                                     max_pr_user, '"'
907          CALL message( 'rrd_read_parts_of_global', 'PA0306', 0, 0, 0, 6, 0 )
908          tmp_mpru = MIN( max_pr_user_on_file, max_pr_user )
909       ELSE
910          tmp_mpru = max_pr_user
911       ENDIF
912
913       READ ( 13 )  length
914       READ ( 13 )  restart_string(1:length)
915
916       IF ( restart_string(1:length) /= 'statistic_regions' )  THEN
917          message_string = 'statistic_regions not found in restart data file'
918          CALL message( 'rrd_read_parts_of_global', 'PA0307', 1, 2, 0, 6, 0 )
919       ENDIF
920       READ ( 13 )  statistic_regions_on_file
921       IF ( statistic_regions_on_file /= statistic_regions )  THEN
922          WRITE( message_string, * ) 'statistic regions on restart data file ',&
923                                     'differ from the current run',            &
924                                     '&statistic regions on file    = "',      &
925                                     statistic_regions_on_file, '"',           &
926                                     '&statistic regions from run   = "',      &
927                                      statistic_regions, '"',                  &
928                                     '&statistic data may be lost!'
929          CALL message( 'rrd_read_parts_of_global', 'PA0308', 0, 1, 0, 6, 0 )
930          tmp_sr = MIN( statistic_regions_on_file, statistic_regions )
931       ELSE
932          tmp_sr = statistic_regions
933       ENDIF
934
935!
936!-- Now read and check some control parameters and skip the rest
937       READ ( 13 )  length
938       READ ( 13 )  restart_string(1:length)
939
940       DO  WHILE ( restart_string(1:length) /= 'binary_version_local' )
941
942          SELECT CASE ( restart_string(1:length) )
943
944             CASE ( 'average_count_pr' )
945                READ ( 13 )  average_count_pr
946                IF ( average_count_pr /= 0 )  THEN
947                   WRITE( message_string, * ) 'inflow profiles not ',          &
948                                  'temporally averaged. &Averaging will be ',  &
949                                  'done now using', average_count_pr,          & 
950                                  ' samples.'
951                   CALL message( 'rrd_read_parts_of_global', 'PA0309',         &
952                                 0, 1, 0, 6, 0 )
953                ENDIF
954
955             CASE ( 'hom' )
956                ALLOCATE( hom_on_file(0:nz+1,2,pr_palm+max_pr_user_on_file,    &
957                          0:statistic_regions_on_file) )
958                READ ( 13 )  hom_on_file
959                hom(:,:,1:pr_palm+tmp_mpru,0:tmp_sr) =                         &
960                             hom_on_file(:,:,1:pr_palm+tmp_mpru,0:tmp_sr)
961                DEALLOCATE( hom_on_file )
962
963             CASE ( 'hom_sum' )
964                ALLOCATE( hom_sum_on_file(0:nz+1,pr_palm+max_pr_user_on_file,  &
965                          0:statistic_regions_on_file) )
966                READ ( 13 )  hom_sum_on_file
967                hom_sum(:,1:pr_palm+tmp_mpru,0:tmp_sr) =                       &
968                             hom_sum_on_file(:,1:pr_palm+tmp_mpru,0:tmp_sr)
969                DEALLOCATE( hom_sum_on_file )
970
971             CASE ( 'momentum_advec' )
972                momentum_advec_check = momentum_advec
973                READ ( 13 )  momentum_advec
974                IF ( TRIM( momentum_advec_check ) /= TRIM( momentum_advec ) )  &
975                THEN
976                   WRITE( message_string, * ) 'momentum_advec of the restart ',&
977                                  'run differs from momentum_advec of the ',   &
978                                  'initial run.'
979                   CALL message( 'rrd_read_parts_of_global', 'PA0100',         &
980                                 1, 2, 0, 6, 0 )
981                ENDIF
982
983             CASE ( 'nx' )
984                READ ( 13 )  nx_on_file
985
986             CASE ( 'ny' )
987                READ ( 13 )  ny_on_file
988
989             CASE ( 'ref_state' )
990                READ ( 13 )  ref_state
991
992             CASE ( 'scalar_advec' )
993                scalar_advec_check = scalar_advec
994                READ ( 13 )  scalar_advec
995                IF ( TRIM( scalar_advec_check ) /= TRIM( scalar_advec ) )      &
996                THEN
997                   WRITE( message_string, * ) 'scalar_advec of the restart ',  &
998                                  'run differs from scalar_advec of the ',     &
999                                  'initial run.'
1000                   CALL message( 'rrd_read_parts_of_global', 'PA0101',         &
1001                                 1, 2, 0, 6, 0 )
1002                ENDIF
1003
1004             CASE DEFAULT
1005
1006                READ ( 13 )  cdum
1007
1008          END SELECT
1009
1010          READ ( 13 )  length
1011          READ ( 13 )  restart_string(1:length)
1012
1013       ENDDO
1014
1015!
1016!-- Calculate the temporal average of vertical profiles, if neccessary
1017    IF ( average_count_pr /= 0 )  THEN
1018       hom_sum = hom_sum / REAL( average_count_pr, KIND=wp )
1019    ENDIF
1020
1021
1022    CALL close_file( 13 )
1023
1024
1025    END SUBROUTINE rrd_read_parts_of_global
1026
1027
1028! Description:
1029! ------------
1030!> Reads processor specific data of variables and arrays from restart file
1031!> (binary format).
1032!------------------------------------------------------------------------------!
1033 SUBROUTINE rrd_local 
1034 
1035
1036    USE arrays_3d,                                                             &
1037        ONLY:  e, kh, km, p, pt, q, ql, qc, nc, nr, prr, precipitation_amount, &
1038               qr, s, sa, u, u_m_l, u_m_n, u_m_r, u_m_s, v, v_m_l, v_m_n,      &
1039               v_m_r, v_m_s, vpt, w, w_m_l, w_m_n, w_m_r, w_m_s
1040
1041    USE averaging
1042
1043    USE chemistry_model_mod,                                                   &
1044        ONLY:  chem_rrd_local, chem_species, nspec                               
1045
1046    USE cpulog,                                                                &
1047        ONLY:  cpu_log, log_point_s
1048
1049    USE gust_mod,                                                           &
1050        ONLY :  gust_rrd_local
1051
1052    USE indices,                                                               &
1053        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, nx_on_file, ny, nys, nysg, nyn, &
1054               nyng, ny_on_file, nzb, nzt
1055
1056    USE kinds
1057
1058    USE land_surface_model_mod,                                                &
1059        ONLY:  lsm_rrd_local
1060
1061    USE particle_attributes,                                                   &
1062        ONLY:  iran_part
1063
1064    USE pegrid
1065
1066    USE radiation_model_mod,                                                   &
1067        ONLY: radiation, radiation_rrd_local
1068
1069    USE random_function_mod,                                                   &
1070        ONLY:  random_iv, random_iy
1071
1072    USE random_generator_parallel,                                             &
1073        ONLY:  id_random_array, seq_random_array
1074
1075    USE surface_mod,                                                           &
1076        ONLY :  surface_rrd_local
1077       
1078    USE urban_surface_mod,                                                     &
1079        ONLY:  usm_rrd_local
1080
1081    USE user_read_restart_data_mod,                                            &
1082        ONLY:  user_rrd_local 
1083 
1084
1085    IMPLICIT NONE
1086
1087    CHARACTER (LEN=7)  ::  myid_char_save
1088    CHARACTER (LEN=10) ::  binary_version_local
1089    CHARACTER (LEN=10) ::  version_on_file
1090
1091    INTEGER(iwp) ::  files_to_be_opened  !<
1092    INTEGER(iwp) ::  i                   !<
1093    INTEGER(iwp) ::  j                   !<
1094    INTEGER(iwp) ::  k                   !<
1095    INTEGER(iwp) ::  myid_on_file        !<
1096    INTEGER(iwp) ::  numprocs_on_file    !<
1097    INTEGER(iwp) ::  nxlc                !<
1098    INTEGER(iwp) ::  nxlf                !<
1099    INTEGER(iwp) ::  nxlpr               !<
1100    INTEGER(iwp) ::  nxl_on_file         !<
1101    INTEGER(iwp) ::  nxrc                !<
1102    INTEGER(iwp) ::  nxrf                !<
1103    INTEGER(iwp) ::  nxrpr               !<
1104    INTEGER(iwp) ::  nxr_on_file         !<
1105    INTEGER(iwp) ::  nync                !<
1106    INTEGER(iwp) ::  nynf                !<
1107    INTEGER(iwp) ::  nynpr               !<
1108    INTEGER(iwp) ::  nyn_on_file         !<
1109    INTEGER(iwp) ::  nysc                !<
1110    INTEGER(iwp) ::  nysf                !<
1111    INTEGER(iwp) ::  nyspr               !<
1112    INTEGER(iwp) ::  nys_on_file         !<
1113    INTEGER(iwp) ::  nzb_on_file         !<
1114    INTEGER(iwp) ::  nzt_on_file         !<
1115    INTEGER(iwp) ::  offset_x            !<
1116    INTEGER(iwp) ::  offset_y            !<
1117    INTEGER(iwp) ::  shift_x             !<
1118    INTEGER(iwp) ::  shift_y             !<
1119
1120    INTEGER(iwp), DIMENSION(numprocs_previous_run) ::  file_list       !<
1121    INTEGER(iwp), DIMENSION(numprocs_previous_run) ::  overlap_count   !<
1122
1123    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nxlfa      !<
1124    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nxrfa      !<
1125    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nynfa      !<
1126    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nysfa      !<
1127    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  offset_xa  !<
1128    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  offset_ya  !<
1129
1130    INTEGER(isp), DIMENSION(:,:),   ALLOCATABLE ::  tmp_2d_id_random   !< temporary array for storing random generator data
1131    INTEGER(isp), DIMENSION(:,:,:), ALLOCATABLE ::  tmp_2d_seq_random  !< temporary array for storing random generator data
1132
1133    LOGICAL ::  found
1134
1135    REAL(wp) ::  rdummy
1136
1137    REAL(wp), DIMENSION(:,:),   ALLOCATABLE   ::  tmp_2d      !< temporary array for storing 2D data
1138    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3d      !< temporary array for storing 3D data
1139    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwul   !<
1140    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwun   !<
1141    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwur   !<
1142    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwus   !<
1143    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwvl   !<
1144    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwvn   !<
1145    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwvr   !<
1146    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwvs   !<
1147    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwwl   !<
1148    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwwn   !<
1149    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwwr   !<
1150    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwws   !<
1151
1152
1153!
1154!-- Read data from previous model run.
1155    CALL cpu_log( log_point_s(14), 'rrd_local', 'start' )
1156
1157!
1158!-- Check which of the restart files contain data needed for the subdomain
1159!-- of this PE
1160    files_to_be_opened = 0
1161
1162    DO  i = 1, numprocs_previous_run
1163!
1164!--    Store array bounds of the previous run ("pr") in temporary scalars
1165       nxlpr = hor_index_bounds_previous_run(1,i-1)
1166       nxrpr = hor_index_bounds_previous_run(2,i-1)
1167       nyspr = hor_index_bounds_previous_run(3,i-1)
1168       nynpr = hor_index_bounds_previous_run(4,i-1)
1169
1170!
1171!--    Determine the offsets. They may be non-zero in case that the total domain
1172!--    on file is smaller than the current total domain.
1173       offset_x = ( nxl / ( nx_on_file + 1 ) ) * ( nx_on_file + 1 )
1174       offset_y = ( nys / ( ny_on_file + 1 ) ) * ( ny_on_file + 1 )
1175
1176!
1177!--    Start with this offset and then check, if the subdomain on file
1178!--    matches another time(s) in the current subdomain by shifting it
1179!--    for nx_on_file+1, ny_on_file+1 respectively
1180   
1181       shift_y = 0
1182       j       = 0
1183       DO WHILE (  nyspr+shift_y <= nyn-offset_y )
1184         
1185          IF ( nynpr+shift_y >= nys-offset_y ) THEN
1186
1187             shift_x = 0
1188             DO WHILE ( nxlpr+shift_x <= nxr-offset_x )
1189               
1190                IF ( nxrpr+shift_x >= nxl-offset_x ) THEN
1191                   j = j +1
1192                   IF ( j > 1000 )  THEN
1193!
1194!--                   Array bound exceeded
1195                      message_string = 'data from subdomain of previous' //    &
1196                                       ' run mapped more than 1000 times'
1197                      CALL message( 'rrd_local', 'PA0284', 2, 2, -1,           &
1198                                       6, 1 )
1199                   ENDIF
1200
1201                   IF ( j == 1 )  THEN
1202                      files_to_be_opened = files_to_be_opened + 1
1203                      file_list(files_to_be_opened) = i-1
1204                   ENDIF
1205                     
1206                   offset_xa(files_to_be_opened,j) = offset_x + shift_x
1207                   offset_ya(files_to_be_opened,j) = offset_y + shift_y
1208!
1209!--                Index bounds of overlapping data
1210                   nxlfa(files_to_be_opened,j) = MAX( nxl-offset_x-shift_x,    &
1211                                                      nxlpr )
1212                   nxrfa(files_to_be_opened,j) = MIN( nxr-offset_x-shift_x,    &
1213                                                      nxrpr )
1214                   nysfa(files_to_be_opened,j) = MAX( nys-offset_y-shift_y,    & 
1215                                                      nyspr )
1216                   nynfa(files_to_be_opened,j) = MIN( nyn-offset_y-shift_y,    & 
1217                                                      nynpr )
1218
1219                ENDIF
1220
1221                shift_x = shift_x + ( nx_on_file + 1 )
1222             ENDDO
1223       
1224          ENDIF
1225             
1226          shift_y = shift_y + ( ny_on_file + 1 )             
1227       ENDDO
1228         
1229       IF ( j > 0 )  overlap_count(files_to_be_opened) = j
1230         
1231    ENDDO
1232   
1233!
1234!-- Save the id-string of the current process, since myid_char may now be used
1235!-- to open files created by PEs with other id.
1236    myid_char_save = myid_char
1237
1238    IF ( files_to_be_opened /= 1  .OR.  numprocs /= numprocs_previous_run )    &
1239    THEN
1240       WRITE( message_string, * ) 'number of PEs or virtual PE-grid changed ', &
1241                        'in restart run&  PE', myid, ' will read from files ', &
1242                         file_list(1:files_to_be_opened)
1243       CALL message( 'rrd_local', 'PA0285', 0, 0, 0, 6, 0 )
1244    ENDIF
1245
1246!
1247!-- Read data from all restart files determined above
1248    DO  i = 1, files_to_be_opened
1249 
1250       j = file_list(i)
1251!
1252!--    Set the filename (underscore followed by four digit processor id)
1253       WRITE (myid_char,'(''_'',I6.6)')  j
1254
1255!
1256!--    Open the restart file. If this file has been created by PE0 (_000000),
1257!--    the global variables at the beginning of the file have to be skipped
1258!--    first.
1259       CALL check_open( 13 )
1260       IF ( j == 0 )  CALL rrd_skip_global
1261
1262!
1263!--    First compare the version numbers
1264       READ ( 13 )  length
1265       READ ( 13 )  restart_string(1:length)
1266       READ ( 13 )  version_on_file
1267
1268       binary_version_local = '4.7'
1269       IF ( TRIM( version_on_file ) /= TRIM( binary_version_local ) )  THEN
1270          WRITE( message_string, * ) 'version mismatch concerning data ',      &
1271                      'from prior run',                                        &
1272                      '&version on file    = "', TRIM( version_on_file ), '"', &
1273                      '&version in program = "', TRIM( binary_version_local ), '"'
1274          CALL message( 'rrd_local', 'PA0286', 1, 2, 0, 6, 0 )
1275       ENDIF
1276
1277!
1278!--    Read number of processors, processor-id, and array ranges.
1279!--    Compare the array ranges with those stored in the index bound array.
1280       READ ( 13 )  numprocs_on_file, myid_on_file, nxl_on_file, nxr_on_file,  &
1281                    nys_on_file, nyn_on_file, nzb_on_file, nzt_on_file
1282
1283       IF ( nxl_on_file /= hor_index_bounds_previous_run(1,j) )  THEN
1284          WRITE( message_string, * ) 'problem with index bound nxl on ',       &
1285                            'restart file "', myid_char, '"',                  &
1286                            '&nxl = ', nxl_on_file, ' but it should be',       &
1287                            '&= ', hor_index_bounds_previous_run(1,j),         &
1288                            '&from the index bound information array'
1289          CALL message( 'rrd_local', 'PA0287', 2, 2, -1, 6, 1 )
1290       ENDIF
1291
1292       IF ( nxr_on_file /= hor_index_bounds_previous_run(2,j) )  THEN
1293           WRITE( message_string, * ) 'problem with index bound nxr on ',      &
1294                               'restart file "', myid_char, '"'  ,             &
1295                               '&nxr = ', nxr_on_file, ' but it should be',    &
1296                               '&= ', hor_index_bounds_previous_run(2,j),      &
1297                               '&from the index bound information array' 
1298          CALL message( 'rrd_local', 'PA0288', 2, 2, -1, 6, 1 )
1299
1300       ENDIF
1301
1302       IF ( nys_on_file /= hor_index_bounds_previous_run(3,j) )  THEN
1303          WRITE( message_string, * ) 'problem with index bound nys on ',       &
1304                                 'restart file "', myid_char, '"',             &
1305                                 '&nys = ', nys_on_file, ' but it should be',  &
1306                                 '&= ', hor_index_bounds_previous_run(3,j),    &
1307                                     '&from the index bound information array'
1308          CALL message( 'rrd_local', 'PA0289', 2, 2, -1, 6, 1 ) 
1309       ENDIF
1310
1311       IF ( nyn_on_file /= hor_index_bounds_previous_run(4,j) )  THEN
1312          WRITE( message_string, * ) 'problem with index bound nyn on ',       &
1313                               'restart file "', myid_char, '"',               &
1314                               '&nyn = ', nyn_on_file, ' but it should be',    &
1315                               '&= ', hor_index_bounds_previous_run(4,j),      &
1316                               '&from the index bound information array'
1317          CALL message( 'rrd_local', 'PA0290', 2, 2, -1, 6, 1 ) 
1318       ENDIF
1319
1320       IF ( nzb_on_file /= nzb )  THEN
1321          WRITE( message_string, * ) 'mismatch between actual data and data ', &
1322                                     '&from prior run on PE ', myid,           &
1323                                     '&nzb on file = ', nzb_on_file,           &
1324                                     '&nzb         = ', nzb
1325          CALL message( 'rrd_local', 'PA0291', 1, 2, 0, 6, 0 ) 
1326       ENDIF
1327
1328       IF ( nzt_on_file /= nzt )  THEN
1329          WRITE( message_string, * ) 'mismatch between actual data and data ', &
1330                                     '&from prior run on PE ', myid,           &
1331                                     '&nzt on file = ', nzt_on_file,           &
1332                                     '&nzt         = ', nzt
1333          CALL message( 'rrd_local', 'PA0292', 1, 2, 0, 6, 0 ) 
1334       ENDIF
1335
1336!
1337!--    Allocate temporary arrays sized as the arrays on the restart file
1338       ALLOCATE( tmp_2d(nys_on_file-nbgp:nyn_on_file+nbgp,                     &
1339                        nxl_on_file-nbgp:nxr_on_file+nbgp),                    &
1340                 tmp_3d(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,           &
1341                        nxl_on_file-nbgp:nxr_on_file+nbgp) )
1342
1343!
1344!--    Read arrays
1345!--    ATTENTION: If the following read commands have been altered, the
1346!--    ---------- version number of the variable binary_version_local must
1347!--               be altered, too. Furthermore, the output list of arrays in
1348!--               wrd_write_local must also be altered
1349!--               accordingly.
1350       READ ( 13 )  length
1351       READ ( 13 )  restart_string(1:length)
1352       
1353
1354!
1355!--    Loop over processor specific field data
1356       DO  WHILE ( restart_string(1:length) /= '*** end ***' )
1357
1358          found = .FALSE.
1359!
1360!--       Map data on file as often as needed (data are read only for k=1)
1361          DO  k = 1, overlap_count(i)
1362
1363!
1364!--          Get the index range of the subdomain on file which overlap with
1365!--          the current subdomain
1366             nxlf = nxlfa(i,k)
1367             nxlc = nxlfa(i,k) + offset_xa(i,k)
1368             nxrf = nxrfa(i,k)
1369             nxrc = nxrfa(i,k) + offset_xa(i,k)
1370             nysf = nysfa(i,k)
1371             nysc = nysfa(i,k) + offset_ya(i,k)
1372             nynf = nynfa(i,k)
1373             nync = nynfa(i,k) + offset_ya(i,k)
1374
1375
1376             SELECT CASE ( restart_string(1:length) )
1377
1378                CASE ( 'ghf_av' )
1379                   IF ( .NOT. ALLOCATED( ghf_av ) )  THEN
1380                      ALLOCATE( ghf_av(nysg:nyng,nxlg:nxrg) )
1381                   ENDIF
1382                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1383                   ghf_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1384                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1385
1386                CASE ( 'e' )
1387                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1388                   e(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =              &
1389                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1390
1391                CASE ( 'e_av' )
1392                   IF ( .NOT. ALLOCATED( e_av ) )  THEN
1393                      ALLOCATE( e_av(nzb:nzt+1,nys-nbgp:nyn+nbgp,              &
1394                                     nxl-nbgp:nxr+nbgp) )   
1395                   ENDIF
1396                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1397                   e_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1398                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1399
1400                CASE ( 'iran' ) ! matching random numbers is still unresolved
1401                                ! issue
1402                   IF ( k == 1 )  READ ( 13 )  iran, iran_part
1403
1404                CASE ( 'kh' )
1405                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1406                   kh(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =             &
1407                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1408
1409                CASE ( 'kh_av' )
1410                   IF ( .NOT. ALLOCATED( kh_av ) )  THEN
1411                      ALLOCATE( kh_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
1412                   ENDIF
1413                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1414                   kh_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1415                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1416
1417                CASE ( 'km' )
1418                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1419                   km(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =             &
1420                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1421
1422                CASE ( 'km_av' )
1423                   IF ( .NOT. ALLOCATED( km_av ) )  THEN
1424                      ALLOCATE( km_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
1425                   ENDIF
1426                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1427                   km_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1428                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1429
1430                CASE ( 'lpt_av' )
1431                   IF ( .NOT. ALLOCATED( lpt_av ) )  THEN
1432                      ALLOCATE( lpt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
1433                   ENDIF
1434                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1435                   lpt_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =         &
1436                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1437
1438                CASE ( 'lwp_av' )
1439                   IF ( .NOT. ALLOCATED( lwp_av ) )  THEN
1440                      ALLOCATE( lwp_av(nysg:nyng,nxlg:nxrg) )
1441                   ENDIF
1442                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1443                   lwp_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1444                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1445
1446                CASE ( 'nc' )
1447                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1448                   nc(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =             &
1449                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1450
1451                CASE ( 'nc_av' )
1452                   IF ( .NOT. ALLOCATED( nc_av ) )  THEN
1453                      ALLOCATE( nc_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1454                   ENDIF
1455                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1456                   nc_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1457                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1458
1459
1460                CASE ( 'nr' )
1461                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1462                   nr(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =             &
1463                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1464
1465                CASE ( 'nr_av' )
1466                   IF ( .NOT. ALLOCATED( nr_av ) )  THEN
1467                      ALLOCATE( nr_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1468                   ENDIF
1469                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1470                   nr_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1471                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1472
1473                CASE ( 'p' )
1474                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1475                   p(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =              &
1476                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1477
1478                CASE ( 'p_av' )
1479                   IF ( .NOT. ALLOCATED( p_av ) )  THEN
1480                      ALLOCATE( p_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1481                   ENDIF
1482                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1483                   p_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1484                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1485
1486                CASE ( 'pc_av' )
1487                   IF ( .NOT. ALLOCATED( pc_av ) )  THEN
1488                      ALLOCATE( pc_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1489                   ENDIF
1490                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1491                   pc_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1492                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1493
1494                CASE ( 'pr_av' )
1495                   IF ( .NOT. ALLOCATED( pr_av ) )  THEN
1496                      ALLOCATE( pr_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1497                   ENDIF
1498                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1499                   pr_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1500                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1501
1502                CASE ( 'prr' )
1503                   IF ( .NOT. ALLOCATED( prr ) )  THEN
1504                      ALLOCATE( prr(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1505                   ENDIF
1506                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1507                   prr(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =            &
1508                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1509
1510                CASE ( 'prr_av' )
1511                   IF ( .NOT. ALLOCATED( prr_av ) )  THEN
1512                      ALLOCATE( prr_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1513                   ENDIF
1514                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1515                   prr_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =         &
1516                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1517
1518                CASE ( 'precipitation_amount' )
1519                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1520                   precipitation_amount(nysc-nbgp:nync+nbgp,                   &
1521                                        nxlc-nbgp:nxrc+nbgp)  =                &
1522                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1523
1524                CASE ( 'precipitation_rate_av' )
1525                   IF ( .NOT. ALLOCATED( precipitation_rate_av ) )  THEN
1526                      ALLOCATE( precipitation_rate_av(nysg:nyng,nxlg:nxrg) )
1527                   ENDIF
1528                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1529                   precipitation_rate_av(nysc-nbgp:nync+nbgp,                  &
1530                                         nxlc-nbgp:nxrc+nbgp)  =               &
1531                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1532
1533                CASE ( 'pt' )
1534                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1535                   pt(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =             &
1536                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1537
1538                CASE ( 'pt_av' )
1539                   IF ( .NOT. ALLOCATED( pt_av ) )  THEN
1540                      ALLOCATE( pt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1541                   ENDIF
1542                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1543                   pt_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1544                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1545
1546                CASE ( 'q' )
1547                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1548                   q(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =              &
1549                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1550
1551                CASE ( 'q_av' )
1552                   IF ( .NOT. ALLOCATED( q_av ) )  THEN
1553                      ALLOCATE( q_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
1554                   ENDIF
1555                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1556                   q_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1557                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1558
1559                CASE ( 'qc' )
1560                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1561                   qc(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =             &
1562                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1563
1564                CASE ( 'qc_av' )
1565                   IF ( .NOT. ALLOCATED( qc_av ) )  THEN
1566                      ALLOCATE( qc_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1567                   ENDIF
1568                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1569                   qc_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1570                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1571
1572                CASE ( 'ql' )
1573                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1574                   ql(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =             &
1575                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1576
1577                CASE ( 'ql_av' )
1578                   IF ( .NOT. ALLOCATED( ql_av ) )  THEN
1579                      ALLOCATE( ql_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1580                   ENDIF
1581                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1582                   ql_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1583                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1584
1585                CASE ( 'qr' )
1586                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1587                   qr(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =             &
1588                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1589
1590                CASE ( 'qr_av' )
1591                   IF ( .NOT. ALLOCATED( qr_av ) )  THEN
1592                      ALLOCATE( qr_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1593                   ENDIF
1594                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1595                   qr_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1596                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1597
1598                CASE ( 'ql_c_av' )
1599                   IF ( .NOT. ALLOCATED( ql_c_av ) )  THEN
1600                      ALLOCATE( ql_c_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1601                   ENDIF
1602                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1603                   ql_c_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =        &
1604                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1605
1606                CASE ( 'ql_v_av' )
1607                   IF ( .NOT. ALLOCATED( ql_v_av ) )  THEN
1608                      ALLOCATE( ql_v_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1609                   ENDIF
1610                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1611                   ql_v_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =        &
1612                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1613
1614                CASE ( 'ql_vp_av' )
1615                   IF ( .NOT. ALLOCATED( ql_vp_av ) )  THEN
1616                      ALLOCATE( ql_vp_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1617                   ENDIF
1618                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1619                   ql_vp_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =       &
1620                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1621
1622                CASE ( 'qsws_av' )
1623                   IF ( .NOT. ALLOCATED( qsws_av ) )  THEN
1624                      ALLOCATE( qsws_av(nysg:nyng,nxlg:nxrg) )
1625                   ENDIF 
1626                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1627                   qsws_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =         &
1628                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1629
1630                CASE ( 'qv_av' )
1631                   IF ( .NOT. ALLOCATED( qv_av ) )  THEN
1632                      ALLOCATE( qv_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1633                   ENDIF
1634                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1635                   qv_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1636                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1637
1638                CASE ( 'r_a_av' )
1639                   IF ( .NOT. ALLOCATED( r_a_av ) )  THEN
1640                      ALLOCATE( r_a_av(nysg:nyng,nxlg:nxrg) )
1641                   ENDIF
1642                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1643                   r_a_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1644                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1645
1646                CASE ( 'random_iv' )  ! still unresolved issue
1647                   IF ( k == 1 )  READ ( 13 )  random_iv
1648                   IF ( k == 1 )  READ ( 13 )  random_iy
1649
1650                CASE ( 'seq_random_array' )
1651                   ALLOCATE( tmp_2d_id_random(nys_on_file:nyn_on_file,         &
1652                                              nxl_on_file:nxr_on_file) )
1653                   ALLOCATE( tmp_2d_seq_random(5,nys_on_file:nyn_on_file,      &
1654                                                 nxl_on_file:nxr_on_file) )
1655                   IF ( .NOT. ALLOCATED( id_random_array ) )  THEN
1656                      ALLOCATE( id_random_array(nys:nyn,nxl:nxr) )
1657                   ENDIF
1658                   IF ( .NOT. ALLOCATED( seq_random_array ) )  THEN
1659                      ALLOCATE( seq_random_array(5,nys:nyn,nxl:nxr) )
1660                   ENDIF
1661                   IF ( k == 1 )  READ ( 13 )  tmp_2d_id_random
1662                   IF ( k == 1 )  READ ( 13 )  tmp_2d_seq_random
1663                   id_random_array(nysc:nync,nxlc:nxrc) =                      &
1664                      tmp_2d_id_random(nysf:nynf,nxlf:nxrf)
1665                   seq_random_array(:,nysc:nync,nxlc:nxrc) =                   &
1666                      tmp_2d_seq_random(:,nysf:nynf,nxlf:nxrf)
1667                   DEALLOCATE( tmp_2d_id_random, tmp_2d_seq_random )
1668
1669                CASE ( 'rho_ocean_av' )
1670                   IF ( .NOT. ALLOCATED( rho_ocean_av ) )  THEN
1671                      ALLOCATE( rho_ocean_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1672                   ENDIF
1673                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1674                   rho_ocean_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =   &
1675                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1676                           
1677                CASE ( 's' )
1678                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1679                   s(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =              &
1680                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1681
1682                CASE ( 's_av' )
1683                   IF ( .NOT. ALLOCATED( s_av ) )  THEN
1684                      ALLOCATE( s_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg))
1685                   ENDIF
1686                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1687                   s_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1688                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1689
1690                CASE ( 'sa' )
1691                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1692                   sa(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =             &
1693                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1694
1695                CASE ( 'sa_av' )
1696                   IF ( .NOT. ALLOCATED( sa_av ) )  THEN
1697                      ALLOCATE( sa_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1698                   ENDIF
1699                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1700                   sa_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1701                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1702
1703                CASE ( 'shf_av' )
1704                   IF ( .NOT. ALLOCATED( shf_av ) )  THEN
1705                      ALLOCATE( shf_av(nysg:nyng,nxlg:nxrg) )
1706                   ENDIF
1707                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1708                   shf_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =          &
1709                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1710                   
1711                CASE ( 'ssws_av' )
1712                   IF ( .NOT. ALLOCATED( ssws_av ) )  THEN
1713                      ALLOCATE( ssws_av(nysg:nyng,nxlg:nxrg) )
1714                   ENDIF 
1715                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1716                   ssws_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =         &
1717                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1718                 
1719                CASE ( 'ts_av' )
1720                   IF ( .NOT. ALLOCATED( ts_av ) )  THEN
1721                      ALLOCATE( ts_av(nysg:nyng,nxlg:nxrg) )
1722                   ENDIF
1723                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1724                   ts_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =           &
1725                        tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1726
1727                CASE ( 'tsurf_av' )
1728                   IF ( .NOT. ALLOCATED( tsurf_av ) )  THEN
1729                      ALLOCATE( tsurf_av(nysg:nyng,nxlg:nxrg) )
1730                   ENDIF
1731                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1732                   tsurf_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =         &
1733                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1734
1735                CASE ( 'u' )
1736                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1737                   u(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =              &
1738                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1739
1740                CASE ( 'u_av' )
1741                   IF ( .NOT. ALLOCATED( u_av ) )  THEN
1742                      ALLOCATE( u_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1743                   ENDIF
1744                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1745                   u_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1746                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1747
1748                CASE ( 'u_m_l' )
1749                   IF ( k == 1 )  THEN
1750                      ALLOCATE( tmp_3dwul(nzb:nzt+1,                           &
1751                                nys_on_file-nbgp:nyn_on_file+nbgp,1:2) )
1752                      READ ( 13 )  tmp_3dwul
1753                   ENDIF
1754                   IF ( outflow_l )  THEN
1755                      u_m_l(:,nysc-nbgp:nync+nbgp,:) =                         & 
1756                         tmp_3dwul(:,nysf-nbgp:nynf+nbgp,:)
1757                   ENDIF
1758
1759                CASE ( 'u_m_n' )
1760                   IF ( k == 1 )  THEN
1761                      ALLOCATE( tmp_3dwun(nzb:nzt+1,ny-1:ny,                   &
1762                                          nxl_on_file-nbgp:nxr_on_file+nbgp) )
1763                      READ ( 13 )  tmp_3dwun
1764                   ENDIF
1765                   IF ( outflow_n )  THEN
1766                      u_m_n(:,:,nxlc-nbgp:nxrc+nbgp) =                         & 
1767                         tmp_3dwun(:,:,nxlf-nbgp:nxrf+nbgp)
1768                   ENDIF
1769
1770                CASE ( 'u_m_r' )
1771                   IF ( k == 1 )  THEN
1772                      ALLOCATE( tmp_3dwur(nzb:nzt+1,                           &
1773                                nys_on_file-nbgp:nyn_on_file+nbgp,nx-1:nx) )
1774                      READ ( 13 )  tmp_3dwur
1775                   ENDIF
1776                   IF ( outflow_r )  THEN
1777                      u_m_r(:,nysc-nbgp:nync+nbgp,:) =                         & 
1778                         tmp_3dwur(:,nysf-nbgp:nynf+nbgp,:)
1779                   ENDIF
1780
1781                CASE ( 'u_m_s' )
1782                   IF ( k == 1 )  THEN
1783                      ALLOCATE( tmp_3dwus(nzb:nzt+1,0:1,                       &
1784                                          nxl_on_file-nbgp:nxr_on_file+nbgp) )
1785                      READ ( 13 )  tmp_3dwus
1786                   ENDIF
1787                   IF ( outflow_s )  THEN
1788                      u_m_s(:,:,nxlc-nbgp:nxrc+nbgp) =                         &
1789                         tmp_3dwus(:,:,nxlf-nbgp:nxrf+nbgp)
1790                   ENDIF
1791
1792                CASE ( 'us_av' )
1793                   IF ( .NOT. ALLOCATED( us_av ) )  THEN
1794                      ALLOCATE( us_av(nysg:nyng,nxlg:nxrg) )
1795                   ENDIF
1796                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1797                   us_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =           &
1798                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1799
1800                CASE ( 'v' )
1801                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1802                   v(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =              &
1803                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1804
1805                CASE ( 'v_av' )
1806                   IF ( .NOT. ALLOCATED( v_av ) )  THEN
1807                      ALLOCATE( v_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1808                   ENDIF
1809                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1810                   v_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1811                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1812
1813                CASE ( 'v_m_l' )
1814                   IF ( k == 1 )  THEN
1815                      ALLOCATE( tmp_3dwvl(nzb:nzt+1,                           &
1816                                nys_on_file-nbgp:nyn_on_file+nbgp,0:1) )
1817                      READ ( 13 )  tmp_3dwvl
1818                   ENDIF
1819                   IF ( outflow_l )  THEN
1820                      v_m_l(:,nysc-nbgp:nync+nbgp,:) =                         & 
1821                         tmp_3dwvl(:,nysf-nbgp:nynf+nbgp,:)
1822                   ENDIF
1823
1824                CASE ( 'v_m_n' )
1825                   IF ( k == 1 )  THEN
1826                      ALLOCATE( tmp_3dwvn(nzb:nzt+1,ny-1:ny,                   &
1827                                          nxl_on_file-nbgp:nxr_on_file+nbgp) )
1828                      READ ( 13 )  tmp_3dwvn
1829                   ENDIF
1830                   IF ( outflow_n )  THEN
1831                      v_m_n(:,:,nxlc-nbgp:nxrc+nbgp) =                         &
1832                         tmp_3dwvn(:,:,nxlf-nbgp:nxrf+nbgp)
1833                   ENDIF
1834
1835                CASE ( 'v_m_r' )
1836                   IF ( k == 1 )  THEN
1837                      ALLOCATE( tmp_3dwvr(nzb:nzt+1,                           &
1838                                nys_on_file-nbgp:nyn_on_file+nbgp,nx-1:nx) )
1839                      READ ( 13 )  tmp_3dwvr
1840                   ENDIF
1841                   IF ( outflow_r )  THEN
1842                      v_m_r(:,nysc-nbgp:nync+nbgp,:) =                         &
1843                         tmp_3dwvr(:,nysf-nbgp:nynf+nbgp,:)
1844                   ENDIF
1845
1846                CASE ( 'v_m_s' )
1847                   IF ( k == 1 )  THEN
1848                      ALLOCATE( tmp_3dwvs(nzb:nzt+1,1:2,                       &
1849                                          nxl_on_file-nbgp:nxr_on_file+nbgp) )
1850                      READ ( 13 )  tmp_3dwvs
1851                   ENDIF
1852                   IF ( outflow_s )  THEN
1853                      v_m_s(:,:,nxlc-nbgp:nxrc+nbgp) =                         &
1854                         tmp_3dwvs(:,:,nxlf-nbgp:nxrf+nbgp)
1855                   ENDIF
1856
1857                CASE ( 'vpt' )
1858                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1859                   vpt(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =            &
1860                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1861
1862                CASE ( 'vpt_av' )
1863                   IF ( .NOT. ALLOCATED( vpt_av ) )  THEN
1864                      ALLOCATE( vpt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1865                   ENDIF
1866                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1867                   vpt_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =         &
1868                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1869
1870                CASE ( 'w' )
1871                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1872                   w(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =              &
1873                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1874
1875                CASE ( 'w_av' )
1876                   IF ( .NOT. ALLOCATED( w_av ) )  THEN
1877                      ALLOCATE( w_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1878                   ENDIF
1879                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1880                   w_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1881                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1882
1883                CASE ( 'w_m_l' )
1884                   IF ( k == 1 )  THEN
1885                      ALLOCATE( tmp_3dwwl(nzb:nzt+1,&
1886                                nys_on_file-nbgp:nyn_on_file+nbgp,0:1) )
1887                      READ ( 13 )  tmp_3dwwl
1888                   ENDIF
1889                   IF ( outflow_l )  THEN
1890                      w_m_l(:,nysc-nbgp:nync+nbgp,:) =                         & 
1891                         tmp_3dwwl(:,nysf-nbgp:nynf+nbgp,:)
1892                   ENDIF
1893
1894                CASE ( 'w_m_n' )
1895                   IF ( k == 1 )  THEN
1896                      ALLOCATE( tmp_3dwwn(nzb:nzt+1,ny-1:ny, &
1897                                          nxl_on_file-nbgp:nxr_on_file+nbgp) )
1898                      READ ( 13 )  tmp_3dwwn
1899                   ENDIF
1900                   IF ( outflow_n )  THEN
1901                      w_m_n(:,:,nxlc-nbgp:nxrc+nbgp) =                         &
1902                         tmp_3dwwn(:,:,nxlf-nbgp:nxrf+nbgp)
1903                   ENDIF
1904
1905                CASE ( 'w_m_r' )
1906                   IF ( k == 1 )  THEN
1907                      ALLOCATE( tmp_3dwwr(nzb:nzt+1,&
1908                                nys_on_file-nbgp:nyn_on_file+nbgp,nx-1:nx) )
1909                      READ ( 13 )  tmp_3dwwr
1910                   ENDIF
1911                   IF ( outflow_r )  THEN
1912                      w_m_r(:,nysc-nbgp:nync+nbgp,:) =                         & 
1913                         tmp_3dwwr(:,nysf-nbgp:nynf+nbgp,:)
1914                   ENDIF
1915
1916                CASE ( 'w_m_s' )
1917                   IF ( k == 1 )  THEN
1918                      ALLOCATE( tmp_3dwws(nzb:nzt+1,0:1, &
1919                                          nxl_on_file-nbgp:nxr_on_file+nbgp) )
1920                      READ ( 13 )  tmp_3dwws
1921                   ENDIF
1922                   IF ( outflow_s )  THEN
1923                      w_m_s(:,:,nxlc-nbgp:nxrc+nbgp) =                         & 
1924                         tmp_3dwws(:,:,nxlf-nbgp:nxrf+nbgp)
1925                   ENDIF
1926
1927                CASE ( 'z0_av' )
1928                   IF ( .NOT. ALLOCATED( z0_av ) )  THEN
1929                      ALLOCATE( z0_av(nysg:nyng,nxlg:nxrg) )
1930                   ENDIF
1931                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1932                   z0_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =           &
1933                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1934
1935                CASE ( 'z0h_av' )
1936                   IF ( .NOT. ALLOCATED( z0h_av ) )  THEN
1937                      ALLOCATE( z0h_av(nysg:nyng,nxlg:nxrg) )
1938                   ENDIF
1939                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1940                   z0h_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =          &
1941                       tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1942
1943                CASE ( 'z0q_av' )
1944                   IF ( .NOT. ALLOCATED( z0q_av ) )  THEN
1945                      ALLOCATE( z0q_av(nysg:nyng,nxlg:nxrg) )
1946                   ENDIF
1947                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1948                   z0q_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =          &
1949                       tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1950
1951                CASE DEFAULT
1952
1953!
1954!--                Read surface related variables
1955                   IF ( .NOT. found ) CALL surface_rrd_local( i, k, nxlf,      &
1956                                           nxlc, nxl_on_file, nxrf, nxrc,      & 
1957                                           nxr_on_file, nynf, nync,            & 
1958                                           nyn_on_file, nysf, nysc,            &
1959                                           nys_on_file, found )
1960
1961!
1962!--                Read urban surface restart data
1963                   IF ( .NOT. found ) CALL usm_rrd_local( i, k, nxlf,          & 
1964                                           nxlc, nxl_on_file, nxrf, nxrc,      &
1965                                           nxr_on_file, nynf, nync,            &
1966                                           nyn_on_file, nysf, nysc,            &
1967                                           nys_on_file, found )
1968
1969!
1970!--                Read land surface restart data
1971                   IF ( .NOT. found ) CALL lsm_rrd_local( i, k, nxlf,          & 
1972                                           nxlc, nxl_on_file, nxrf, nxrc,      &
1973                                           nxr_on_file, nynf, nync,            &
1974                                           nyn_on_file, nysf, nysc,            &
1975                                           nys_on_file, tmp_2d, found )
1976
1977!
1978!--                Read radiation restart data
1979                   IF ( .NOT. found ) CALL radiation_rrd_local( i, k, nxlf,    &
1980                                           nxlc, nxl_on_file, nxrf, nxrc,      &
1981                                           nxr_on_file, nynf, nync,            &
1982                                           nyn_on_file, nysf, nysc,            &
1983                                           nys_on_file, tmp_2d, tmp_3d, found )
1984
1985!
1986!--                Read chemistry restart data
1987                   IF ( .NOT. found ) CALL chem_rrd_local( i, k, nxlf,         &
1988                                           nxlc, nxl_on_file, nxrf, nxrc,      &
1989                                           nxr_on_file, nynf, nync,            & 
1990                                           nyn_on_file, nysf, nysc,            &
1991                                           nys_on_file, tmp_3d, found )
1992
1993!
1994!--                Read gust module restart data
1995                   IF ( .NOT. found ) CALL gust_rrd_local( i, k, nxlf,         &
1996                                           nxlc, nxl_on_file, nxrf, nxrc,      &
1997                                           nxr_on_file, nynf, nync,            &
1998                                           nyn_on_file, nysf, nysc,            &
1999                                           nys_on_file, tmp_2d, tmp_3d, found )
2000
2001!
2002!--                Read user-defined restart data
2003                   IF ( .NOT. found ) CALL user_rrd_local( i, k, nxlf,         &
2004                                           nxlc, nxl_on_file, nxrf, nxrc,      &
2005                                           nxr_on_file, nynf, nync,            &
2006                                           nyn_on_file, nysf, nysc,            &
2007                                           nys_on_file, tmp_3d, found )
2008
2009
2010                   IF ( .NOT. found )  THEN
2011                      WRITE( message_string, * ) 'unknown variable named "',   &
2012                                                 restart_string(1:length),     &
2013                                                '" found in subdomain data ',  & 
2014                                                'from prior run on PE ', myid
2015                      CALL message( 'rrd_local', 'PA0302', 1, 2, 0, 6, 0 )
2016 
2017                   ENDIF
2018
2019             END SELECT
2020
2021          ENDDO ! overlaploop
2022
2023!
2024!--       Deallocate arrays needed for specific variables only
2025          IF ( ALLOCATED( tmp_3dwul ) )  DEALLOCATE( tmp_3dwul )
2026          IF ( ALLOCATED( tmp_3dwun ) )  DEALLOCATE( tmp_3dwun )
2027          IF ( ALLOCATED( tmp_3dwur ) )  DEALLOCATE( tmp_3dwur )
2028          IF ( ALLOCATED( tmp_3dwus ) )  DEALLOCATE( tmp_3dwus )
2029          IF ( ALLOCATED( tmp_3dwvl ) )  DEALLOCATE( tmp_3dwvl )
2030          IF ( ALLOCATED( tmp_3dwvn ) )  DEALLOCATE( tmp_3dwvn )
2031          IF ( ALLOCATED( tmp_3dwvr ) )  DEALLOCATE( tmp_3dwvr )
2032          IF ( ALLOCATED( tmp_3dwvs ) )  DEALLOCATE( tmp_3dwvs )
2033          IF ( ALLOCATED( tmp_3dwwl ) )  DEALLOCATE( tmp_3dwwl )
2034          IF ( ALLOCATED( tmp_3dwwn ) )  DEALLOCATE( tmp_3dwwn )
2035          IF ( ALLOCATED( tmp_3dwwr ) )  DEALLOCATE( tmp_3dwwr )
2036          IF ( ALLOCATED( tmp_3dwws ) )  DEALLOCATE( tmp_3dwws )
2037
2038!
2039!--       Read next character string
2040          READ ( 13 )  length
2041          READ ( 13 )  restart_string(1:length)
2042
2043       ENDDO ! dataloop
2044
2045!
2046!--    Close the restart file
2047       CALL close_file( 13 )
2048
2049       DEALLOCATE( tmp_2d, tmp_3d )
2050
2051    ENDDO  ! loop over restart files
2052
2053
2054!
2055!-- Restore the original filename for the restart file to be written
2056    myid_char = myid_char_save
2057
2058!
2059!-- End of time measuring for reading binary data
2060    CALL cpu_log( log_point_s(14), 'rrd_local', 'stop' )
2061
2062 END SUBROUTINE rrd_local
2063
2064
2065!------------------------------------------------------------------------------!
2066! Description:
2067! ------------
2068!> Skipping the global control variables from restart-file (binary format)
2069!------------------------------------------------------------------------------!
2070
2071    SUBROUTINE rrd_skip_global
2072
2073
2074       IMPLICIT NONE
2075
2076       CHARACTER (LEN=10) ::  version_on_file
2077
2078       CHARACTER (LEN=1) ::  cdum
2079
2080
2081       READ ( 13 )  length
2082       READ ( 13 )  restart_string(1:length)
2083
2084       DO  WHILE ( restart_string(1:length) /= 'binary_version_local' )
2085
2086          READ ( 13 )  cdum
2087          READ ( 13 )  length 
2088          READ ( 13 )  restart_string(1:length)
2089
2090       ENDDO
2091
2092       BACKSPACE ( 13 )
2093       BACKSPACE ( 13 )
2094
2095
2096    END SUBROUTINE rrd_skip_global
2097
2098
2099 END MODULE read_restart_data_mod
Note: See TracBrowser for help on using the repository browser.