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

Last change on this file since 3995 was 3994, checked in by suehring, 5 years ago

new module for diagnostic output quantities added + output of turbulence intensity

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