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

Last change on this file since 3294 was 3294, checked in by raasch, 6 years ago

modularization of the ocean code

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