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

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

precipitation_rate removed, further allocation checks for data output of averaged quantities implemented, double CALL of flow_statistics at the beginning of time_integration removed, further minor bugfixes, comments added

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