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

Last change on this file since 4180 was 4180, checked in by scharf, 5 years ago

removed comments in 'Former revisions' section that are older than 01.01.2019

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