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

Last change on this file since 4725 was 4671, checked in by pavelkrc, 4 years ago

Radiative transfer model RTM version 4.1

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