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

Last change on this file since 4431 was 4431, checked in by gronemeier, 4 years ago

diagnostic_output_quantities: added wspeed and wdir output; bugfix: set fill_value in case of masked output

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