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

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

Vertical nesting method of Huq et al. (2019) removed

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