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

Last change on this file since 3587 was 3582, checked in by suehring, 5 years ago

Merge branch salsa with trunk

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