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

Last change on this file since 4103 was 4101, checked in by gronemeier, 5 years ago

timestep.f90:

  • consider 2*Km within diffusion criterion as Km is considered twice within the diffusion of e,
  • in RANS mode, instead of considering each wind component individually use the wind speed of 3d wind vector in CFL criterion
  • do not limit the increase of dt based on its previous value in RANS mode

other:

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