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

Last change on this file since 2912 was 2912, checked in by knoop, 6 years ago

Added gust module interface calls to restart data modules

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