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

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

bugfix for creation of filetypes, argument removed from rd_mpi_io_open, files re-formatted to follow the PALM coding standard

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