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

Last change on this file since 4533 was 4518, checked in by suehring, 4 years ago

Diagnostic output: Define arrays over ghost points in order to allow for standard mpi-io treatment. By this modularization of restart-data input is possible with the module interface. Move input of restart data to doq_rrd_local. Enable mpi-io for restart data. Bugfix: add missing restart input of wtheta_av, wq_av, wu_av, and wv_av.

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