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

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

checks added, if index limits in header are exceeded (restart_data_mpi_io_mod), bugfix in rrd_mpi_io_int_2d, location and log_point names added/modified, cpu time per grid point and timestep does not included initialization and spinup any more (cpulog_mod)

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