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

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

maximum phase velocities are alwasy used for radiation boundary conditions, parameter use_cmax removed

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