source: palm/tags/release-6.0/SOURCE/read_restart_data_mod.f90

Last change on this file was 3467, checked in by suehring, 5 years ago

Branch salsa @3446 re-integrated into trunk

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