source: palm/trunk/SOURCE/read_restart_data_mod.f90

Last change on this file was 4893, checked in by raasch, 3 years ago

revised output of surface data via MPI-IO for better performance

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