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

Last change on this file since 4131 was 4131, checked in by monakurppa, 5 years ago

Several changes in the salsa aerosol module:

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