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

Last change on this file since 4888 was 4848, checked in by gronemeier, 3 years ago

bugfix: removed syn_turb_gen from restart files, replaced use_syn_turb_gen by syn_turb_gen

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