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

Last change on this file since 4534 was 4534, checked in by raasch, 4 years ago

I/O on reduced number of cores added (using shared memory MPI)

  • Property svn:keywords set to Id
File size: 110.2 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-2020 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: read_restart_data_mod.f90 4534 2020-05-14 18:35:22Z raasch $
27! adjustments for I/O on reduced number of cores using shared memory MPI
28!
29! 4518 2020-05-04 15:44:28Z suehring
30! Move input of diagnostic output quantities to doq_rrd_local
31!
32! 4517 2020-05-03 14:29:30Z raasch
33! qsurf and ssurf added
34!
35! 4498 2020-04-15 14:26:31Z raasch
36! argument removed from rd_mpi_io_open
37!
38! 4496 2020-04-15 08:37:26Z raasch
39! bugfix: MPI barrier removed, coupling character added to input filename
40!
41! 4495 2020-04-13 20:11:20Z raasch
42! restart data handling with MPI-IO added
43!
44! 4435 2020-03-03 10:38:41Z raasch
45! bugfix for message that reports about files that are read from in case that the virtual PE grid
46! has chenged (in case of large number of files format was exceeded), detailed messages about the
47! files are now output to the debug file
48!
49! 4431 2020-02-27 23:23:01Z gronemeier
50! added u_center_av, v_center_av, wspeed_av
51!
52! 4360 2020-01-07 11:25:50Z suehring
53! Change automatic arrays to allocatable ones in rrd_local, in order to avoid
54! memory problems due to too small stack size for large jobs with intel
55! compiler. (J.Resler)
56!
57! 4331 2019-12-10 18:25:02Z suehring
58! Enable restart data for 2-m potential temperature output
59!
60! 4301 2019-11-22 12:09:09Z oliver.maas
61! removed recycling_yshift
62!
63! 4227 2019-09-10 18:04:34Z gronemeier
64! implement new palm_date_time_mod and increased binary version
65!
66! 4146 2019-08-07 07:47:36Z gronemeier
67! Corrected "Former revisions" section
68!
69! 4131 2019-08-02 11:06:18Z monakurppa
70! Allocate hom and hom_sum to allow profile output for salsa variables.
71!
72! 4101 2019-07-17 15:14:26Z gronemeier
73! remove old_dt
74!
75! 4039 2019-06-18 10:32:41Z suehring
76! input of uu_av, vv_av, ww_av added
77!
78! 4017 2019-06-06 12:16:46Z schwenkel
79! bugfix for r3998, allocation of 3d temporary arrays of various dimensions revised
80!
81! 3998 2019-05-23 13:38:11Z suehring
82! Formatting adjustment
83!
84! 3994 2019-05-22 18:08:09Z suehring
85! output of turbulence intensity added
86!
87! 3988 2019-05-22 11:32:37Z kanani
88! + time_virtual_measurement (to enable steering of output interval)
89!
90! 3936 2019-04-26 15:38:02Z kanani
91! Enable time-averaged output of theta_2m* with restarts
92!
93! 3767 2019-02-27 08:18:02Z raasch
94! unused variables removed from rrd-subroutines parameter list
95!
96! 3766 2019-02-26 16:23:41Z raasch
97! first argument removed from module_interface_rrd_*
98!
99! 3668 2019-01-14 12:49:24Z maronga
100! Removed most_method and increased binary version
101!
102! 3655 2019-01-07 16:51:22Z knoop
103! Implementation of the PALM module interface
104!
105! 2894 2018-03-15 09:17:58Z Giersch
106! Initial revision
107!
108!
109! Description:
110! ------------
111!> Reads restart data from restart-file(s) (binary format).
112!>
113!> @todo: Revise max_pr_cs (profiles for chemistry)
114!> @todo: Modularize reading of restart data for diagnostic quantities, which
115!>        is not possible with the current module-interface structure
116!------------------------------------------------------------------------------!
117 MODULE read_restart_data_mod
118
119
120    USE arrays_3d,                                                             &
121        ONLY:  inflow_damping_factor, mean_inflow_profiles, pt_init,           &
122               q_init, ref_state, sa_init, s_init, u_init, ug, v_init, vg,     &
123               e, kh, km, p, pt, q, ql, s, u, u_m_l, u_m_n, u_m_r, u_m_s,      &
124               v, v_m_l, v_m_n, v_m_r, v_m_s, vpt, w, w_m_l, w_m_n, w_m_r, w_m_s
125
126    USE averaging
127
128    USE bulk_cloud_model_mod,                                                                      &
129        ONLY:  bulk_cloud_model
130
131    USE chem_modules,                                                                              &
132       ONLY: max_pr_cs
133
134    USE control_parameters
135
136    USE cpulog,                                                                &
137        ONLY:  cpu_log, log_point_s
138
139    USE grid_variables,                                                        &
140        ONLY:  dx, dy
141
142    USE gust_mod,                                                                                  &
143        ONLY:  gust_module_enabled
144
145    USE indices,                                                               &
146        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, nx_on_file, ny, nys, nysg, nyn, &
147               nyng, ny_on_file, nz, nzb, nzt
148
149    USE kinds
150
151    USE model_1d_mod,                                                          &
152        ONLY:  damp_level_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
153
154    USE module_interface,                                                      &
155        ONLY:  module_interface_rrd_global,                                    &
156               module_interface_rrd_local
157
158    USE netcdf_interface,                                                      &
159        ONLY:  netcdf_precision, output_for_t0
160
161    USE particle_attributes,                                                                       &
162        ONLY:  particle_advection
163
164    USE pegrid
165
166    USE radiation_model_mod,                                                   &
167        ONLY:  time_radiation
168
169    USE random_function_mod,                                                   &
170        ONLY:  random_iv, random_iy
171
172    USE random_generator_parallel,                                             &
173        ONLY:  id_random_array, seq_random_array
174
175    USE restart_data_mpi_io_mod,                                                                   &
176        ONLY:  rd_mpi_io_check_array, rd_mpi_io_close, rd_mpi_io_open, rrd_mpi_io,                 &
177               rrd_mpi_io_global_array
178
179    USE spectra_mod,                                                           &
180        ONLY:  average_count_sp, spectrum_x, spectrum_y
181
182    USE surface_mod,                                                           &
183        ONLY :  surface_rrd_local
184
185    USE statistics,                                                            &
186        ONLY:  statistic_regions, hom, hom_sum, pr_palm, u_max, u_max_ijk,     &
187               v_max, v_max_ijk, w_max, w_max_ijk, z_i
188
189    USE user,                                                                                      &
190        ONLY:  user_module_enabled
191
192    USE vertical_nesting_mod,                                                  &
193        ONLY:  vnest_init
194
195    USE virtual_measurement_mod,                                               &
196        ONLY:  time_virtual_measurement
197
198
199    IMPLICIT NONE
200
201
202    INTERFACE rrd_global
203       MODULE PROCEDURE rrd_global
204    END INTERFACE rrd_global
205
206    INTERFACE rrd_read_parts_of_global
207       MODULE PROCEDURE rrd_read_parts_of_global
208    END INTERFACE rrd_read_parts_of_global
209
210    INTERFACE rrd_local
211       MODULE PROCEDURE rrd_local
212    END INTERFACE rrd_local
213
214    INTERFACE rrd_skip_global
215       MODULE PROCEDURE rrd_skip_global
216    END INTERFACE rrd_skip_global
217
218
219    PUBLIC rrd_global, rrd_read_parts_of_global, rrd_local, rrd_skip_global
220
221
222 CONTAINS
223
224!------------------------------------------------------------------------------!
225! Description:
226! ------------
227!> Reads values of global control variables from restart-file (binary format)
228!> created by PE0 of the previous run
229!------------------------------------------------------------------------------!
230 SUBROUTINE rrd_global
231
232
233    CHARACTER(LEN=10) ::  binary_version_global  !<
234    CHARACTER(LEN=10) ::  version_on_file        !<
235    CHARACTER(LEN=20) ::  tmp_name               !< temporary variable
236
237    INTEGER ::  i                                !< loop index
238
239    LOGICAL ::  array_found                      !<
240    LOGICAL ::  found                            !<
241
242
243    CALL location_message( 'read global restart data', 'start' )
244
245    IF ( TRIM( restart_data_format_input ) == 'fortran_binary' )  THEN
246!
247!--    Input in Fortran binary format
248       CALL check_open( 13 )
249!
250!--    Make version number check first
251       READ ( 13 )  length
252       READ ( 13 )  restart_string(1:length)
253       READ ( 13 )  version_on_file
254
255       binary_version_global = '4.9'
256       IF ( TRIM( version_on_file ) /= TRIM( binary_version_global ) )  THEN
257          WRITE( message_string, * ) 'version mismatch concerning ',           &
258                                     'binary_version_global:',                 &
259                                     '&version on file    = "',                &
260                                     TRIM( version_on_file ), '"',             &
261                                     '&version on program = "',                &
262                                     TRIM( binary_version_global ), '"'
263          CALL message( 'rrd_global', 'PA0296', 1, 2, 0, 6, 0 )
264       ENDIF
265
266!
267!--    Read number of PEs and horizontal index bounds of all PEs used in the
268!--    previous run
269       READ ( 13 )  length
270       READ ( 13 )  restart_string(1:length)
271
272       IF ( TRIM( restart_string(1:length) ) /= 'numprocs' )  THEN
273          WRITE( message_string, * ) 'numprocs not found in data from prior ', &
274                                     'run on PE ', myid
275          CALL message( 'rrd_global', 'PA0297', 1, 2, 0, 6, 0 )
276       ENDIF
277       READ ( 13 )  numprocs_previous_run
278
279       IF ( .NOT. ALLOCATED( hor_index_bounds_previous_run ) )  THEN
280          ALLOCATE( hor_index_bounds_previous_run(4,0:numprocs_previous_run-1) )
281       ENDIF
282
283       READ ( 13 )  length
284       READ ( 13 )  restart_string(1:length)
285
286       IF ( restart_string(1:length) /= 'hor_index_bounds' )  THEN
287          WRITE( message_string, * ) 'hor_index_bounds not found in data ',    &
288                                     'from prior run on PE ', myid
289          CALL message( 'rrd_global', 'PA0298', 1, 2, 0, 6, 0 )
290       ENDIF
291       READ ( 13 )  hor_index_bounds_previous_run
292
293!
294!--    Read vertical number of gridpoints and number of different areas used
295!--    for computing statistics. Allocate arrays depending on these values,
296!--    which are needed for the following read instructions.
297       READ ( 13 )  length
298       READ ( 13 )  restart_string(1:length)
299
300       IF ( restart_string(1:length) /= 'nz' )  THEN
301          WRITE( message_string, * ) 'nz not found in data from prior run ',   &
302                                     'on PE ', myid
303          CALL message( 'rrd_global', 'PA0299', 1, 2, 0, 6, 0 )
304       ENDIF
305       READ ( 13 )  nz
306
307       READ ( 13 )  length
308       READ ( 13 )  restart_string(1:length)
309
310       IF ( restart_string(1:length) /= 'max_pr_user' )  THEN
311          WRITE( message_string, * ) 'max_pr_user not found in data from ',    &
312                                     'prior run on PE ', myid
313          CALL message( 'rrd_global', 'PA0300', 1, 2, 0, 6, 0 )
314       ENDIF
315       READ ( 13 )  max_pr_user    ! This value is checked against the number of
316                                   ! user profiles given for the current run
317                                   ! in routine user_parin (it has to match)
318
319       READ ( 13 )  length
320       READ ( 13 )  restart_string(1:length)
321
322       IF ( restart_string(1:length) /= 'statistic_regions' )  THEN
323          WRITE( message_string, * ) 'statistic_regions not found in data ',   &
324                                     'from prior run on PE ', myid
325          CALL message( 'rrd_global', 'PA0301', 1, 2, 0, 6, 0 )
326       ENDIF
327       READ ( 13 )  statistic_regions
328
329!
330!--    The following global arrays (better to say, they have the same size and values on each
331!--    subdomain) are by default allocated in routine parin, but not in case of restarts!
332       IF ( .NOT. ALLOCATED( ug ) )  THEN
333          ALLOCATE( ug(0:nz+1), u_init(0:nz+1), vg(0:nz+1),                                        &
334                    v_init(0:nz+1), pt_init(0:nz+1), q_init(0:nz+1),                               &
335                    ref_state(0:nz+1), s_init(0:nz+1), sa_init(0:nz+1),                            &
336                    hom(0:nz+1,2,pr_palm+max_pr_user+max_pr_cs+max_pr_salsa,0:statistic_regions),  &
337                    hom_sum(0:nz+1,pr_palm+max_pr_user+max_pr_cs+max_pr_salsa,0:statistic_regions) )
338       ENDIF
339
340!
341!--    Now read all control parameters:
342!--    Caution: When the following read instructions have been changed, the
343!--    -------  version number stored in the variable binary_version_global has
344!--             to be increased. The same changes must also be done in
345!--             wrd_write_global.
346       READ ( 13 )  length
347       READ ( 13 )  restart_string(1:length)
348
349       DO WHILE ( restart_string(1:length) /= 'binary_version_local' )
350
351          found = .FALSE.
352
353          SELECT CASE ( restart_string(1:length) )
354
355             CASE ( 'advected_distance_x' )
356                READ ( 13 )  advected_distance_x
357             CASE ( 'advected_distance_y' )
358                READ ( 13 )  advected_distance_y
359             CASE ( 'alpha_surface' )
360                READ ( 13 )  alpha_surface
361             CASE ( 'average_count_pr' )
362                READ ( 13 )  average_count_pr
363             CASE ( 'average_count_sp' )
364                READ ( 13 )  average_count_sp
365             CASE ( 'average_count_3d' )
366                READ ( 13 )  average_count_3d
367             CASE ( 'bc_e_b' )
368                READ ( 13 )  bc_e_b
369             CASE ( 'bc_lr' )
370                READ ( 13 )  bc_lr
371             CASE ( 'bc_ns' )
372                READ ( 13 )  bc_ns
373             CASE ( 'bc_p_b' )
374                READ ( 13 )  bc_p_b
375             CASE ( 'bc_p_t' )
376                READ ( 13 )  bc_p_t
377             CASE ( 'bc_pt_b' )
378                READ ( 13 )  bc_pt_b
379             CASE ( 'bc_pt_t' )
380                READ ( 13 )  bc_pt_t
381             CASE ( 'bc_pt_t_val' )
382                READ ( 13 )  bc_pt_t_val
383             CASE ( 'bc_q_b' )
384                READ ( 13 )  bc_q_b
385             CASE ( 'bc_q_t' )
386                READ ( 13 )  bc_q_t
387             CASE ( 'bc_q_t_val' )
388                READ ( 13 )  bc_q_t_val
389             CASE ( 'bc_s_b' )
390                READ ( 13 )  bc_s_b
391             CASE ( 'bc_s_t' )
392                READ ( 13 )  bc_s_t
393             CASE ( 'bc_uv_b' )
394                READ ( 13 )  bc_uv_b
395             CASE ( 'bc_uv_t' )
396                READ ( 13 )  bc_uv_t
397             CASE ( 'building_height' )
398                READ ( 13 )  building_height
399             CASE ( 'building_length_x' )
400                READ ( 13 )  building_length_x
401             CASE ( 'building_length_y' )
402                READ ( 13 )  building_length_y
403             CASE ( 'building_wall_left' )
404                READ ( 13 )  building_wall_left
405             CASE ( 'building_wall_south' )
406                READ ( 13 )  building_wall_south
407             CASE ( 'call_psolver_at_all_substeps' )
408                READ ( 13 )  call_psolver_at_all_substeps
409             CASE ( 'canyon_height' )
410                READ ( 13 )  canyon_height
411             CASE ( 'canyon_wall_left' )
412                READ ( 13 )  canyon_wall_left
413             CASE ( 'canyon_wall_south' )
414                READ ( 13 )  canyon_wall_south
415             CASE ( 'canyon_width_x' )
416                READ ( 13 )  canyon_width_x
417             CASE ( 'canyon_width_y' )
418                READ ( 13 )  canyon_width_y
419             CASE ( 'cfl_factor' )
420                READ ( 13 )  cfl_factor
421             CASE ( 'cloud_droplets' )
422                READ ( 13 )  cloud_droplets
423             CASE ( 'collective_wait' )
424                READ ( 13 )  collective_wait
425             CASE ( 'conserve_volume_flow' )
426                READ ( 13 )  conserve_volume_flow
427             CASE ( 'conserve_volume_flow_mode' )
428                READ ( 13 )  conserve_volume_flow_mode
429             CASE ( 'constant_flux_layer' )
430                READ ( 13 )  constant_flux_layer
431             CASE ( 'coupling_start_time' )
432                READ ( 13 )  coupling_start_time
433             CASE ( 'current_timestep_number' )
434                READ ( 13 )  current_timestep_number
435             CASE ( 'cycle_mg' )
436                READ ( 13 )  cycle_mg
437             CASE ( 'damp_level_1d' )
438                READ ( 13 )  damp_level_1d
439             CASE ( 'origin_date_time' )
440                READ ( 13 )  origin_date_time
441             CASE ( 'dissipation_1d' )
442                READ ( 13 )  dissipation_1d
443             CASE ( 'do2d_xy_time_count' )
444                READ ( 13 )  do2d_xy_time_count
445             CASE ( 'do2d_xz_time_count' )
446                READ ( 13 )  do2d_xz_time_count
447             CASE ( 'do2d_yz_time_count' )
448                READ ( 13 )  do2d_yz_time_count
449             CASE ( 'do3d_time_count' )
450                READ ( 13 )  do3d_time_count
451             CASE ( 'dp_external' )
452                READ ( 13 )  dp_external
453             CASE ( 'dp_level_b' )
454                READ ( 13 )  dp_level_b
455             CASE ( 'dp_smooth' )
456                READ ( 13 )  dp_smooth
457             CASE ( 'dpdxy' )
458                READ ( 13 )  dpdxy
459             CASE ( 'dt_3d' )
460                READ ( 13 )  dt_3d
461             CASE ( 'dt_pr_1d' )
462                READ ( 13 )  dt_pr_1d
463             CASE ( 'dt_run_control_1d' )
464                READ ( 13 )  dt_run_control_1d
465             CASE ( 'dx' )
466                READ ( 13 )  dx
467             CASE ( 'dy' )
468                READ ( 13 )  dy
469             CASE ( 'dz' )
470                READ ( 13 )  dz
471             CASE ( 'dz_max' )
472                READ ( 13 )  dz_max
473             CASE ( 'dz_stretch_factor' )
474                READ ( 13 )  dz_stretch_factor
475             CASE ( 'dz_stretch_factor_array' )
476                READ ( 13 )  dz_stretch_factor_array
477             CASE ( 'dz_stretch_level' )
478                READ ( 13 )  dz_stretch_level
479             CASE ( 'dz_stretch_level_end' )
480                READ ( 13 )  dz_stretch_level_end
481             CASE ( 'dz_stretch_level_start' )
482                READ ( 13 )  dz_stretch_level_start
483             CASE ( 'e_min' )
484                READ ( 13 )  e_min
485             CASE ( 'end_time_1d' )
486                READ ( 13 )  end_time_1d
487             CASE ( 'fft_method' )
488                READ ( 13 )  fft_method
489             CASE ( 'first_call_lpm' )
490                READ ( 13 )  first_call_lpm
491             CASE ( 'galilei_transformation' )
492                READ ( 13 )  galilei_transformation
493             CASE ( 'hom' )
494                READ ( 13 )  hom
495             CASE ( 'hom_sum' )
496                READ ( 13 )  hom_sum
497             CASE ( 'humidity' )
498                READ ( 13 )  humidity
499             CASE ( 'inflow_damping_factor' )
500                IF ( .NOT. ALLOCATED( inflow_damping_factor ) )  THEN
501                   ALLOCATE( inflow_damping_factor(0:nz+1) )
502                ENDIF
503                READ ( 13 )  inflow_damping_factor
504             CASE ( 'inflow_damping_height' )
505                READ ( 13 )  inflow_damping_height
506             CASE ( 'inflow_damping_width' )
507                READ ( 13 )  inflow_damping_width
508             CASE ( 'inflow_disturbance_begin' )
509                READ ( 13 )  inflow_disturbance_begin
510             CASE ( 'inflow_disturbance_end' )
511                READ ( 13 )  inflow_disturbance_end
512             CASE ( 'km_constant' )
513                READ ( 13 )  km_constant
514             CASE ( 'large_scale_forcing' )
515                READ ( 13 )  large_scale_forcing
516             CASE ( 'large_scale_subsidence' )
517                READ ( 13 )  large_scale_subsidence
518             CASE ( 'latitude' )
519                READ ( 13 )  latitude
520             CASE ( 'longitude' )
521                READ ( 13 )  longitude
522             CASE ( 'loop_optimization' )
523                READ ( 13 )  loop_optimization
524             CASE ( 'masking_method' )
525                READ ( 13 )  masking_method
526             CASE ( 'mean_inflow_profiles' )
527                IF ( .NOT. ALLOCATED( mean_inflow_profiles ) )  THEN
528                   ALLOCATE( mean_inflow_profiles(0:nz+1,1:num_mean_inflow_profiles) )
529                ENDIF
530                READ ( 13 )  mean_inflow_profiles
531             CASE ( 'mg_cycles' )
532                READ ( 13 )  mg_cycles
533             CASE ( 'mg_switch_to_pe0_level' )
534                READ ( 13 )  mg_switch_to_pe0_level
535             CASE ( 'mixing_length_1d' )
536                READ ( 13 )  mixing_length_1d
537             CASE ( 'momentum_advec' )
538                READ ( 13 )  momentum_advec
539             CASE ( 'netcdf_precision' )
540                READ ( 13 )  netcdf_precision
541             CASE ( 'neutral' )
542                READ ( 13 )  neutral
543             CASE ( 'ngsrb' )
544                READ ( 13 )  ngsrb
545             CASE ( 'nsor' )
546                READ ( 13 )  nsor
547             CASE ( 'nsor_ini' )
548                READ ( 13 )  nsor_ini
549             CASE ( 'nudging' )
550                READ ( 13 )  nudging
551             CASE ( 'num_leg' )
552                READ ( 13 )  num_leg
553             CASE ( 'nx' )
554                READ ( 13 )  nx
555                nx_on_file = nx
556             CASE ( 'ny' )
557                READ ( 13 )  ny
558                ny_on_file = ny
559             CASE ( 'ocean_mode' )
560                READ ( 13 )  ocean_mode
561             CASE ( 'omega' )
562                READ ( 13 )  omega
563             CASE ( 'omega_sor' )
564                READ ( 13 )  omega_sor
565             CASE ( 'output_for_t0' )
566                READ (13)    output_for_t0
567             CASE ( 'passive_scalar' )
568                READ ( 13 )  passive_scalar
569             CASE ( 'prandtl_number' )
570                READ ( 13 )  prandtl_number
571             CASE ( 'psolver' )
572                READ ( 13 )  psolver
573             CASE ( 'pt_damping_factor' )
574                READ ( 13 )  pt_damping_factor
575             CASE ( 'pt_damping_width' )
576                READ ( 13 )  pt_damping_width
577             CASE ( 'pt_init' )
578                READ ( 13 )  pt_init
579             CASE ( 'pt_reference' )
580                READ ( 13 )  pt_reference
581             CASE ( 'pt_surface' )
582                READ ( 13 )  pt_surface
583             CASE ( 'pt_surface_initial_change' )
584                READ ( 13 )  pt_surface_initial_change
585             CASE ( 'pt_vertical_gradient' )
586                READ ( 13 )  pt_vertical_gradient
587             CASE ( 'pt_vertical_gradient_level' )
588                READ ( 13 )  pt_vertical_gradient_level
589             CASE ( 'pt_vertical_gradient_level_ind' )
590                READ ( 13 )  pt_vertical_gradient_level_ind
591             CASE ( 'q_init' )
592                READ ( 13 )  q_init
593             CASE ( 'q_surface' )
594                READ ( 13 )  q_surface
595             CASE ( 'q_surface_initial_change' )
596                READ ( 13 )  q_surface_initial_change
597             CASE ( 'q_vertical_gradient' )
598                READ ( 13 )  q_vertical_gradient
599             CASE ( 'q_vertical_gradient_level' )
600                READ ( 13 )  q_vertical_gradient_level
601             CASE ( 'q_vertical_gradient_level_ind' )
602                READ ( 13 )  q_vertical_gradient_level_ind
603             CASE ( 'random_generator' )
604                READ ( 13 )  random_generator
605             CASE ( 'random_heatflux' )
606                READ ( 13 )  random_heatflux
607             CASE ( 'rans_mode' )
608                READ ( 13 )  rans_mode
609             CASE ( 'rayleigh_damping_factor' )
610                READ ( 13 )  rayleigh_damping_factor
611             CASE ( 'rayleigh_damping_height' )
612                READ ( 13 )  rayleigh_damping_height
613             CASE ( 'recycling_width' )
614                READ ( 13 )  recycling_width
615             CASE ( 'ref_state' )
616                READ ( 13 )  ref_state
617             CASE ( 'reference_state' )
618                READ ( 13 )  reference_state
619             CASE ( 'residual_limit' )
620                READ ( 13 )  residual_limit
621             CASE ( 'roughness_length' )
622                READ ( 13 )  roughness_length
623             CASE ( 'run_coupled' )
624                READ ( 13 )  run_coupled
625             CASE ( 'runnr' )
626                READ ( 13 )  runnr
627             CASE ( 's_init' )
628                READ ( 13 )  s_init
629             CASE ( 's_surface' )
630                READ ( 13 )  s_surface
631             CASE ( 's_surface_initial_change' )
632                READ ( 13 )  s_surface_initial_change
633             CASE ( 's_vertical_gradient' )
634                READ ( 13 )  s_vertical_gradient
635             CASE ( 's_vertical_gradient_level' )
636                READ ( 13 )  s_vertical_gradient_level
637             CASE ( 's_vertical_gradient_level_ind' )
638                READ ( 13 )  s_vertical_gradient_level_ind
639             CASE ( 'scalar_advec' )
640                READ ( 13 )  scalar_advec
641             CASE ( 'simulated_time' )
642                READ ( 13 )  simulated_time
643             CASE ( 'spectrum_x' )
644                IF ( .NOT. ALLOCATED( spectrum_x ) )  THEN
645                   ALLOCATE( spectrum_x( 1:nx/2, 1:100, 1:10 ) )
646                ENDIF
647                READ ( 13 )  spectrum_x
648             CASE ( 'spectrum_y' )
649                IF ( .NOT. ALLOCATED( spectrum_y ) )  THEN
650                   ALLOCATE( spectrum_y( 1:ny/2, 1:100, 1:10 ) )
651                ENDIF
652                READ ( 13 )  spectrum_y
653             CASE ( 'spinup_time' )
654                READ ( 13 )  spinup_time
655             CASE ( 'subs_vertical_gradient' )
656                READ ( 13 )  subs_vertical_gradient
657             CASE ( 'subs_vertical_gradient_level' )
658                READ ( 13 )  subs_vertical_gradient_level
659             CASE ( 'subs_vertical_gradient_level_i' )
660                READ ( 13 )  subs_vertical_gradient_level_i
661             CASE ( 'surface_heatflux' )
662                READ ( 13 )  surface_heatflux
663             CASE ( 'surface_pressure' )
664                READ ( 13 )  surface_pressure
665             CASE ( 'surface_scalarflux' )
666                READ ( 13 )  surface_scalarflux
667             CASE ( 'surface_waterflux' )
668                READ ( 13 )  surface_waterflux
669             CASE ( 'time_coupling' )
670                READ ( 13 )  time_coupling
671             CASE ( 'time_disturb' )
672                READ ( 13 )  time_disturb
673             CASE ( 'time_do2d_xy' )
674                READ ( 13 )  time_do2d_xy
675             CASE ( 'time_do2d_xz' )
676                READ ( 13 )  time_do2d_xz
677             CASE ( 'time_do2d_yz' )
678                READ ( 13 )  time_do2d_yz
679             CASE ( 'time_do3d' )
680                READ ( 13 )  time_do3d
681             CASE ( 'time_do_av' )
682                READ ( 13 )  time_do_av
683             CASE ( 'time_do_sla' )
684                READ ( 13 )  time_do_sla
685             CASE ( 'time_domask' )
686                READ ( 13 )  time_domask
687             CASE ( 'time_dopr' )
688                READ ( 13 )  time_dopr
689             CASE ( 'time_dopr_av' )
690                READ ( 13 )  time_dopr_av
691             CASE ( 'time_dopr_listing' )
692                READ ( 13 )  time_dopr_listing
693             CASE ( 'time_dopts' )
694                READ ( 13 )  time_dopts
695             CASE ( 'time_dosp' )
696                READ ( 13 )  time_dosp
697             CASE ( 'time_dots' )
698                READ ( 13 )  time_dots
699             CASE ( 'time_radiation' )
700                READ ( 13 )  time_radiation
701             CASE ( 'time_restart' )
702                READ ( 13 )  time_restart
703             CASE ( 'time_run_control' )
704                READ ( 13 )  time_run_control
705             CASE ( 'time_since_reference_point' )
706                READ ( 13 )  time_since_reference_point
707             CASE ( 'time_virtual_measurement' )
708                READ ( 13 )  time_virtual_measurement
709             CASE ( 'timestep_scheme' )
710                READ ( 13 )  timestep_scheme
711             CASE ( 'top_heatflux' )
712                READ ( 13 )  top_heatflux
713             CASE ( 'top_momentumflux_u' )
714                READ ( 13 )  top_momentumflux_u
715             CASE ( 'top_momentumflux_v' )
716                READ ( 13 )  top_momentumflux_v
717             CASE ( 'top_scalarflux' )
718                READ ( 13 )  top_scalarflux
719             CASE ( 'topography' )
720                READ ( 13 )  topography
721             CASE ( 'topography_grid_convention' )
722                READ ( 13 )  topography_grid_convention
723             CASE ( 'tsc' )
724                READ ( 13 )  tsc
725             CASE ( 'tunnel_height' )
726                READ ( 13 )  tunnel_height
727             CASE ( 'tunnel_length' )
728                READ ( 13 )  tunnel_length
729             CASE ( 'tunnel_wall_depth' )
730                READ ( 13 )  tunnel_wall_depth
731             CASE ( 'tunnel_width_x' )
732                READ ( 13 )  tunnel_width_x
733             CASE ( 'tunnel_width_y' )
734                READ ( 13 )  tunnel_width_y
735             CASE ( 'turbulence_closure' )
736                READ ( 13 )  turbulence_closure
737             CASE ( 'turbulent_inflow' )
738                READ ( 13 )  turbulent_inflow
739             CASE ( 'u_bulk' )
740                READ ( 13 )  u_bulk
741             CASE ( 'u_init' )
742                READ ( 13 )  u_init
743             CASE ( 'u_max' )
744                READ ( 13 )  u_max
745             CASE ( 'u_max_ijk' )
746                READ ( 13 )  u_max_ijk
747             CASE ( 'ug' )
748                READ ( 13 )  ug
749             CASE ( 'ug_surface' )
750                READ ( 13 )  ug_surface
751             CASE ( 'ug_vertical_gradient' )
752                READ ( 13 )  ug_vertical_gradient
753             CASE ( 'ug_vertical_gradient_level' )
754                READ ( 13 )  ug_vertical_gradient_level
755             CASE ( 'ug_vertical_gradient_level_ind' )
756                READ ( 13 )  ug_vertical_gradient_level_ind
757             CASE ( 'use_surface_fluxes' )
758                READ ( 13 )  use_surface_fluxes
759             CASE ( 'use_top_fluxes' )
760                READ ( 13 )  use_top_fluxes
761             CASE ( 'use_ug_for_galilei_tr' )
762                READ ( 13 )  use_ug_for_galilei_tr
763             CASE ( 'use_upstream_for_tke' )
764                READ ( 13 )  use_upstream_for_tke
765             CASE ( 'v_bulk' )
766                READ ( 13 )  v_bulk
767             CASE ( 'v_init' )
768                READ ( 13 )  v_init
769             CASE ( 'v_max' )
770                READ ( 13 )  v_max
771             CASE ( 'v_max_ijk' )
772                READ ( 13 )  v_max_ijk
773             CASE ( 'vg' )
774                READ ( 13 )  vg
775             CASE ( 'vg_surface' )
776                READ ( 13 )  vg_surface
777             CASE ( 'vg_vertical_gradient' )
778                READ ( 13 )  vg_vertical_gradient
779             CASE ( 'vg_vertical_gradient_level' )
780                READ ( 13 )  vg_vertical_gradient_level
781             CASE ( 'vg_vertical_gradient_level_ind' )
782                READ ( 13 )  vg_vertical_gradient_level_ind
783             CASE ( 'virtual_flight' )
784                READ ( 13 )  virtual_flight
785             CASE ( 'vnest_init' )
786                READ ( 13 )  vnest_init
787             CASE ( 'volume_flow_area' )
788                READ ( 13 )  volume_flow_area
789             CASE ( 'volume_flow_initial' )
790                READ ( 13 )  volume_flow_initial
791             CASE ( 'w_max' )
792                READ ( 13 )  w_max
793             CASE ( 'w_max_ijk' )
794                READ ( 13 )  w_max_ijk
795             CASE ( 'wall_adjustment' )
796                READ ( 13 )  wall_adjustment
797             CASE ( 'wall_heatflux' )
798                READ ( 13 )  wall_heatflux
799             CASE ( 'wall_humidityflux' )
800                READ ( 13 )  wall_humidityflux
801             CASE ( 'wall_scalarflux' )
802                READ ( 13 )  wall_scalarflux
803             CASE ( 'y_shift' )
804                READ ( 13 )  y_shift
805             CASE ( 'z0h_factor' )
806                READ ( 13 )  z0h_factor
807             CASE ( 'zeta_max' )
808                READ ( 13 )  zeta_max
809             CASE ( 'zeta_min' )
810                READ ( 13 )  zeta_min
811             CASE ( 'z_i' )
812                READ ( 13 )  z_i
813
814             CASE DEFAULT
815!
816!--             Read global variables from of other modules
817                CALL module_interface_rrd_global( found )
818
819                IF ( .NOT. found )  THEN
820                   WRITE( message_string, * ) 'unknown variable named "',      &
821                                           restart_string(1:length),           &
822                                          '" found in global data from ',      &
823                                          'prior run on PE ', myid
824                CALL message( 'rrd_global', 'PA0302', 1, 2, 0, 6, 0 )
825
826                ENDIF
827
828          END SELECT
829!
830!--       Read next string
831          READ ( 13 )  length
832          READ ( 13 )  restart_string(1:length)
833
834       ENDDO  ! End of loop for reading the restart string
835
836       CALL close_file( 13 )
837
838    ELSEIF ( restart_data_format_input(1:3) == 'mpi' )  THEN
839!
840!--    Read global restart data using MPI-IO
841!--    ATTENTION: Arrays need to be read with routine rrd_mpi_io_global_array!
842!--    Caution: When any of the following read instructions have been changed, the
843!--    -------  version number stored in the variable binary_version_global has
844!--             to be increased. The same changes must also be done in
845!--             wrd_write_global.
846!
847!--    Open the MPI-IO restart file.
848       CALL rd_mpi_io_open( 'read', 'BININ' // TRIM( coupling_char ),                              &
849                            open_for_global_io_only = .TRUE. )
850
851!
852!--    Make version number check first
853       CALL rrd_mpi_io( 'binary_version_global',  version_on_file )
854
855       binary_version_global = '5.0'
856       IF ( TRIM( version_on_file ) /= TRIM( binary_version_global ) )  THEN
857          WRITE( message_string, * ) 'version mismatch concerning binary_version_global:',         &
858                                     '&version on file    = "', TRIM( version_on_file ), '"',      &
859                                     '&version in program = "', TRIM( binary_version_global ), '"'
860          CALL message( 'rrd_global', 'PA0296', 1, 2, 0, 6, 0 )
861       ENDIF
862
863       CALL rrd_mpi_io( 'numprocs',  numprocs_previous_run )
864       CALL rrd_mpi_io( 'nz' , nz )
865       CALL rrd_mpi_io( 'max_pr_user',  max_pr_user )
866       CALL rrd_mpi_io( 'statistic_regions', statistic_regions )
867
868!
869!--    The following global arrays (better to say, they have the same size and values on each
870!--    subdomain) are by default allocated in routine parin, but not in case of restarts!
871       IF ( .NOT. ALLOCATED( ug ) )  THEN
872           ALLOCATE( ug(0:nz+1), u_init(0:nz+1), vg(0:nz+1),                                       &
873                     v_init(0:nz+1), pt_init(0:nz+1), q_init(0:nz+1),                              &
874                     ref_state(0:nz+1), s_init(0:nz+1), sa_init(0:nz+1),                           &
875                     hom(0:nz+1,2,pr_palm+max_pr_user,0:statistic_regions),                        &
876                     hom_sum(0:nz+1,pr_palm+max_pr_user,0:statistic_regions) )
877       ENDIF
878
879       CALL rrd_mpi_io( 'advected_distance_x',  advected_distance_x )
880       CALL rrd_mpi_io( 'advected_distance_y', advected_distance_y )
881       CALL rrd_mpi_io( 'alpha_surface', alpha_surface )
882       CALL rrd_mpi_io( 'average_count_pr', average_count_pr )
883       CALL rrd_mpi_io( 'average_count_sp', average_count_sp )
884       CALL rrd_mpi_io( 'average_count_3d', average_count_3d )
885       CALL rrd_mpi_io( 'bc_e_b', bc_e_b )
886       CALL rrd_mpi_io( 'bc_lr', bc_lr )
887       CALL rrd_mpi_io( 'bc_ns', bc_ns )
888       CALL rrd_mpi_io( 'bc_p_b', bc_p_b )
889       CALL rrd_mpi_io( 'bc_p_t', bc_p_t )
890       CALL rrd_mpi_io( 'bc_pt_b', bc_pt_b )
891       CALL rrd_mpi_io( 'bc_pt_t', bc_pt_t )
892       CALL rrd_mpi_io( 'bc_pt_t_val', bc_pt_t_val )
893       CALL rrd_mpi_io( 'bc_q_b', bc_q_b )
894       CALL rrd_mpi_io( 'bc_q_t', bc_q_t )
895       CALL rrd_mpi_io( 'bc_q_t_val', bc_q_t_val )
896       CALL rrd_mpi_io( 'bc_s_b', bc_s_b )
897       CALL rrd_mpi_io( 'bc_s_t', bc_s_t )
898       CALL rrd_mpi_io( 'bc_uv_b', bc_uv_b )
899       CALL rrd_mpi_io( 'bc_uv_t', bc_uv_t )
900       CALL rrd_mpi_io( 'biometeorology', biometeorology )
901       CALL rrd_mpi_io( 'building_height', building_height )
902       CALL rrd_mpi_io( 'building_length_x', building_length_x )
903       CALL rrd_mpi_io( 'building_length_y', building_length_y )
904       CALL rrd_mpi_io( 'building_wall_left', building_wall_left )
905       CALL rrd_mpi_io( 'building_wall_south', building_wall_south )
906       CALL rrd_mpi_io( 'bulk_cloud_model', bulk_cloud_model )
907       CALL rrd_mpi_io( 'call_psolver_at_all_substeps', call_psolver_at_all_substeps )
908       CALL rrd_mpi_io( 'canyon_height', canyon_height )
909       CALL rrd_mpi_io( 'canyon_wall_left', canyon_wall_left )
910       CALL rrd_mpi_io( 'canyon_wall_south', canyon_wall_south )
911       CALL rrd_mpi_io( 'canyon_width_x',  canyon_width_x )
912       CALL rrd_mpi_io( 'canyon_width_y', canyon_width_y )
913       CALL rrd_mpi_io( 'cfl_factor', cfl_factor )
914       CALL rrd_mpi_io( 'cloud_droplets',  cloud_droplets )
915       CALL rrd_mpi_io( 'collective_wait', collective_wait )
916       CALL rrd_mpi_io( 'conserve_volume_flow', conserve_volume_flow )
917       CALL rrd_mpi_io( 'conserve_volume_flow_mode', conserve_volume_flow_mode )
918       CALL rrd_mpi_io( 'constant_flux_layer', constant_flux_layer )
919       CALL rrd_mpi_io( 'coupling_start_time', coupling_start_time )
920       CALL rrd_mpi_io( 'current_timestep_number', current_timestep_number )
921       CALL rrd_mpi_io( 'cycle_mg', cycle_mg )
922       CALL rrd_mpi_io( 'damp_level_1d', damp_level_1d )
923       CALL rrd_mpi_io( 'dissipation_1d', dissipation_1d )
924       CALL rrd_mpi_io_global_array( 'do2d_xy_time_count', do2d_xy_time_count )
925       CALL rrd_mpi_io_global_array( 'do2d_xz_time_count', do2d_xz_time_count )
926       CALL rrd_mpi_io_global_array( 'do2d_yz_time_count', do2d_yz_time_count )
927       CALL rrd_mpi_io_global_array( 'do3d_time_count', do3d_time_count )
928       CALL rrd_mpi_io( 'dp_external', dp_external )
929       CALL rrd_mpi_io( 'dp_level_b', dp_level_b )
930       CALL rrd_mpi_io( 'dp_smooth', dp_smooth )
931       CALL rrd_mpi_io_global_array( 'dpdxy', dpdxy )
932       CALL rrd_mpi_io( 'dt_3d', dt_3d )
933       CALL rrd_mpi_io( 'dt_pr_1d', dt_pr_1d )
934       CALL rrd_mpi_io( 'dt_run_control_1d', dt_run_control_1d )
935       CALL rrd_mpi_io( 'dx', dx )
936       CALL rrd_mpi_io( 'dy', dy )
937       CALL rrd_mpi_io_global_array( 'dz', dz )
938       CALL rrd_mpi_io( 'dz_max', dz_max )
939       CALL rrd_mpi_io( 'dz_stretch_factor', dz_stretch_factor )
940       CALL rrd_mpi_io_global_array( 'dz_stretch_factor_array', dz_stretch_factor_array )
941       CALL rrd_mpi_io( 'dz_stretch_level', dz_stretch_level )
942       CALL rrd_mpi_io_global_array( 'dz_stretch_level_end', dz_stretch_level_end )
943       CALL rrd_mpi_io_global_array( 'dz_stretch_level_start', dz_stretch_level_start )
944       CALL rrd_mpi_io( 'e_min', e_min )
945       CALL rrd_mpi_io( 'end_time_1d', end_time_1d )
946       CALL rrd_mpi_io( 'fft_method', fft_method )
947       CALL rrd_mpi_io( 'first_call_lpm', first_call_lpm )
948       CALL rrd_mpi_io( 'galilei_transformation', galilei_transformation )
949       CALL rrd_mpi_io( 'gust_module_enabled', gust_module_enabled )
950       CALL rrd_mpi_io_global_array( 'hom', hom )
951       CALL rrd_mpi_io_global_array( 'hom_sum', hom_sum )
952       CALL rrd_mpi_io( 'humidity', humidity )
953       CALL rd_mpi_io_check_array( 'inflow_damping_factor', found = array_found )
954       IF ( array_found )  THEN
955           IF ( .NOT. ALLOCATED( inflow_damping_factor ) )  THEN
956               ALLOCATE( inflow_damping_factor(0:nz+1) )
957           ENDIF
958           CALL rrd_mpi_io_global_array( 'inflow_damping_factor', inflow_damping_factor )
959       ENDIF
960       CALL rrd_mpi_io( 'inflow_damping_height', inflow_damping_height )
961       CALL rrd_mpi_io( 'inflow_damping_width', inflow_damping_width )
962       CALL rrd_mpi_io( 'inflow_disturbance_begin', inflow_disturbance_begin )
963       CALL rrd_mpi_io( 'inflow_disturbance_end', inflow_disturbance_end )
964       CALL rrd_mpi_io( 'km_constant', km_constant )
965       CALL rrd_mpi_io( 'large_scale_forcing', large_scale_forcing )
966       CALL rrd_mpi_io( 'large_scale_subsidence', large_scale_subsidence )
967       CALL rrd_mpi_io( 'latitude', latitude )
968       CALL rrd_mpi_io( 'longitude', longitude )
969       CALL rrd_mpi_io( 'loop_optimization', loop_optimization )
970       CALL rrd_mpi_io( 'masking_method', masking_method )
971       CALL rd_mpi_io_check_array( 'mean_inflow_profiles', found = array_found )
972       IF ( array_found)  THEN
973          IF ( .NOT. ALLOCATED( mean_inflow_profiles ) )  THEN
974             ALLOCATE( mean_inflow_profiles(0:nz+1,7) )
975          ENDIF
976          CALL rrd_mpi_io_global_array( 'mean_inflow_profiles', mean_inflow_profiles )
977       ENDIF
978       CALL rrd_mpi_io( 'mg_cycles', mg_cycles )
979       CALL rrd_mpi_io( 'mg_switch_to_pe0_level', mg_switch_to_pe0_level )
980       CALL rrd_mpi_io( 'mixing_length_1d', mixing_length_1d )
981       CALL rrd_mpi_io( 'momentum_advec', momentum_advec )
982!
983!--    There is no module procedure for CHARACTER arrays
984       DO  i = 1, SIZE( netcdf_precision , 1 )
985          WRITE( tmp_name, '(A,I2.2)' )  'netcdf_precision_', i
986          CALL rrd_mpi_io( TRIM( tmp_name ), netcdf_precision(i) )
987       ENDDO
988       CALL rrd_mpi_io( 'neutral', neutral )
989       CALL rrd_mpi_io( 'ngsrb', ngsrb )
990       CALL rrd_mpi_io( 'nsor', nsor )
991       CALL rrd_mpi_io( 'nsor_ini', nsor_ini )
992       CALL rrd_mpi_io( 'nudging', nudging )
993       CALL rrd_mpi_io( 'num_leg', num_leg )
994       CALL rrd_mpi_io( 'nx', nx )
995       nx_on_file = nx
996       CALL rrd_mpi_io( 'ny', ny )
997       ny_on_file = ny
998       CALL rrd_mpi_io( 'ocean_mode', ocean_mode )
999       CALL rrd_mpi_io( 'omega', omega )
1000       CALL rrd_mpi_io( 'omega_sor', omega_sor )
1001       CALL rrd_mpi_io( 'origin_data_time', origin_date_time )
1002       CALL rrd_mpi_io( 'output_for_t0', output_for_t0 )
1003       CALL rrd_mpi_io( 'particle_advection', particle_advection )
1004       CALL rrd_mpi_io( 'passive_scalar', passive_scalar )
1005       CALL rrd_mpi_io( 'prandtl_number', prandtl_number )
1006       CALL rrd_mpi_io( 'psolver', psolver )
1007       CALL rrd_mpi_io( 'pt_damping_factor', pt_damping_factor )
1008       CALL rrd_mpi_io( 'pt_damping_width', pt_damping_width )
1009       CALL rrd_mpi_io_global_array( 'pt_init', pt_init )
1010       CALL rrd_mpi_io( 'pt_reference', pt_reference )
1011       CALL rrd_mpi_io( 'pt_surface', pt_surface )
1012       CALL rrd_mpi_io( 'pt_surface_initial_change', pt_surface_initial_change )
1013       CALL rrd_mpi_io_global_array( 'pt_vertical_gradient', pt_vertical_gradient )
1014       CALL rrd_mpi_io_global_array( 'pt_vertical_gradient_level', pt_vertical_gradient_level )
1015       CALL rrd_mpi_io_global_array( 'pt_vertical_gradient_level_ind', pt_vertical_gradient_level_ind )
1016       CALL rrd_mpi_io_global_array( 'q_init', q_init )
1017       CALL rrd_mpi_io( 'q_surface', q_surface )
1018       CALL rrd_mpi_io( 'q_surface_initial_change', q_surface_initial_change )
1019       CALL rrd_mpi_io_global_array( 'q_vertical_gradient', q_vertical_gradient )
1020       CALL rrd_mpi_io_global_array( 'q_vertical_gradient_level', q_vertical_gradient_level )
1021       CALL rrd_mpi_io_global_array( 'q_vertical_gradient_level_ind', q_vertical_gradient_level_ind )
1022       CALL rrd_mpi_io( 'random_generator', random_generator )
1023       CALL rrd_mpi_io( 'random_heatflux', random_heatflux )
1024       CALL rrd_mpi_io( 'rans_mode', rans_mode )
1025       CALL rrd_mpi_io( 'rayleigh_damping_factor', rayleigh_damping_factor )
1026       CALL rrd_mpi_io( 'rayleigh_damping_height', rayleigh_damping_height )
1027       CALL rrd_mpi_io( 'recycling_width', recycling_width )
1028       CALL rrd_mpi_io_global_array( 'ref_state', ref_state )
1029       CALL rrd_mpi_io( 'reference_state', reference_state )
1030       CALL rrd_mpi_io( 'residual_limit', residual_limit )
1031       CALL rrd_mpi_io( 'roughness_length', roughness_length )
1032       CALL rrd_mpi_io( 'run_coupled', run_coupled )
1033       CALL rrd_mpi_io( 'runnr', runnr )
1034       CALL rrd_mpi_io_global_array( 's_init', s_init )
1035       CALL rrd_mpi_io( 's_surface', s_surface )
1036       CALL rrd_mpi_io( 's_surface_initial_change', s_surface_initial_change )
1037       CALL rrd_mpi_io_global_array( 's_vertical_gradient', s_vertical_gradient )
1038       CALL rrd_mpi_io_global_array( 's_vertical_gradient_level', s_vertical_gradient_level )
1039       CALL rrd_mpi_io_global_array( 's_vertical_gradient_level_ind', s_vertical_gradient_level_ind )
1040       CALL rrd_mpi_io( 'scalar_advec', scalar_advec )
1041       CALL rrd_mpi_io( 'simulated_time', simulated_time )
1042       CALL rd_mpi_io_check_array( 'spectrum_x', found = array_found )
1043       IF (array_found )  THEN
1044           IF ( .NOT. ALLOCATED( spectrum_x ) )  THEN
1045              ALLOCATE( spectrum_x( 1:nx/2, 1:100, 1:10 ) )
1046           ENDIF
1047           CALL rrd_mpi_io( 'spectrum_y', spectrum_y )
1048       ENDIF
1049       CALL rd_mpi_io_check_array( 'spectrum_y', found = array_found )
1050       IF ( array_found )  THEN
1051           IF ( .NOT. ALLOCATED( spectrum_y ) )  THEN
1052              ALLOCATE( spectrum_y( 1:ny/2, 1:100, 1:10 ) )
1053           ENDIF
1054           CALL rrd_mpi_io( 'spectrum_y', spectrum_y )
1055       ENDIF
1056       CALL rrd_mpi_io( 'spinup_time ', spinup_time )
1057       CALL rrd_mpi_io_global_array( 'subs_vertical_gradient', subs_vertical_gradient )
1058       CALL rrd_mpi_io_global_array( 'subs_vertical_gradient_level', subs_vertical_gradient_level )
1059       CALL rrd_mpi_io_global_array( 'subs_vertical_gradient_level_i', subs_vertical_gradient_level_i )
1060       CALL rrd_mpi_io( 'surface_heatflux', surface_heatflux )
1061       CALL rrd_mpi_io( 'surface_pressure', surface_pressure )
1062       CALL rrd_mpi_io( 'surface_output', surface_output )
1063       CALL rrd_mpi_io( 'surface_scalarflux', surface_scalarflux )
1064       CALL rrd_mpi_io( 'surface_waterflux', surface_waterflux )
1065       CALL rrd_mpi_io( 'syn_turb_gen', syn_turb_gen )
1066       CALL rrd_mpi_io( 'time_coupling', time_coupling )
1067       CALL rrd_mpi_io( 'time_disturb', time_disturb )
1068       CALL rrd_mpi_io( 'time_do2d_xy', time_do2d_xy )
1069       CALL rrd_mpi_io( 'time_do2d_xz', time_do2d_xz )
1070       CALL rrd_mpi_io( 'time_do2d_yz', time_do2d_yz )
1071       CALL rrd_mpi_io( 'time_do3d', time_do3d )
1072       CALL rrd_mpi_io( 'time_do_av', time_do_av )
1073       CALL rrd_mpi_io( 'time_do_sla', time_do_sla )
1074       CALL rrd_mpi_io_global_array( 'time_domask', time_domask )
1075       CALL rrd_mpi_io( 'time_dopr', time_dopr )
1076       CALL rrd_mpi_io( 'time_dopr_av', time_dopr_av )
1077       CALL rrd_mpi_io( 'time_dopr_listing', time_dopr_listing )
1078       CALL rrd_mpi_io( 'time_dopts', time_dopts )
1079       CALL rrd_mpi_io( 'time_dosp', time_dosp )
1080       CALL rrd_mpi_io( 'time_dots', time_dots )
1081       CALL rrd_mpi_io( 'time_radiation', time_radiation )
1082       CALL rrd_mpi_io( 'time_restart', time_restart )
1083       CALL rrd_mpi_io( 'time_run_control', time_run_control )
1084       CALL rrd_mpi_io( 'time_since_reference_point', time_since_reference_point )
1085       CALL rrd_mpi_io( 'time_virtual_measurement', time_virtual_measurement )
1086       CALL rrd_mpi_io( 'timestep_scheme', timestep_scheme )
1087       CALL rrd_mpi_io( 'top_heatflux', top_heatflux )
1088       CALL rrd_mpi_io( 'top_momentumflux_u', top_momentumflux_u )
1089       CALL rrd_mpi_io( 'top_momentumflux_v', top_momentumflux_v )
1090       CALL rrd_mpi_io( 'top_scalarflux', top_scalarflux )
1091       CALL rrd_mpi_io( 'topography', topography )
1092       CALL rrd_mpi_io( 'topography_grid_convention', topography_grid_convention )
1093       CALL rrd_mpi_io_global_array( 'tsc', tsc )
1094       CALL rrd_mpi_io( 'tunnel_height', tunnel_height )
1095       CALL rrd_mpi_io( 'tunnel_length', tunnel_length )
1096       CALL rrd_mpi_io( 'tunnel_wall_depth', tunnel_wall_depth )
1097       CALL rrd_mpi_io( 'tunnel_width_x', tunnel_width_x )
1098       CALL rrd_mpi_io( 'tunnel_width_y', tunnel_width_y )
1099       CALL rrd_mpi_io( 'turbulence_closure', turbulence_closure )
1100       CALL rrd_mpi_io( 'turbulent_inflow', turbulent_inflow )
1101       CALL rrd_mpi_io( 'u_bulk', u_bulk )
1102       CALL rrd_mpi_io_global_array( 'u_init', u_init )
1103       CALL rrd_mpi_io( 'u_max', u_max )
1104       CALL rrd_mpi_io_global_array( 'u_max_ijk', u_max_ijk )
1105       CALL rrd_mpi_io_global_array( 'ug', ug )
1106       CALL rrd_mpi_io( 'ug_surface', ug_surface )
1107       CALL rrd_mpi_io_global_array( 'ug_vertical_gradient', ug_vertical_gradient )
1108       CALL rrd_mpi_io_global_array( 'ug_vertical_gradient_level', ug_vertical_gradient_level )
1109       CALL rrd_mpi_io_global_array( 'ug_vertical_gradient_level_ind', ug_vertical_gradient_level_ind )
1110       CALL rrd_mpi_io( 'use_surface_fluxes', use_surface_fluxes )
1111       CALL rrd_mpi_io( 'use_top_fluxes', use_top_fluxes )
1112       CALL rrd_mpi_io( 'use_ug_for_galilei_tr', use_ug_for_galilei_tr )
1113       CALL rrd_mpi_io( 'use_upstream_for_tke', use_upstream_for_tke )
1114       CALL rrd_mpi_io( 'user_module_enabled', user_module_enabled )
1115       CALL rrd_mpi_io( 'v_bulk', v_bulk )
1116       CALL rrd_mpi_io_global_array( 'v_init', v_init )
1117       CALL rrd_mpi_io( 'v_max', v_max )
1118       CALL rrd_mpi_io_global_array( 'v_max_ijk', v_max_ijk )
1119       CALL rrd_mpi_io_global_array( 'vg', vg )
1120       CALL rrd_mpi_io( 'vg_surface', vg_surface )
1121       CALL rrd_mpi_io_global_array( 'vg_vertical_gradient', vg_vertical_gradient )
1122       CALL rrd_mpi_io_global_array( 'vg_vertical_gradient_level', vg_vertical_gradient_level )
1123       CALL rrd_mpi_io_global_array( 'vg_vertical_gradient_level_ind', vg_vertical_gradient_level_ind )
1124       CALL rrd_mpi_io( 'virtual_flight', virtual_flight )
1125       CALL rrd_mpi_io( 'vnest_init', vnest_init )
1126       CALL rrd_mpi_io_global_array( 'volume_flow_area', volume_flow_area )
1127       CALL rrd_mpi_io_global_array( 'volume_flow_initial', volume_flow_initial )
1128       CALL rrd_mpi_io( 'w_max', w_max )
1129       CALL rrd_mpi_io_global_array( 'w_max_ijk', w_max_ijk )
1130       CALL rrd_mpi_io( 'wall_adjustment', wall_adjustment )
1131       CALL rrd_mpi_io_global_array( 'wall_heatflux', wall_heatflux )
1132       CALL rrd_mpi_io_global_array( 'wall_humidityflux', wall_humidityflux )
1133       CALL rrd_mpi_io_global_array( 'wall_scalarflux', wall_scalarflux )
1134       CALL rrd_mpi_io( 'y_shift', y_shift )
1135       CALL rrd_mpi_io( 'z0h_factor', z0h_factor )
1136       CALL rrd_mpi_io( 'zeta_max', zeta_max )
1137       CALL rrd_mpi_io( 'zeta_min', zeta_min )
1138       CALL rrd_mpi_io_global_array( 'z_i', z_i )
1139
1140!
1141!--    Read global variables from of other modules
1142       CALL module_interface_rrd_global
1143
1144!
1145!--    Close restart file
1146       CALL rd_mpi_io_close
1147
1148    ENDIF
1149
1150    CALL location_message( 'read global restart data', 'finished' )
1151
1152 END SUBROUTINE rrd_global
1153
1154
1155
1156!------------------------------------------------------------------------------!
1157! Description:
1158! ------------
1159!> Skipping the global control variables from restart-file (binary format)
1160!> except some information needed when reading restart data from a previous
1161!> run which used a smaller total domain or/and a different domain decomposition
1162!> (initializing_actions  == 'cyclic_fill').
1163!------------------------------------------------------------------------------!
1164
1165    SUBROUTINE rrd_read_parts_of_global
1166
1167
1168       CHARACTER (LEN=10) ::  version_on_file
1169       CHARACTER (LEN=20) ::  momentum_advec_check
1170       CHARACTER (LEN=20) ::  scalar_advec_check
1171       CHARACTER (LEN=1)  ::  cdum
1172
1173       INTEGER(iwp) ::  max_pr_user_on_file
1174       INTEGER(iwp) ::  nz_on_file
1175       INTEGER(iwp) ::  statistic_regions_on_file
1176       INTEGER(iwp) ::  tmp_mpru
1177       INTEGER(iwp) ::  tmp_sr
1178
1179       REAL(wp), DIMENSION(:,:,:),   ALLOCATABLE ::  hom_sum_on_file
1180       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  hom_on_file
1181
1182
1183       CALL check_open( 13 )
1184
1185       READ ( 13 )  length
1186       READ ( 13 )  restart_string(1:length)
1187       READ ( 13 )  version_on_file
1188
1189!
1190!-- Read number of PEs and horizontal index bounds of all PEs used in previous
1191!-- run
1192       READ ( 13 )  length
1193       READ ( 13 )  restart_string(1:length)
1194
1195       IF ( restart_string(1:length) /= 'numprocs' )  THEN
1196          WRITE( message_string, * ) 'numprocs not found in data from prior ', &
1197                                     'run on PE ', myid
1198          CALL message( 'rrd_read_parts_of_global', 'PA0297', 1, 2, 0, 6, 0 )
1199       ENDIF
1200       READ ( 13 )  numprocs_previous_run
1201
1202       IF ( .NOT. ALLOCATED( hor_index_bounds_previous_run ) )  THEN
1203          ALLOCATE( hor_index_bounds_previous_run(4,0:numprocs_previous_run-1) )
1204       ENDIF
1205
1206       READ ( 13 )  length
1207       READ ( 13 )  restart_string(1:length)
1208
1209       IF ( restart_string(1:length) /= 'hor_index_bounds' )  THEN
1210          WRITE( message_string, * ) 'hor_index_bounds not found in data ',    &
1211                                     'from prior run on PE ', myid
1212          CALL message( 'rrd_read_parts_of_global', 'PA0298', 1, 2, 0, 6, 0 )
1213       ENDIF
1214       READ ( 13 )  hor_index_bounds_previous_run
1215
1216!
1217!-- Read vertical number of gridpoints and number of different areas used
1218!-- for computing statistics. Allocate arrays depending on these values,
1219!-- which are needed for the following read instructions.
1220       READ ( 13 )  length
1221       READ ( 13 )  restart_string(1:length)
1222
1223       IF ( restart_string(1:length) /= 'nz' )  THEN
1224          message_string = 'nz not found in restart data file'
1225          CALL message( 'rrd_read_parts_of_global', 'PA0303', 1, 2, 0, 6, 0 )
1226       ENDIF
1227       READ ( 13 )  nz_on_file
1228       IF ( nz_on_file /= nz )  THEN
1229          WRITE( message_string, * ) 'mismatch concerning number of ',         &
1230                                     'gridpoints along z:',                    &
1231                                     '&nz on file    = "', nz_on_file, '"',    &
1232                                     '&nz from run   = "', nz, '"'
1233          CALL message( 'rrd_read_parts_of_global', 'PA0304', 1, 2, 0, 6, 0 )
1234       ENDIF
1235
1236       READ ( 13 )  length
1237       READ ( 13 )  restart_string(1:length)
1238
1239       IF ( restart_string(1:length) /= 'max_pr_user' )  THEN
1240          message_string = 'max_pr_user not found in restart data file'
1241          CALL message( 'rrd_read_parts_of_global', 'PA0305', 1, 2, 0, 6, 0 )
1242       ENDIF
1243       READ ( 13 )  max_pr_user_on_file
1244       IF ( max_pr_user_on_file /= max_pr_user )  THEN
1245          WRITE( message_string, * ) 'number of user profiles on res',         &
1246                                     'tart data file differs from the ',       &
1247                                     'current run:&max_pr_user on file    = "',&
1248                                     max_pr_user_on_file, '"',                 &
1249                                     '&max_pr_user from run   = "',            &
1250                                     max_pr_user, '"'
1251          CALL message( 'rrd_read_parts_of_global', 'PA0306', 0, 0, 0, 6, 0 )
1252          tmp_mpru = MIN( max_pr_user_on_file, max_pr_user )
1253       ELSE
1254          tmp_mpru = max_pr_user
1255       ENDIF
1256
1257       READ ( 13 )  length
1258       READ ( 13 )  restart_string(1:length)
1259
1260       IF ( restart_string(1:length) /= 'statistic_regions' )  THEN
1261          message_string = 'statistic_regions not found in restart data file'
1262          CALL message( 'rrd_read_parts_of_global', 'PA0307', 1, 2, 0, 6, 0 )
1263       ENDIF
1264       READ ( 13 )  statistic_regions_on_file
1265       IF ( statistic_regions_on_file /= statistic_regions )  THEN
1266          WRITE( message_string, * ) 'statistic regions on restart data file ',&
1267                                     'differ from the current run:',           &
1268                                     '&statistic regions on file    = "',      &
1269                                     statistic_regions_on_file, '"',           &
1270                                     '&statistic regions from run   = "',      &
1271                                      statistic_regions, '"',                  &
1272                                     '&statistic data may be lost!'
1273          CALL message( 'rrd_read_parts_of_global', 'PA0308', 0, 1, 0, 6, 0 )
1274          tmp_sr = MIN( statistic_regions_on_file, statistic_regions )
1275       ELSE
1276          tmp_sr = statistic_regions
1277       ENDIF
1278
1279!
1280!-- Now read and check some control parameters and skip the rest
1281       READ ( 13 )  length
1282       READ ( 13 )  restart_string(1:length)
1283
1284       DO  WHILE ( restart_string(1:length) /= 'binary_version_local' )
1285
1286          SELECT CASE ( restart_string(1:length) )
1287
1288             CASE ( 'average_count_pr' )
1289                READ ( 13 )  average_count_pr
1290                IF ( average_count_pr /= 0 )  THEN
1291                   WRITE( message_string, * ) 'inflow profiles not ',          &
1292                                  'temporally averaged. &Averaging will be ',  &
1293                                  'done now using', average_count_pr,          &
1294                                  ' samples.'
1295                   CALL message( 'rrd_read_parts_of_global', 'PA0309',         &
1296                                 0, 1, 0, 6, 0 )
1297                ENDIF
1298
1299             CASE ( 'hom' )
1300                ALLOCATE( hom_on_file(0:nz+1,2,pr_palm+max_pr_user_on_file,    &
1301                          0:statistic_regions_on_file) )
1302                READ ( 13 )  hom_on_file
1303                hom(:,:,1:pr_palm+tmp_mpru,0:tmp_sr) =                         &
1304                             hom_on_file(:,:,1:pr_palm+tmp_mpru,0:tmp_sr)
1305                DEALLOCATE( hom_on_file )
1306
1307             CASE ( 'hom_sum' )
1308                ALLOCATE( hom_sum_on_file(0:nz+1,pr_palm+max_pr_user_on_file,  &
1309                          0:statistic_regions_on_file) )
1310                READ ( 13 )  hom_sum_on_file
1311                hom_sum(:,1:pr_palm+tmp_mpru,0:tmp_sr) =                       &
1312                             hom_sum_on_file(:,1:pr_palm+tmp_mpru,0:tmp_sr)
1313                DEALLOCATE( hom_sum_on_file )
1314
1315             CASE ( 'momentum_advec' )
1316                momentum_advec_check = momentum_advec
1317                READ ( 13 )  momentum_advec
1318                IF ( TRIM( momentum_advec_check ) /= TRIM( momentum_advec ) )  &
1319                THEN
1320                   WRITE( message_string, * ) 'momentum_advec of the restart ',&
1321                                  'run differs from momentum_advec of the ',   &
1322                                  'initial run.'
1323                   CALL message( 'rrd_read_parts_of_global', 'PA0100',         &
1324                                 1, 2, 0, 6, 0 )
1325                ENDIF
1326
1327             CASE ( 'nx' )
1328                READ ( 13 )  nx_on_file
1329
1330             CASE ( 'ny' )
1331                READ ( 13 )  ny_on_file
1332
1333             CASE ( 'ref_state' )
1334                READ ( 13 )  ref_state
1335
1336             CASE ( 'scalar_advec' )
1337                scalar_advec_check = scalar_advec
1338                READ ( 13 )  scalar_advec
1339                IF ( TRIM( scalar_advec_check ) /= TRIM( scalar_advec ) )      &
1340                THEN
1341                   WRITE( message_string, * ) 'scalar_advec of the restart ',  &
1342                                  'run differs from scalar_advec of the ',     &
1343                                  'initial run.'
1344                   CALL message( 'rrd_read_parts_of_global', 'PA0101',         &
1345                                 1, 2, 0, 6, 0 )
1346                ENDIF
1347
1348             CASE DEFAULT
1349
1350                READ ( 13 )  cdum
1351
1352          END SELECT
1353
1354          READ ( 13 )  length
1355          READ ( 13 )  restart_string(1:length)
1356
1357       ENDDO
1358
1359!
1360!-- Calculate the temporal average of vertical profiles, if neccessary
1361    IF ( average_count_pr /= 0 )  THEN
1362       hom_sum = hom_sum / REAL( average_count_pr, KIND=wp )
1363    ENDIF
1364
1365
1366    CALL close_file( 13 )
1367
1368
1369    END SUBROUTINE rrd_read_parts_of_global
1370
1371
1372! Description:
1373! ------------
1374!> Reads processor (subdomain) specific data of variables and arrays from restart file
1375!> (binary format).
1376!------------------------------------------------------------------------------!
1377 SUBROUTINE rrd_local
1378
1379
1380    CHARACTER (LEN=7)  ::  myid_char_save
1381    CHARACTER (LEN=10) ::  binary_version_local
1382    CHARACTER (LEN=10) ::  version_on_file
1383    CHARACTER (LEN=20) ::  tmp_name               !< temporary variable
1384
1385    INTEGER(iwp) ::  files_to_be_opened  !<
1386    INTEGER(iwp) ::  i                   !<
1387    INTEGER(iwp) ::  j                   !<
1388    INTEGER(iwp) ::  k                   !<
1389    INTEGER(iwp) ::  myid_on_file        !<
1390    INTEGER(iwp) ::  numprocs_on_file    !<
1391    INTEGER(iwp) ::  nxlc                !<
1392    INTEGER(iwp) ::  nxlf                !<
1393    INTEGER(iwp) ::  nxlpr               !<
1394    INTEGER(iwp) ::  nxl_on_file         !<
1395    INTEGER(iwp) ::  nxrc                !<
1396    INTEGER(iwp) ::  nxrf                !<
1397    INTEGER(iwp) ::  nxrpr               !<
1398    INTEGER(iwp) ::  nxr_on_file         !<
1399    INTEGER(iwp) ::  nync                !<
1400    INTEGER(iwp) ::  nynf                !<
1401    INTEGER(iwp) ::  nynpr               !<
1402    INTEGER(iwp) ::  nyn_on_file         !<
1403    INTEGER(iwp) ::  nysc                !<
1404    INTEGER(iwp) ::  nysf                !<
1405    INTEGER(iwp) ::  nyspr               !<
1406    INTEGER(iwp) ::  nys_on_file         !<
1407    INTEGER(iwp) ::  nzb_on_file         !<
1408    INTEGER(iwp) ::  nzt_on_file         !<
1409    INTEGER(iwp) ::  offset_x            !<
1410    INTEGER(iwp) ::  offset_y            !<
1411    INTEGER(iwp) ::  shift_x             !<
1412    INTEGER(iwp) ::  shift_y             !<
1413
1414    INTEGER(iwp), DIMENSION(numprocs_previous_run) ::  file_list       !<
1415    INTEGER(iwp), DIMENSION(numprocs_previous_run) ::  overlap_count   !<
1416
1417    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nxlfa      !<
1418    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nxrfa      !<
1419    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nynfa      !<
1420    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nysfa      !<
1421    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  offset_xa  !<
1422    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  offset_ya  !<
1423
1424    INTEGER(isp), DIMENSION(:,:),   ALLOCATABLE ::  tmp_2d_id_random   !< temporary array for storing random generator data
1425    INTEGER(isp), DIMENSION(:,:,:), ALLOCATABLE ::  tmp_2d_seq_random  !< temporary array for storing random generator data
1426
1427    LOGICAL ::  array_found                      !<
1428    LOGICAL ::  found                            !<
1429
1430    REAL(wp), DIMENSION(:,:),   ALLOCATABLE   ::  tmp_2d         !< temporary array for storing 2D data
1431    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3d         !< temporary array for storing 3D data
1432    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3d_non_standard !< temporary array for storing 3D data
1433                                                                 !< with non standard dimensions
1434
1435!
1436!-- Read data from previous model run.
1437    CALL cpu_log( log_point_s(14), 'rrd_local', 'start' )
1438
1439    IF ( TRIM( restart_data_format_input ) == 'fortran_binary' )  THEN
1440!
1441!--    Input in Fortran binary format
1442
1443!
1444!--    Allocate temporary buffer arrays. In previous versions, there were
1445!--    declared as automated arrays, causing memory problems when these
1446!--    were allocate on stack.
1447       ALLOCATE( nxlfa(numprocs_previous_run,1000) )
1448       ALLOCATE( nxrfa(numprocs_previous_run,1000) )
1449       ALLOCATE( nynfa(numprocs_previous_run,1000) )
1450       ALLOCATE( nysfa(numprocs_previous_run,1000) )
1451       ALLOCATE( offset_xa(numprocs_previous_run,1000) )
1452       ALLOCATE( offset_ya(numprocs_previous_run,1000) )
1453
1454!
1455!--    Check which of the restart files contain data needed for the subdomain
1456!--    of this PE
1457       files_to_be_opened = 0
1458
1459       DO  i = 1, numprocs_previous_run
1460!
1461!--       Store array bounds of the previous run ("pr") in temporary scalars
1462          nxlpr = hor_index_bounds_previous_run(1,i-1)
1463          nxrpr = hor_index_bounds_previous_run(2,i-1)
1464          nyspr = hor_index_bounds_previous_run(3,i-1)
1465          nynpr = hor_index_bounds_previous_run(4,i-1)
1466
1467!
1468!--       Determine the offsets. They may be non-zero in case that the total domain
1469!--       on file is smaller than the current total domain.
1470          offset_x = ( nxl / ( nx_on_file + 1 ) ) * ( nx_on_file + 1 )
1471          offset_y = ( nys / ( ny_on_file + 1 ) ) * ( ny_on_file + 1 )
1472
1473!
1474!--       Start with this offset and then check, if the subdomain on file
1475!--       matches another time(s) in the current subdomain by shifting it
1476!--       for nx_on_file+1, ny_on_file+1 respectively
1477
1478          shift_y = 0
1479          j       = 0
1480          DO WHILE (  nyspr+shift_y <= nyn-offset_y )
1481
1482             IF ( nynpr+shift_y >= nys-offset_y ) THEN
1483
1484                shift_x = 0
1485                DO WHILE ( nxlpr+shift_x <= nxr-offset_x )
1486
1487                   IF ( nxrpr+shift_x >= nxl-offset_x ) THEN
1488                      j = j +1
1489                      IF ( j > 1000 )  THEN
1490!
1491!--                      Array bound exceeded
1492                         message_string = 'data from subdomain of previous' //                        &
1493                                          ' run mapped more than 1000 times'
1494                         CALL message( 'rrd_local', 'PA0284', 2, 2, -1, 6, 1 )
1495                      ENDIF
1496
1497                      IF ( j == 1 )  THEN
1498                         files_to_be_opened = files_to_be_opened + 1
1499                         file_list(files_to_be_opened) = i-1
1500                      ENDIF
1501
1502                      offset_xa(files_to_be_opened,j) = offset_x + shift_x
1503                      offset_ya(files_to_be_opened,j) = offset_y + shift_y
1504!
1505!--                   Index bounds of overlapping data
1506                      nxlfa(files_to_be_opened,j) = MAX( nxl-offset_x-shift_x, nxlpr )
1507                      nxrfa(files_to_be_opened,j) = MIN( nxr-offset_x-shift_x, nxrpr )
1508                      nysfa(files_to_be_opened,j) = MAX( nys-offset_y-shift_y, nyspr )
1509                      nynfa(files_to_be_opened,j) = MIN( nyn-offset_y-shift_y, nynpr )
1510
1511                   ENDIF
1512
1513                   shift_x = shift_x + ( nx_on_file + 1 )
1514                ENDDO
1515
1516             ENDIF
1517
1518             shift_y = shift_y + ( ny_on_file + 1 )
1519          ENDDO
1520
1521          IF ( j > 0 )  overlap_count(files_to_be_opened) = j
1522
1523       ENDDO
1524
1525!
1526!--    Save the id-string of the current process, since myid_char may now be used
1527!--    to open files created by PEs with other id.
1528       myid_char_save = myid_char
1529
1530       IF ( files_to_be_opened /= 1  .OR.  numprocs /= numprocs_previous_run )  THEN
1531          WRITE( message_string, * ) 'number of PEs or virtual PE-grid changed in restart run. & ',   &
1532                                     'Set debug_output =.T. to get a list of files from which the & ',&
1533                                     'single PEs will read respectively'
1534          CALL message( 'rrd_local', 'PA0285', 0, 0, 0, 6, 0 )
1535          IF ( debug_output )  THEN
1536             IF ( files_to_be_opened <= 120 )  THEN
1537                WRITE( debug_string, '(2A,1X,120(I6.6,1X))' )                                         &
1538                     'number of PEs or virtual PE-grid changed in restart run.  PE will read from ',  &
1539                     'files ', file_list(1:files_to_be_opened)
1540             ELSE
1541                WRITE( debug_string, '(3A,1X,120(I6.6,1X),A)' )                                      &
1542                     'number of PEs or virtual PE-grid changed in restart run.  PE will read from ',  &
1543                     'files ', file_list(1:120), '... and more'
1544             ENDIF
1545             CALL debug_message( 'rrd_local', 'info' )
1546          ENDIF
1547       ENDIF
1548
1549!
1550!--    Read data from all restart files determined above
1551       DO  i = 1, files_to_be_opened
1552
1553          j = file_list(i)
1554!
1555!--       Set the filename (underscore followed by four digit processor id)
1556          WRITE (myid_char,'(''_'',I6.6)')  j
1557
1558!
1559!--       Open the restart file. If this file has been created by PE0 (_000000),
1560!--       the global variables at the beginning of the file have to be skipped
1561!--       first.
1562          CALL check_open( 13 )
1563          IF ( j == 0 )  CALL rrd_skip_global
1564
1565!
1566!--       First compare the version numbers
1567          READ ( 13 )  length
1568          READ ( 13 )  restart_string(1:length)
1569          READ ( 13 )  version_on_file
1570
1571          binary_version_local = '4.7'
1572          IF ( TRIM( version_on_file ) /= TRIM( binary_version_local ) )  THEN
1573             WRITE( message_string, * ) 'version mismatch concerning ',                               &
1574                                        'binary_version_local:',                                      &
1575                                        '&version on file    = "', TRIM( version_on_file ), '"',      &
1576                                        '&version in program = "', TRIM( binary_version_local ), '"'
1577             CALL message( 'rrd_local', 'PA0286', 1, 2, 0, 6, 0 )
1578          ENDIF
1579
1580!
1581!--       Read number of processors, processor-id, and array ranges.
1582!--       Compare the array ranges with those stored in the index bound array.
1583          READ ( 13 )  numprocs_on_file, myid_on_file, nxl_on_file, nxr_on_file, nys_on_file,         &
1584                       nyn_on_file, nzb_on_file, nzt_on_file
1585
1586          IF ( nxl_on_file /= hor_index_bounds_previous_run(1,j) )  THEN
1587             WRITE( message_string, * ) 'problem with index bound nxl on ',                           &
1588                                        'restart file "', myid_char, '"',                             &
1589                                        '&nxl = ', nxl_on_file, ' but it should be',                  &
1590                                        '&= ', hor_index_bounds_previous_run(1,j),                    &
1591                                        '&from the index bound information array'
1592             CALL message( 'rrd_local', 'PA0287', 2, 2, -1, 6, 1 )
1593          ENDIF
1594
1595          IF ( nxr_on_file /= hor_index_bounds_previous_run(2,j) )  THEN
1596              WRITE( message_string, * ) 'problem with index bound nxr on ',                          &
1597                                         'restart file "', myid_char, '"'  ,                          &
1598                                         ' nxr = ', nxr_on_file, ' but it should be',                 &
1599                                         ' = ', hor_index_bounds_previous_run(2,j),                   &
1600                                         ' from the index bound information array'
1601             CALL message( 'rrd_local', 'PA0288', 2, 2, -1, 6, 1 )
1602
1603          ENDIF
1604
1605          IF ( nys_on_file /= hor_index_bounds_previous_run(3,j) )  THEN
1606             WRITE( message_string, * ) 'problem with index bound nys on ',                           &
1607                                        'restart file "', myid_char, '"',                             &
1608                                        '&nys = ', nys_on_file, ' but it should be',                  &
1609                                        '&= ', hor_index_bounds_previous_run(3,j),                    &
1610                                        '&from the index bound information array'
1611             CALL message( 'rrd_local', 'PA0289', 2, 2, -1, 6, 1 )
1612          ENDIF
1613
1614          IF ( nyn_on_file /= hor_index_bounds_previous_run(4,j) )  THEN
1615             WRITE( message_string, * ) 'problem with index bound nyn on ',                           &
1616                                        'restart file "', myid_char, '"',                             &
1617                                        '&nyn = ', nyn_on_file, ' but it should be',                  &
1618                                        '&= ', hor_index_bounds_previous_run(4,j),                    &
1619                                        '&from the index bound information array'
1620             CALL message( 'rrd_local', 'PA0290', 2, 2, -1, 6, 1 )
1621          ENDIF
1622
1623          IF ( nzb_on_file /= nzb )  THEN
1624             WRITE( message_string, * ) 'mismatch between actual data and data ',                     &
1625                                        'from prior run on PE ', myid,                                &
1626                                        '&nzb on file = ', nzb_on_file,                               &
1627                                        '&nzb         = ', nzb
1628             CALL message( 'rrd_local', 'PA0291', 1, 2, 0, 6, 0 )
1629          ENDIF
1630
1631          IF ( nzt_on_file /= nzt )  THEN
1632             WRITE( message_string, * ) 'mismatch between actual data and data ',                     &
1633                                        'from prior run on PE ', myid,                                &
1634                                        '&nzt on file = ', nzt_on_file,                               &
1635                                        '&nzt         = ', nzt
1636             CALL message( 'rrd_local', 'PA0292', 1, 2, 0, 6, 0 )
1637          ENDIF
1638
1639!
1640!--       Allocate temporary arrays sized as the arrays on the restart file
1641          ALLOCATE( tmp_2d(nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp),      &
1642                    tmp_3d(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,                               &
1643                           nxl_on_file-nbgp:nxr_on_file+nbgp) )
1644
1645!
1646!--       Read arrays
1647!--       ATTENTION: If the following read commands have been altered, the
1648!--       ---------- version number of the variable binary_version_local must
1649!--                  be altered, too. Furthermore, the output list of arrays in
1650!--                  wrd_write_local must also be altered
1651!--                  accordingly.
1652          READ ( 13 )  length
1653          READ ( 13 )  restart_string(1:length)
1654
1655
1656!
1657!--       Loop over processor specific field data
1658          DO  WHILE ( restart_string(1:length) /= '*** end ***' )
1659
1660!
1661!--          Map data on file as often as needed (data are read only for k=1)
1662             DO  k = 1, overlap_count(i)
1663
1664                found = .FALSE.
1665
1666!
1667!--             Get the index range of the subdomain on file which overlap with
1668!--             the current subdomain
1669                nxlf = nxlfa(i,k)
1670                nxlc = nxlfa(i,k) + offset_xa(i,k)
1671                nxrf = nxrfa(i,k)
1672                nxrc = nxrfa(i,k) + offset_xa(i,k)
1673                nysf = nysfa(i,k)
1674                nysc = nysfa(i,k) + offset_ya(i,k)
1675                nynf = nynfa(i,k)
1676                nync = nynfa(i,k) + offset_ya(i,k)
1677
1678
1679                SELECT CASE ( restart_string(1:length) )
1680
1681                   CASE ( 'ghf_av' )
1682                      IF ( .NOT. ALLOCATED( ghf_av ) )  THEN
1683                         ALLOCATE( ghf_av(nysg:nyng,nxlg:nxrg) )
1684                      ENDIF
1685                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1686                      ghf_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
1687                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1688
1689                   CASE ( 'e' )
1690                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1691                      e(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
1692                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1693
1694                   CASE ( 'e_av' )
1695                      IF ( .NOT. ALLOCATED( e_av ) )  THEN
1696                         ALLOCATE( e_av(nzb:nzt+1,nys-nbgp:nyn+nbgp,                                  &
1697                                        nxl-nbgp:nxr+nbgp) )
1698                      ENDIF
1699                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1700                      e_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
1701                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1702
1703                   CASE ( 'kh' )
1704                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1705                      kh(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                 &
1706                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1707
1708                   CASE ( 'kh_av' )
1709                      IF ( .NOT. ALLOCATED( kh_av ) )  THEN
1710                         ALLOCATE( kh_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
1711                      ENDIF
1712                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1713                      kh_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                              &
1714                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1715
1716                   CASE ( 'km' )
1717                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1718                      km(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                 &
1719                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1720
1721                   CASE ( 'km_av' )
1722                      IF ( .NOT. ALLOCATED( km_av ) )  THEN
1723                         ALLOCATE( km_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
1724                      ENDIF
1725                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1726                      km_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                              &
1727                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1728
1729                   CASE ( 'lpt_av' )
1730                      IF ( .NOT. ALLOCATED( lpt_av ) )  THEN
1731                         ALLOCATE( lpt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
1732                      ENDIF
1733                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1734                      lpt_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                             &
1735                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1736
1737                   CASE ( 'lwp_av' )
1738                      IF ( .NOT. ALLOCATED( lwp_av ) )  THEN
1739                         ALLOCATE( lwp_av(nysg:nyng,nxlg:nxrg) )
1740                      ENDIF
1741                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1742                      lwp_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
1743                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1744
1745                   CASE ( 'p' )
1746                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1747                      p(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
1748                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1749
1750                   CASE ( 'p_av' )
1751                      IF ( .NOT. ALLOCATED( p_av ) )  THEN
1752                         ALLOCATE( p_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1753                      ENDIF
1754                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1755                      p_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
1756                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1757
1758                   CASE ( 'pt' )
1759                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1760                      pt(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                 &
1761                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1762
1763                   CASE ( 'pt_av' )
1764                      IF ( .NOT. ALLOCATED( pt_av ) )  THEN
1765                         ALLOCATE( pt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1766                      ENDIF
1767                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1768                      pt_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                              &
1769                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1770
1771                   CASE ( 'q' )
1772                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1773                      q(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
1774                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1775
1776                   CASE ( 'q_av' )
1777                      IF ( .NOT. ALLOCATED( q_av ) )  THEN
1778                         ALLOCATE( q_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
1779                      ENDIF
1780                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1781                      q_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
1782                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1783
1784                   CASE ( 'ql' )
1785                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1786                      ql(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                 &
1787                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1788
1789                   CASE ( 'ql_av' )
1790                      IF ( .NOT. ALLOCATED( ql_av ) )  THEN
1791                         ALLOCATE( ql_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1792                      ENDIF
1793                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1794                      ql_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                              &
1795                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1796
1797                   CASE ( 'qsurf_av' )
1798                      IF ( .NOT. ALLOCATED( qsurf_av ) )  THEN
1799                         ALLOCATE( qsurf_av(nysg:nyng,nxlg:nxrg) )
1800                      ENDIF
1801                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1802                      qsurf_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                             &
1803                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1804
1805                   CASE ( 'qsws_av' )
1806                      IF ( .NOT. ALLOCATED( qsws_av ) )  THEN
1807                         ALLOCATE( qsws_av(nysg:nyng,nxlg:nxrg) )
1808                      ENDIF
1809                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1810                      qsws_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                             &
1811                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1812
1813                   CASE ( 'qv_av' )
1814                      IF ( .NOT. ALLOCATED( qv_av ) )  THEN
1815                         ALLOCATE( qv_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1816                      ENDIF
1817                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1818                      qv_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                              &
1819                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1820
1821                   CASE ( 'r_a_av' )
1822                      IF ( .NOT. ALLOCATED( r_a_av ) )  THEN
1823                         ALLOCATE( r_a_av(nysg:nyng,nxlg:nxrg) )
1824                      ENDIF
1825                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1826                      r_a_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
1827                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1828
1829                   CASE ( 'random_iv' )  ! still unresolved issue
1830                      IF ( k == 1 )  READ ( 13 )  random_iv
1831                      IF ( k == 1 )  READ ( 13 )  random_iy
1832
1833                   CASE ( 'seq_random_array' )
1834                      ALLOCATE( tmp_2d_id_random(nys_on_file:nyn_on_file,nxl_on_file:nxr_on_file) )
1835                      ALLOCATE( tmp_2d_seq_random(5,nys_on_file:nyn_on_file,nxl_on_file:nxr_on_file) )
1836                      IF ( .NOT. ALLOCATED( id_random_array ) )  THEN
1837                         ALLOCATE( id_random_array(nys:nyn,nxl:nxr) )
1838                      ENDIF
1839                      IF ( .NOT. ALLOCATED( seq_random_array ) )  THEN
1840                         ALLOCATE( seq_random_array(5,nys:nyn,nxl:nxr) )
1841                      ENDIF
1842                      IF ( k == 1 )  READ ( 13 )  tmp_2d_id_random
1843                      IF ( k == 1 )  READ ( 13 )  tmp_2d_seq_random
1844                      id_random_array(nysc:nync,nxlc:nxrc) = tmp_2d_id_random(nysf:nynf,nxlf:nxrf)
1845                      seq_random_array(:,nysc:nync,nxlc:nxrc) = tmp_2d_seq_random(:,nysf:nynf,nxlf:nxrf)
1846                      DEALLOCATE( tmp_2d_id_random, tmp_2d_seq_random )
1847
1848                   CASE ( 's' )
1849                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1850                      s(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
1851                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1852
1853                   CASE ( 's_av' )
1854                      IF ( .NOT. ALLOCATED( s_av ) )  THEN
1855                         ALLOCATE( s_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg))
1856                      ENDIF
1857                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1858                      s_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
1859                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1860
1861                   CASE ( 'shf_av' )
1862                      IF ( .NOT. ALLOCATED( shf_av ) )  THEN
1863                         ALLOCATE( shf_av(nysg:nyng,nxlg:nxrg) )
1864                      ENDIF
1865                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1866                      shf_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                              &
1867                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1868
1869                   CASE ( 'ssurf_av' )
1870                      IF ( .NOT. ALLOCATED( ssurf_av ) )  THEN
1871                         ALLOCATE( ssurf_av(nysg:nyng,nxlg:nxrg) )
1872                      ENDIF
1873                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1874                      ssurf_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                             &
1875                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1876
1877                   CASE ( 'ssws_av' )
1878                      IF ( .NOT. ALLOCATED( ssws_av ) )  THEN
1879                         ALLOCATE( ssws_av(nysg:nyng,nxlg:nxrg) )
1880                      ENDIF
1881                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1882                      ssws_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                             &
1883                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1884
1885                   CASE ( 'ts_av' )
1886                      IF ( .NOT. ALLOCATED( ts_av ) )  THEN
1887                         ALLOCATE( ts_av(nysg:nyng,nxlg:nxrg) )
1888                      ENDIF
1889                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1890                      ts_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                               &
1891                           tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1892
1893                   CASE ( 'tsurf_av' )
1894                      IF ( .NOT. ALLOCATED( tsurf_av ) )  THEN
1895                         ALLOCATE( tsurf_av(nysg:nyng,nxlg:nxrg) )
1896                      ENDIF
1897                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1898                      tsurf_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                             &
1899                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1900
1901                   CASE ( 'u' )
1902                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1903                      u(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
1904                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1905
1906                   CASE ( 'u_av' )
1907                      IF ( .NOT. ALLOCATED( u_av ) )  THEN
1908                         ALLOCATE( u_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1909                      ENDIF
1910                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1911                      u_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
1912                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1913
1914                   CASE ( 'u_m_l' )
1915                      IF ( k == 1 )  THEN
1916                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,   &
1917                                                       1:2) )
1918                         READ ( 13 )  tmp_3d_non_standard
1919                      ENDIF
1920                      IF ( bc_radiation_l )  THEN
1921                         u_m_l(:,nysc-nbgp:nync+nbgp,:) =  tmp_3d_non_standard(:,nysf-nbgp:nynf+nbgp,:)
1922                      ENDIF
1923
1924                   CASE ( 'u_m_n' )
1925                      IF ( k == 1 )  THEN
1926                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,ny-1:ny,                             &
1927                                                       nxl_on_file-nbgp:nxr_on_file+nbgp) )
1928                         READ ( 13 )  tmp_3d_non_standard
1929                      ENDIF
1930                      IF ( bc_radiation_n )  THEN
1931                         u_m_n(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3d_non_standard(:,:,nxlf-nbgp:nxrf+nbgp)
1932                      ENDIF
1933
1934                   CASE ( 'u_m_r' )
1935                      IF ( k == 1 )  THEN
1936                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,   &
1937                                                       nx-1:nx) )
1938                         READ ( 13 )  tmp_3d_non_standard
1939                      ENDIF
1940                      IF ( bc_radiation_r )  THEN
1941                         u_m_r(:,nysc-nbgp:nync+nbgp,:) = tmp_3d_non_standard(:,nysf-nbgp:nynf+nbgp,:)
1942                      ENDIF
1943
1944                   CASE ( 'u_m_s' )
1945                      IF ( k == 1 )  THEN
1946                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,0:1,                                 &
1947                                                       nxl_on_file-nbgp:nxr_on_file+nbgp) )
1948                         READ ( 13 )  tmp_3d_non_standard
1949                      ENDIF
1950                      IF ( bc_radiation_s )  THEN
1951                         u_m_s(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3d_non_standard(:,:,nxlf-nbgp:nxrf+nbgp)
1952                      ENDIF
1953
1954                   CASE ( 'us_av' )
1955                      IF ( .NOT. ALLOCATED( us_av ) )  THEN
1956                         ALLOCATE( us_av(nysg:nyng,nxlg:nxrg) )
1957                      ENDIF
1958                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1959                      us_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                               &
1960                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1961
1962                   CASE ( 'v' )
1963                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1964                      v(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
1965                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1966
1967                   CASE ( 'v_av' )
1968                      IF ( .NOT. ALLOCATED( v_av ) )  THEN
1969                         ALLOCATE( v_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1970                      ENDIF
1971                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1972                      v_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
1973                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1974
1975                   CASE ( 'v_m_l' )
1976                      IF ( k == 1 )  THEN
1977                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,   &
1978                                                       0:1) )
1979                         READ ( 13 )  tmp_3d_non_standard
1980                      ENDIF
1981                      IF ( bc_radiation_l )  THEN
1982                         v_m_l(:,nysc-nbgp:nync+nbgp,:) = tmp_3d_non_standard(:,nysf-nbgp:nynf+nbgp,:)
1983                      ENDIF
1984
1985                   CASE ( 'v_m_n' )
1986                      IF ( k == 1 )  THEN
1987                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,ny-1:ny,                             &
1988                                                       nxl_on_file-nbgp:nxr_on_file+nbgp) )
1989                         READ ( 13 )  tmp_3d_non_standard
1990                      ENDIF
1991                      IF ( bc_radiation_n )  THEN
1992                         v_m_n(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3d_non_standard(:,:,nxlf-nbgp:nxrf+nbgp)
1993                      ENDIF
1994
1995                   CASE ( 'v_m_r' )
1996                      IF ( k == 1 )  THEN
1997                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,   &
1998                                                       nx-1:nx) )
1999                         READ ( 13 )  tmp_3d_non_standard
2000                      ENDIF
2001                      IF ( bc_radiation_r )  THEN
2002                         v_m_r(:,nysc-nbgp:nync+nbgp,:) = tmp_3d_non_standard(:,nysf-nbgp:nynf+nbgp,:)
2003                      ENDIF
2004
2005                   CASE ( 'v_m_s' )
2006                      IF ( k == 1 )  THEN
2007                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,1:2,                                 &
2008                                                       nxl_on_file-nbgp:nxr_on_file+nbgp) )
2009                         READ ( 13 )  tmp_3d_non_standard
2010                      ENDIF
2011                      IF ( bc_radiation_s )  THEN
2012                         v_m_s(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3d_non_standard(:,:,nxlf-nbgp:nxrf+nbgp)
2013                      ENDIF
2014
2015                   CASE ( 'vpt' )
2016                      IF ( k == 1 )  READ ( 13 )  tmp_3d
2017                      vpt(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                &
2018                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2019
2020                   CASE ( 'vpt_av' )
2021                      IF ( .NOT. ALLOCATED( vpt_av ) )  THEN
2022                         ALLOCATE( vpt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2023                      ENDIF
2024                      IF ( k == 1 )  READ ( 13 )  tmp_3d
2025                      vpt_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                             &
2026                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2027
2028                   CASE ( 'w' )
2029                      IF ( k == 1 )  READ ( 13 )  tmp_3d
2030                      w(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
2031                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2032
2033                   CASE ( 'w_av' )
2034                      IF ( .NOT. ALLOCATED( w_av ) )  THEN
2035                         ALLOCATE( w_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2036                      ENDIF
2037                      IF ( k == 1 )  READ ( 13 )  tmp_3d
2038                      w_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
2039                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2040
2041                   CASE ( 'w_m_l' )
2042                      IF ( k == 1 )  THEN
2043                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,   &
2044                                                       0:1) )
2045                         READ ( 13 )  tmp_3d_non_standard
2046                      ENDIF
2047                      IF ( bc_radiation_l )  THEN
2048                         w_m_l(:,nysc-nbgp:nync+nbgp,:) = tmp_3d_non_standard(:,nysf-nbgp:nynf+nbgp,:)
2049                      ENDIF
2050
2051                   CASE ( 'w_m_n' )
2052                      IF ( k == 1 )  THEN
2053                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,ny-1:ny,                             &
2054                                                       nxl_on_file-nbgp:nxr_on_file+nbgp) )
2055                         READ ( 13 )  tmp_3d_non_standard
2056                      ENDIF
2057                      IF ( bc_radiation_n )  THEN
2058                         w_m_n(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3d_non_standard(:,:,nxlf-nbgp:nxrf+nbgp)
2059                      ENDIF
2060
2061                   CASE ( 'w_m_r' )
2062                      IF ( k == 1 )  THEN
2063                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,   &
2064                                                       nx-1:nx) )
2065                         READ ( 13 )  tmp_3d_non_standard
2066                      ENDIF
2067                      IF ( bc_radiation_r )  THEN
2068                         w_m_r(:,nysc-nbgp:nync+nbgp,:) = tmp_3d_non_standard(:,nysf-nbgp:nynf+nbgp,:)
2069                      ENDIF
2070
2071                   CASE ( 'w_m_s' )
2072                      IF ( k == 1 )  THEN
2073                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,0:1,                                 &
2074                                                       nxl_on_file-nbgp:nxr_on_file+nbgp) )
2075                         READ ( 13 )  tmp_3d_non_standard
2076                      ENDIF
2077                      IF ( bc_radiation_s )  THEN
2078                         w_m_s(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3d_non_standard(:,:,nxlf-nbgp:nxrf+nbgp)
2079                      ENDIF
2080
2081                   CASE ( 'z0_av' )
2082                      IF ( .NOT. ALLOCATED( z0_av ) )  THEN
2083                         ALLOCATE( z0_av(nysg:nyng,nxlg:nxrg) )
2084                      ENDIF
2085                      IF ( k == 1 )  READ ( 13 )  tmp_2d
2086                      z0_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                               &
2087                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2088
2089                   CASE ( 'z0h_av' )
2090                      IF ( .NOT. ALLOCATED( z0h_av ) )  THEN
2091                         ALLOCATE( z0h_av(nysg:nyng,nxlg:nxrg) )
2092                      ENDIF
2093                      IF ( k == 1 )  READ ( 13 )  tmp_2d
2094                      z0h_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                              &
2095                          tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2096
2097                   CASE ( 'z0q_av' )
2098                      IF ( .NOT. ALLOCATED( z0q_av ) )  THEN
2099                         ALLOCATE( z0q_av(nysg:nyng,nxlg:nxrg) )
2100                      ENDIF
2101                      IF ( k == 1 )  READ ( 13 )  tmp_2d
2102                      z0q_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                              &
2103                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
2104
2105                   CASE DEFAULT
2106
2107!
2108!--                   Read restart data of surfaces
2109                      IF ( .NOT. found )  CALL surface_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf,   &
2110                                                                  nxr_on_file, nynf, nyn_on_file,     &
2111                                                                  nysf, nysc, nys_on_file, found )
2112!
2113!--                   Read restart data of other modules
2114                      IF ( .NOT. found ) CALL module_interface_rrd_local(                             &
2115                                                                  k, nxlf, nxlc, nxl_on_file, nxrf,   &
2116                                                                  nxrc, nxr_on_file, nynf, nync,      &
2117                                                                  nyn_on_file, nysf, nysc,            &
2118                                                                  nys_on_file, tmp_2d, tmp_3d, found )
2119
2120
2121                      IF ( .NOT. found )  THEN
2122                         WRITE( message_string, * ) 'unknown variable named "',                       &
2123                                                    restart_string(1:length),                         &
2124                                                   '" found in subdomain data ',                      &
2125                                                   'from prior run on PE ', myid
2126                         CALL message( 'rrd_local', 'PA0302', 1, 2, 0, 6, 0 )
2127
2128                      ENDIF
2129
2130                END SELECT
2131
2132             ENDDO ! overlaploop
2133
2134!
2135!--          Deallocate non standard array needed for specific variables only
2136             IF ( ALLOCATED( tmp_3d_non_standard ) )  DEALLOCATE( tmp_3d_non_standard )
2137
2138!
2139!--          Read next character string
2140             READ ( 13 )  length
2141             READ ( 13 )  restart_string(1:length)
2142
2143          ENDDO ! dataloop
2144!
2145!--       Close the restart file
2146          CALL close_file( 13 )
2147
2148          DEALLOCATE( tmp_2d, tmp_3d )
2149
2150       ENDDO  ! loop over restart files
2151!
2152!--    Deallocate temporary buffer arrays
2153       DEALLOCATE( nxlfa )
2154       DEALLOCATE( nxrfa )
2155       DEALLOCATE( nynfa )
2156       DEALLOCATE( nysfa )
2157       DEALLOCATE( offset_xa )
2158       DEALLOCATE( offset_ya )
2159!
2160!--    Restore the original filename for the restart file to be written
2161       myid_char = myid_char_save
2162
2163
2164    ELSEIF ( restart_data_format_input(1:3) == 'mpi' )  THEN
2165
2166!
2167!--    Read global restart data using MPI-IO
2168!
2169!--    Open the MPI-IO restart file.
2170       CALL rd_mpi_io_open( 'read', 'BININ' // TRIM( coupling_char ) )
2171
2172
2173       CALL rd_mpi_io_check_array( 'ghf_av' , found = array_found )
2174       IF ( array_found )  THEN
2175          IF (.NOT. ALLOCATED( ghf_av ) )  ALLOCATE( ghf_av(nysg:nyng,nxlg:nxrg) )
2176          CALL rrd_mpi_io( 'ghf_av', ghf_av )
2177       ENDIF
2178
2179       CALL rrd_mpi_io( 'e', e )
2180
2181       CALL rd_mpi_io_check_array( 'e_av' , found = array_found )
2182       IF ( array_found  )  THEN
2183          IF ( .NOT. ALLOCATED( e_av ) )  ALLOCATE( e_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2184          CALL rrd_mpi_io( 'e_av', e_av )
2185       ENDIF
2186
2187       CALL rrd_mpi_io( 'kh', kh )
2188
2189       CALL rd_mpi_io_check_array( 'kh_av' , found = array_found )
2190       IF ( array_found )  THEN
2191          IF ( .NOT. ALLOCATED( kh_av ) )  ALLOCATE( kh_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2192          CALL rrd_mpi_io( 'kh_av', kh_av )
2193       ENDIF
2194
2195       CALL rrd_mpi_io( 'km' , km)
2196
2197       CALL rd_mpi_io_check_array( 'km_av' , found = array_found )
2198       IF ( array_found )  THEN
2199          IF ( .NOT. ALLOCATED( km_av ) )  ALLOCATE( km_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2200          CALL rrd_mpi_io( 'km_av', km_av )
2201       ENDIF
2202
2203       CALL rd_mpi_io_check_array( 'lpt_av' , found = array_found )
2204       IF ( array_found )  THEN
2205          IF ( .NOT. ALLOCATED( lpt_av ) )  ALLOCATE( lpt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2206          CALL rrd_mpi_io( 'lpt_av', lpt_av )
2207       ENDIF
2208
2209       CALL rd_mpi_io_check_array( 'lwp_av' , found = array_found )
2210       IF ( array_found )  THEN
2211          IF ( .NOT. ALLOCATED( lwp_av ) )  ALLOCATE( lwp_av(nysg:nyng,nxlg:nxrg) )
2212          CALL rrd_mpi_io( 'lwp_av', lwp_av )
2213       ENDIF
2214
2215       CALL rrd_mpi_io( 'p', p)
2216
2217       CALL rd_mpi_io_check_array( 'p_av' , found = array_found )
2218       IF ( array_found )  THEN
2219          IF ( .NOT. ALLOCATED( p_av ) )  ALLOCATE( p_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2220          CALL rrd_mpi_io( 'p_av', p_av )
2221       ENDIF
2222
2223       CALL rrd_mpi_io( 'pt', pt)
2224
2225       CALL rd_mpi_io_check_array( 'pt_av' , found = array_found )
2226       IF ( array_found )  THEN
2227          IF ( .NOT. ALLOCATED( pt_av ) )  ALLOCATE( pt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2228          CALL rrd_mpi_io( 'pt_av', pt_av )
2229       ENDIF
2230
2231       CALL rd_mpi_io_check_array( 'q' , found = array_found )
2232       IF ( array_found )  THEN
2233          CALL rrd_mpi_io( 'q', q )
2234       ENDIF
2235
2236       CALL rd_mpi_io_check_array( 'q_av' , found = array_found )
2237       IF ( array_found )  THEN
2238          IF ( .NOT. ALLOCATED( q_av ) )  ALLOCATE( q_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2239          CALL rrd_mpi_io( 'q_av', q_av )
2240       ENDIF
2241
2242       CALL rd_mpi_io_check_array( 'ql' , found = array_found )
2243       IF ( array_found )  THEN
2244          CALL rrd_mpi_io( 'ql', ql )
2245       ENDIF
2246
2247       CALL rd_mpi_io_check_array( 'ql_av' , found = array_found )
2248       IF ( array_found )  THEN
2249          IF ( .NOT. ALLOCATED( ql_av ) )  ALLOCATE( ql_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2250          CALL rrd_mpi_io( 'ql_av', ql_av )
2251       ENDIF
2252
2253       CALL rd_mpi_io_check_array( 'qsurf_av' , found = array_found )
2254       IF ( array_found )  THEN
2255          IF ( .NOT. ALLOCATED( qsurf_av ) )  ALLOCATE( qsurf_av(nysg:nyng,nxlg:nxrg) )
2256          CALL rrd_mpi_io( 'qsurf_av', qsurf_av )
2257       ENDIF
2258
2259       CALL rd_mpi_io_check_array( 'qsws_av' , found = array_found )
2260       IF ( array_found )  THEN
2261          IF ( .NOT. ALLOCATED( qsws_av ) )  ALLOCATE( qsws_av(nysg:nyng,nxlg:nxrg) )
2262          CALL rrd_mpi_io( 'qsws_av', qsws_av )
2263       ENDIF
2264
2265       CALL rd_mpi_io_check_array( 'qv_av' , found = array_found )
2266       IF ( array_found )  THEN
2267          IF ( .NOT. ALLOCATED( qv_av ) )  ALLOCATE( qv_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2268          CALL rrd_mpi_io( 'qv_av', qv_av )
2269       ENDIF
2270
2271       CALL rd_mpi_io_check_array( 'r_a_av' , found = array_found )
2272       IF ( array_found )  THEN
2273          IF ( .NOT. ALLOCATED( r_a_av ) )  ALLOCATE( r_a_av(nysg:nyng,nxlg:nxrg) )
2274          CALL rrd_mpi_io( 'r_a_av', r_a_av )
2275       ENDIF
2276
2277!
2278!--    ATTENTION: The random seeds are global data! If independent values for every PE are required,
2279!--    the general approach of PE indendent restart will be lost. That means that in general the
2280!--    parallel random number generator in random_generator_parallel_mod should be used!
2281       CALL rrd_mpi_io_global_array( 'random_iv', random_iv )
2282       CALL rrd_mpi_io( 'random_iy', random_iy )
2283
2284       CALL rd_mpi_io_check_array( 'id_random_array' , found = array_found )
2285       IF ( array_found )  THEN
2286          IF ( .NOT. ALLOCATED( id_random_array ) )  ALLOCATE( id_random_array(nys:nyn,nxl:nxr) )
2287          IF ( .NOT. ALLOCATED( seq_random_array ) )  ALLOCATE( seq_random_array(5,nys:nyn,nxl:nxr) )
2288          CALL rrd_mpi_io( 'id_random_array', id_random_array)
2289          DO  i = 1, SIZE( seq_random_array, 1 )
2290             WRITE( tmp_name, '(A,I2.2)' )  'seq_random_array', i
2291             CALL rrd_mpi_io( TRIM(tmp_name), seq_random_array(i,:,:) )
2292          ENDDO
2293       ENDIF
2294
2295       CALL rd_mpi_io_check_array( 's' , found = array_found )
2296       IF ( array_found )  THEN
2297          CALL rrd_mpi_io( 's', s )
2298       ENDIF
2299
2300       CALL rd_mpi_io_check_array( 's_av' , found = array_found )
2301       IF ( array_found )  THEN
2302          IF ( .NOT. ALLOCATED( s_av ) )  ALLOCATE( s_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2303          CALL rrd_mpi_io( 's_av', s_av )
2304       ENDIF
2305
2306       CALL rd_mpi_io_check_array( 'shf_av' , found = array_found )
2307       IF ( array_found )  THEN
2308          IF ( .NOT. ALLOCATED( shf_av ) )  ALLOCATE( shf_av(nysg:nyng,nxlg:nxrg) )
2309          CALL rrd_mpi_io( 'shf_av', shf_av )
2310       ENDIF
2311
2312       CALL rd_mpi_io_check_array( 'ssurf_av' , found = array_found )
2313       IF ( array_found )  THEN
2314          IF ( .NOT. ALLOCATED( ssurf_av ) )  ALLOCATE( ssurf_av(nysg:nyng,nxlg:nxrg) )
2315          CALL rrd_mpi_io( 'ssurf_av', ssurf_av )
2316       ENDIF
2317
2318       CALL rd_mpi_io_check_array( 'ssws_av' , found = array_found )
2319       IF ( array_found )  THEN
2320          IF ( .NOT. ALLOCATED( ssws_av ) )  ALLOCATE( ssws_av(nysg:nyng,nxlg:nxrg) )
2321          CALL rrd_mpi_io( 'ssws_av', ssws_av )
2322       ENDIF
2323
2324       CALL rd_mpi_io_check_array( 'ts_av' , found = array_found )
2325       IF ( array_found )  THEN
2326          IF ( .NOT. ALLOCATED( ts_av ) )  ALLOCATE( ts_av(nysg:nyng,nxlg:nxrg) )
2327          CALL rrd_mpi_io( 'ts_av', ts_av )
2328       ENDIF
2329
2330       CALL rd_mpi_io_check_array( 'tsurf_av' , found = array_found )
2331       IF ( array_found )  THEN
2332          IF ( .NOT. ALLOCATED( tsurf_av ) )  ALLOCATE( tsurf_av(nysg:nyng,nxlg:nxrg) )
2333          CALL rrd_mpi_io( 'tsurf_av', tsurf_av )
2334       ENDIF
2335
2336       CALL rrd_mpi_io( 'u', u)
2337
2338       CALL rd_mpi_io_check_array( 'u_av' , found = array_found )
2339       IF ( array_found )  THEN
2340          IF ( .NOT. ALLOCATED( u_av ) )  ALLOCATE( u_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2341          CALL rrd_mpi_io( 'u_av', u_av )
2342       ENDIF
2343
2344       CALL rd_mpi_io_check_array( 'u_m_l' , found = array_found )
2345       IF ( array_found )  THEN
2346          IF ( .NOT. ALLOCATED( u_m_l ) )  ALLOCATE( u_m_l(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2347          CALL rrd_mpi_io( 'u_m_l', u_m_l )
2348       ENDIF
2349
2350       CALL rd_mpi_io_check_array( 'u_m_n' , found = array_found )
2351       IF ( array_found )  THEN
2352          IF ( .NOT. ALLOCATED( u_m_n ) )  ALLOCATE( u_m_n(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2353          CALL rrd_mpi_io( 'u_m_n', u_m_n )
2354       ENDIF
2355
2356       CALL rd_mpi_io_check_array( 'u_m_r' , found = array_found )
2357       IF ( array_found )  THEN
2358          IF ( .NOT. ALLOCATED( u_m_r ) )  ALLOCATE( u_m_r(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2359          CALL rrd_mpi_io( 'u_m_r', u_m_r )
2360       ENDIF
2361
2362       CALL rd_mpi_io_check_array( 'u_m_s' , found = array_found )
2363       IF ( array_found )  THEN
2364          IF ( .NOT. ALLOCATED( u_m_s ) )  ALLOCATE( u_m_s(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2365          CALL rrd_mpi_io( 'u_m_s', u_m_s )
2366       ENDIF
2367
2368       CALL rd_mpi_io_check_array( 'us_av' , found = array_found )
2369       IF ( array_found )  THEN
2370          IF ( .NOT. ALLOCATED( us_av ) )  ALLOCATE( us_av(nysg:nyng,nxlg:nxrg) )
2371          CALL rrd_mpi_io( 'us_av', us_av )
2372       ENDIF
2373
2374       CALL rrd_mpi_io( 'v', v )
2375
2376       CALL rd_mpi_io_check_array( 'v_av' , found = array_found )
2377       IF ( array_found )  THEN
2378          IF ( .NOT. ALLOCATED( v_av ) )  ALLOCATE( v_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2379          CALL rrd_mpi_io( 'v_av', v_av )
2380       ENDIF
2381
2382       CALL rd_mpi_io_check_array( 'v_m_l' , found = array_found )
2383       IF ( array_found )  THEN
2384          IF ( .NOT. ALLOCATED( v_m_l ) )  ALLOCATE( v_m_l(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2385          CALL rrd_mpi_io( 'v_m_l', v_m_l )
2386       ENDIF
2387
2388       CALL rd_mpi_io_check_array( 'v_m_n' , found = array_found )
2389       IF ( array_found )  THEN
2390          IF ( .NOT. ALLOCATED( v_m_n ) )  ALLOCATE( v_m_n(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2391          CALL rrd_mpi_io( 'v_m_n', v_m_n )
2392       ENDIF
2393
2394       CALL rd_mpi_io_check_array( 'v_m_r' , found = array_found )
2395       IF ( array_found )  THEN
2396          IF ( .NOT. ALLOCATED( v_m_r ) )  ALLOCATE( v_m_r(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2397          CALL rrd_mpi_io( 'v_m_r', v_m_r )
2398       ENDIF
2399
2400       CALL rd_mpi_io_check_array( 'v_m_s' , found = array_found )
2401       IF ( array_found )  THEN
2402          IF ( .NOT. ALLOCATED( v_m_s ) )  ALLOCATE( v_m_s(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2403          CALL rrd_mpi_io( 'v_m_s', v_m_s )
2404       ENDIF
2405
2406       CALL rd_mpi_io_check_array( 'vpt' , found = array_found )
2407       IF ( array_found )  THEN
2408          CALL rrd_mpi_io( 'vpt',  vpt)
2409       ENDIF
2410
2411       CALL rd_mpi_io_check_array( 'vpt_av' , found = array_found )
2412       IF ( array_found )  THEN
2413          IF ( .NOT. ALLOCATED( vpt_av ) )  ALLOCATE( vpt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2414          CALL rrd_mpi_io( 'vpt_av', vpt_av )
2415       ENDIF
2416
2417       CALL rrd_mpi_io( 'w', w)
2418
2419       CALL rd_mpi_io_check_array( 'w_av' , found = array_found )
2420       IF ( array_found )  THEN
2421          IF ( .NOT. ALLOCATED( w_av ) )  ALLOCATE( w_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2422          CALL rrd_mpi_io( 'w_av', w_av )
2423       ENDIF
2424
2425       CALL rd_mpi_io_check_array( 'w_m_l' , found = array_found )
2426       IF ( array_found )  THEN
2427          IF ( .NOT. ALLOCATED( w_m_l ) )  ALLOCATE( w_m_l(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2428          CALL rrd_mpi_io( 'w_m_l', w_m_l )
2429       ENDIF
2430
2431       CALL rd_mpi_io_check_array( 'w_m_n' , found = array_found )
2432       IF ( array_found )  THEN
2433          IF ( .NOT. ALLOCATED( w_m_n ) )  ALLOCATE( w_m_n(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2434          CALL rrd_mpi_io( 'w_m_n', w_m_n )
2435       ENDIF
2436
2437       CALL rd_mpi_io_check_array( 'w_m_r' , found = array_found )
2438       IF ( array_found )  THEN
2439          IF ( .NOT. ALLOCATED( w_m_r ) )  ALLOCATE( w_m_r(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2440          CALL rrd_mpi_io( 'w_m_r', w_m_r )
2441       ENDIF
2442
2443       CALL rd_mpi_io_check_array( 'w_m_s' , found = array_found )
2444       IF ( array_found )  THEN
2445          IF ( .NOT. ALLOCATED( w_m_s ) )  ALLOCATE( w_m_s(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2446          CALL rrd_mpi_io( 'w_m_s', w_m_s )
2447       ENDIF
2448
2449       CALL rd_mpi_io_check_array( 'z0_av' , found = array_found )
2450       IF ( array_found )  THEN
2451          IF ( .NOT. ALLOCATED( z0_av ) )  ALLOCATE( z0_av(nysg:nyng,nxlg:nxrg) )
2452          CALL rrd_mpi_io( 'z0_av', z0_av )
2453       ENDIF
2454
2455       CALL rd_mpi_io_check_array( 'z0h_av' , found = array_found )
2456       IF ( array_found )  THEN
2457          IF ( .NOT. ALLOCATED( z0h_av ) )  ALLOCATE( z0h_av(nysg:nyng,nxlg:nxrg) )
2458          CALL rrd_mpi_io( 'z0h_av', z0h_av )
2459       ENDIF
2460
2461       CALL rd_mpi_io_check_array( 'z0q_av' , found = array_found )
2462       IF ( array_found )  THEN
2463          IF ( .NOT. ALLOCATED( z0q_av ) )  ALLOCATE( z0q_av(nysg:nyng,nxlg:nxrg) )
2464          CALL rrd_mpi_io( 'z0q_av', z0q_av )
2465       ENDIF
2466
2467!
2468!--    Read restart data of surfaces
2469       CALL surface_rrd_local
2470
2471!
2472!--    Read restart data of other modules
2473       CALL module_interface_rrd_local
2474
2475!
2476!--    Close restart file
2477       CALL rd_mpi_io_close
2478
2479    ENDIF
2480
2481!
2482!-- End of time measuring for reading binary data
2483    CALL cpu_log( log_point_s(14), 'rrd_local', 'stop' )
2484
2485 END SUBROUTINE rrd_local
2486
2487
2488!------------------------------------------------------------------------------!
2489! Description:
2490! ------------
2491!> Skipping the global control variables from restart-file (binary format)
2492!------------------------------------------------------------------------------!
2493 SUBROUTINE rrd_skip_global
2494
2495
2496    CHARACTER (LEN=1) ::  cdum
2497
2498
2499    READ ( 13 )  length
2500    READ ( 13 )  restart_string(1:length)
2501
2502    DO  WHILE ( restart_string(1:length) /= 'binary_version_local' )
2503
2504       READ ( 13 )  cdum
2505       READ ( 13 )  length
2506       READ ( 13 )  restart_string(1:length)
2507
2508    ENDDO
2509
2510    BACKSPACE ( 13 )
2511    BACKSPACE ( 13 )
2512
2513
2514 END SUBROUTINE rrd_skip_global
2515
2516
2517 END MODULE read_restart_data_mod
Note: See TracBrowser for help on using the repository browser.