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

Last change on this file since 3655 was 3655, checked in by knoop, 5 years ago

Bugfix: made "unit" and "found" intend INOUT in module interface subroutines + automatic copyright update

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