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

Last change on this file since 3268 was 3241, checked in by raasch, 6 years ago

various changes to avoid compiler warnings (mainly removal of unused variables)

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