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

Last change on this file since 4046 was 4039, checked in by suehring, 5 years ago

diagnostic output: Modularize diagnostic output, rename subroutines; formatting adjustments; allocate arrays only when required; add output of uu, vv, ww to enable variance calculation via temporal EC method; radiation: bugfix in masked data output; flow_statistics: Correct conversion to kinematic vertical scalar fluxes in case of pw-scheme and statistic regions

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