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

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

restart data handling with MPI-IO added, first part

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