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

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

messages and debug output converted to PALM routines (restart_data_mpi_io_mod), binary version number set to 5.0, heeader output for restart data format added, restart data filesize and I/O transfer speed added in cpu_measures, handling of single restart files (created with MPI-I/O) added to palmrun, bugfix: preprocessor directive adjusted (virtual_measurement_mod), location message format changed

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