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

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

New vertical stretching procedure has been introduced

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