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

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

Bugfix in case of restarts using cyclic fill

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