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

Last change on this file since 3990 was 3988, checked in by kanani, 5 years ago

enable steering of output interval for virtual measurements

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