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

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

bugfixes for restart with MPI-IO: problem with posix read arguments for surface data fixed, MPI barrier removed, coupling character added to restart input and output filename

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