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

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

bugfix for aborts in case of nested runs, data handling with MPI-IO for cyclic-fill added (so far only for global data)

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