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

Last change on this file since 3448 was 3355, checked in by knoop, 6 years ago

removed calc_radiation.f90 and related cloud_top_radiation namelist parameter (functionality replaced by radiation model)

  • Property svn:keywords set to Id
File size: 83.0 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 3355 2018-10-16 14:03:34Z kanani $
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 surface_mod,                                                           &
1089        ONLY :  surface_rrd_local
1090       
1091    USE urban_surface_mod,                                                     &
1092        ONLY:  usm_rrd_local
1093
1094    USE user_read_restart_data_mod,                                            &
1095        ONLY:  user_rrd_local 
1096 
1097
1098    IMPLICIT NONE
1099
1100    CHARACTER (LEN=7)  ::  myid_char_save
1101    CHARACTER (LEN=10) ::  binary_version_local
1102    CHARACTER (LEN=10) ::  version_on_file
1103
1104    INTEGER(iwp) ::  files_to_be_opened  !<
1105    INTEGER(iwp) ::  i                   !<
1106    INTEGER(iwp) ::  j                   !<
1107    INTEGER(iwp) ::  k                   !<
1108    INTEGER(iwp) ::  myid_on_file        !<
1109    INTEGER(iwp) ::  numprocs_on_file    !<
1110    INTEGER(iwp) ::  nxlc                !<
1111    INTEGER(iwp) ::  nxlf                !<
1112    INTEGER(iwp) ::  nxlpr               !<
1113    INTEGER(iwp) ::  nxl_on_file         !<
1114    INTEGER(iwp) ::  nxrc                !<
1115    INTEGER(iwp) ::  nxrf                !<
1116    INTEGER(iwp) ::  nxrpr               !<
1117    INTEGER(iwp) ::  nxr_on_file         !<
1118    INTEGER(iwp) ::  nync                !<
1119    INTEGER(iwp) ::  nynf                !<
1120    INTEGER(iwp) ::  nynpr               !<
1121    INTEGER(iwp) ::  nyn_on_file         !<
1122    INTEGER(iwp) ::  nysc                !<
1123    INTEGER(iwp) ::  nysf                !<
1124    INTEGER(iwp) ::  nyspr               !<
1125    INTEGER(iwp) ::  nys_on_file         !<
1126    INTEGER(iwp) ::  nzb_on_file         !<
1127    INTEGER(iwp) ::  nzt_on_file         !<
1128    INTEGER(iwp) ::  offset_x            !<
1129    INTEGER(iwp) ::  offset_y            !<
1130    INTEGER(iwp) ::  shift_x             !<
1131    INTEGER(iwp) ::  shift_y             !<
1132
1133    INTEGER(iwp), DIMENSION(numprocs_previous_run) ::  file_list       !<
1134    INTEGER(iwp), DIMENSION(numprocs_previous_run) ::  overlap_count   !<
1135
1136    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nxlfa      !<
1137    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nxrfa      !<
1138    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nynfa      !<
1139    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nysfa      !<
1140    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  offset_xa  !<
1141    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  offset_ya  !<
1142
1143    INTEGER(isp), DIMENSION(:,:),   ALLOCATABLE ::  tmp_2d_id_random   !< temporary array for storing random generator data
1144    INTEGER(isp), DIMENSION(:,:,:), ALLOCATABLE ::  tmp_2d_seq_random  !< temporary array for storing random generator data
1145
1146    LOGICAL ::  found
1147
1148    REAL(wp), DIMENSION(:,:),   ALLOCATABLE   ::  tmp_2d      !< temporary array for storing 2D data
1149    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3d      !< temporary array for storing 3D data
1150    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwul   !<
1151    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwun   !<
1152    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwur   !<
1153    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwus   !<
1154    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwvl   !<
1155    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwvn   !<
1156    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwvr   !<
1157    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwvs   !<
1158    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwwl   !<
1159    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwwn   !<
1160    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwwr   !<
1161    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwws   !<
1162
1163
1164!
1165!-- Read data from previous model run.
1166    CALL cpu_log( log_point_s(14), 'rrd_local', 'start' )
1167
1168!
1169!-- Check which of the restart files contain data needed for the subdomain
1170!-- of this PE
1171    files_to_be_opened = 0
1172
1173    DO  i = 1, numprocs_previous_run
1174!
1175!--    Store array bounds of the previous run ("pr") in temporary scalars
1176       nxlpr = hor_index_bounds_previous_run(1,i-1)
1177       nxrpr = hor_index_bounds_previous_run(2,i-1)
1178       nyspr = hor_index_bounds_previous_run(3,i-1)
1179       nynpr = hor_index_bounds_previous_run(4,i-1)
1180
1181!
1182!--    Determine the offsets. They may be non-zero in case that the total domain
1183!--    on file is smaller than the current total domain.
1184       offset_x = ( nxl / ( nx_on_file + 1 ) ) * ( nx_on_file + 1 )
1185       offset_y = ( nys / ( ny_on_file + 1 ) ) * ( ny_on_file + 1 )
1186
1187!
1188!--    Start with this offset and then check, if the subdomain on file
1189!--    matches another time(s) in the current subdomain by shifting it
1190!--    for nx_on_file+1, ny_on_file+1 respectively
1191   
1192       shift_y = 0
1193       j       = 0
1194       DO WHILE (  nyspr+shift_y <= nyn-offset_y )
1195         
1196          IF ( nynpr+shift_y >= nys-offset_y ) THEN
1197
1198             shift_x = 0
1199             DO WHILE ( nxlpr+shift_x <= nxr-offset_x )
1200               
1201                IF ( nxrpr+shift_x >= nxl-offset_x ) THEN
1202                   j = j +1
1203                   IF ( j > 1000 )  THEN
1204!
1205!--                   Array bound exceeded
1206                      message_string = 'data from subdomain of previous' //    &
1207                                       ' run mapped more than 1000 times'
1208                      CALL message( 'rrd_local', 'PA0284', 2, 2, -1,           &
1209                                       6, 1 )
1210                   ENDIF
1211
1212                   IF ( j == 1 )  THEN
1213                      files_to_be_opened = files_to_be_opened + 1
1214                      file_list(files_to_be_opened) = i-1
1215                   ENDIF
1216                     
1217                   offset_xa(files_to_be_opened,j) = offset_x + shift_x
1218                   offset_ya(files_to_be_opened,j) = offset_y + shift_y
1219!
1220!--                Index bounds of overlapping data
1221                   nxlfa(files_to_be_opened,j) = MAX( nxl-offset_x-shift_x,    &
1222                                                      nxlpr )
1223                   nxrfa(files_to_be_opened,j) = MIN( nxr-offset_x-shift_x,    &
1224                                                      nxrpr )
1225                   nysfa(files_to_be_opened,j) = MAX( nys-offset_y-shift_y,    & 
1226                                                      nyspr )
1227                   nynfa(files_to_be_opened,j) = MIN( nyn-offset_y-shift_y,    & 
1228                                                      nynpr )
1229
1230                ENDIF
1231
1232                shift_x = shift_x + ( nx_on_file + 1 )
1233             ENDDO
1234       
1235          ENDIF
1236             
1237          shift_y = shift_y + ( ny_on_file + 1 )             
1238       ENDDO
1239         
1240       IF ( j > 0 )  overlap_count(files_to_be_opened) = j
1241         
1242    ENDDO
1243   
1244!
1245!-- Save the id-string of the current process, since myid_char may now be used
1246!-- to open files created by PEs with other id.
1247    myid_char_save = myid_char
1248
1249    IF ( files_to_be_opened /= 1  .OR.  numprocs /= numprocs_previous_run )    &
1250    THEN
1251       WRITE( message_string, * ) 'number of PEs or virtual PE-grid changed ', &
1252                        'in restart run & PE', myid, ' will read from files ', &
1253                         file_list(1:files_to_be_opened)
1254       CALL message( 'rrd_local', 'PA0285', 0, 0, 0, 6, 0 )
1255    ENDIF
1256
1257!
1258!-- Read data from all restart files determined above
1259    DO  i = 1, files_to_be_opened
1260 
1261       j = file_list(i)
1262!
1263!--    Set the filename (underscore followed by four digit processor id)
1264       WRITE (myid_char,'(''_'',I6.6)')  j
1265
1266!
1267!--    Open the restart file. If this file has been created by PE0 (_000000),
1268!--    the global variables at the beginning of the file have to be skipped
1269!--    first.
1270       CALL check_open( 13 )
1271       IF ( j == 0 )  CALL rrd_skip_global
1272
1273!
1274!--    First compare the version numbers
1275       READ ( 13 )  length
1276       READ ( 13 )  restart_string(1:length)
1277       READ ( 13 )  version_on_file
1278
1279       binary_version_local = '4.7'
1280       IF ( TRIM( version_on_file ) /= TRIM( binary_version_local ) )  THEN
1281          WRITE( message_string, * ) 'version mismatch concerning ',           &
1282                      'binary_version_local:',                                 &
1283                      '&version on file    = "', TRIM( version_on_file ), '"', &
1284                      '&version in program = "', TRIM( binary_version_local ), '"'
1285          CALL message( 'rrd_local', 'PA0286', 1, 2, 0, 6, 0 )
1286       ENDIF
1287
1288!
1289!--    Read number of processors, processor-id, and array ranges.
1290!--    Compare the array ranges with those stored in the index bound array.
1291       READ ( 13 )  numprocs_on_file, myid_on_file, nxl_on_file, nxr_on_file,  &
1292                    nys_on_file, nyn_on_file, nzb_on_file, nzt_on_file
1293
1294       IF ( nxl_on_file /= hor_index_bounds_previous_run(1,j) )  THEN
1295          WRITE( message_string, * ) 'problem with index bound nxl on ',       &
1296                            'restart file "', myid_char, '"',                  &
1297                            '&nxl = ', nxl_on_file, ' but it should be',       &
1298                            '&= ', hor_index_bounds_previous_run(1,j),         &
1299                            '&from the index bound information array'
1300          CALL message( 'rrd_local', 'PA0287', 2, 2, -1, 6, 1 )
1301       ENDIF
1302
1303       IF ( nxr_on_file /= hor_index_bounds_previous_run(2,j) )  THEN
1304           WRITE( message_string, * ) 'problem with index bound nxr on ',      &
1305                               'restart file "', myid_char, '"'  ,             &
1306                               ' nxr = ', nxr_on_file, ' but it should be',    &
1307                               ' = ', hor_index_bounds_previous_run(2,j),      &
1308                               ' from the index bound information array' 
1309          CALL message( 'rrd_local', 'PA0288', 2, 2, -1, 6, 1 )
1310
1311       ENDIF
1312
1313       IF ( nys_on_file /= hor_index_bounds_previous_run(3,j) )  THEN
1314          WRITE( message_string, * ) 'problem with index bound nys on ',       &
1315                                 'restart file "', myid_char, '"',             &
1316                                 '&nys = ', nys_on_file, ' but it should be',  &
1317                                 '&= ', hor_index_bounds_previous_run(3,j),    &
1318                                 '&from the index bound information array'
1319          CALL message( 'rrd_local', 'PA0289', 2, 2, -1, 6, 1 ) 
1320       ENDIF
1321
1322       IF ( nyn_on_file /= hor_index_bounds_previous_run(4,j) )  THEN
1323          WRITE( message_string, * ) 'problem with index bound nyn on ',       &
1324                               'restart file "', myid_char, '"',               &
1325                               '&nyn = ', nyn_on_file, ' but it should be',    &
1326                               '&= ', hor_index_bounds_previous_run(4,j),      &
1327                               '&from the index bound information array'
1328          CALL message( 'rrd_local', 'PA0290', 2, 2, -1, 6, 1 ) 
1329       ENDIF
1330
1331       IF ( nzb_on_file /= nzb )  THEN
1332          WRITE( message_string, * ) 'mismatch between actual data and data ', &
1333                                     'from prior run on PE ', myid,            &
1334                                     '&nzb on file = ', nzb_on_file,           &
1335                                     '&nzb         = ', nzb
1336          CALL message( 'rrd_local', 'PA0291', 1, 2, 0, 6, 0 ) 
1337       ENDIF
1338
1339       IF ( nzt_on_file /= nzt )  THEN
1340          WRITE( message_string, * ) 'mismatch between actual data and data ', &
1341                                     'from prior run on PE ', myid,            &
1342                                     '&nzt on file = ', nzt_on_file,           &
1343                                     '&nzt         = ', nzt
1344          CALL message( 'rrd_local', 'PA0292', 1, 2, 0, 6, 0 ) 
1345       ENDIF
1346
1347!
1348!--    Allocate temporary arrays sized as the arrays on the restart file
1349       ALLOCATE( tmp_2d(nys_on_file-nbgp:nyn_on_file+nbgp,                     &
1350                        nxl_on_file-nbgp:nxr_on_file+nbgp),                    &
1351                 tmp_3d(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,           &
1352                        nxl_on_file-nbgp:nxr_on_file+nbgp) )
1353
1354!
1355!--    Read arrays
1356!--    ATTENTION: If the following read commands have been altered, the
1357!--    ---------- version number of the variable binary_version_local must
1358!--               be altered, too. Furthermore, the output list of arrays in
1359!--               wrd_write_local must also be altered
1360!--               accordingly.
1361       READ ( 13 )  length
1362       READ ( 13 )  restart_string(1:length)
1363       
1364
1365!
1366!--    Loop over processor specific field data
1367       DO  WHILE ( restart_string(1:length) /= '*** end ***' )
1368
1369!
1370!--       Map data on file as often as needed (data are read only for k=1)
1371          DO  k = 1, overlap_count(i)
1372
1373             found = .FALSE.
1374             
1375!
1376!--          Get the index range of the subdomain on file which overlap with
1377!--          the current subdomain
1378             nxlf = nxlfa(i,k)
1379             nxlc = nxlfa(i,k) + offset_xa(i,k)
1380             nxrf = nxrfa(i,k)
1381             nxrc = nxrfa(i,k) + offset_xa(i,k)
1382             nysf = nysfa(i,k)
1383             nysc = nysfa(i,k) + offset_ya(i,k)
1384             nynf = nynfa(i,k)
1385             nync = nynfa(i,k) + offset_ya(i,k)
1386
1387
1388             SELECT CASE ( restart_string(1:length) )
1389
1390                CASE ( 'ghf_av' )
1391                   IF ( .NOT. ALLOCATED( ghf_av ) )  THEN
1392                      ALLOCATE( ghf_av(nysg:nyng,nxlg:nxrg) )
1393                   ENDIF
1394                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1395                   ghf_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1396                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1397
1398                CASE ( 'e' )
1399                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1400                   e(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =              &
1401                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1402
1403                CASE ( 'e_av' )
1404                   IF ( .NOT. ALLOCATED( e_av ) )  THEN
1405                      ALLOCATE( e_av(nzb:nzt+1,nys-nbgp:nyn+nbgp,              &
1406                                     nxl-nbgp:nxr+nbgp) )   
1407                   ENDIF
1408                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1409                   e_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1410                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1411
1412                CASE ( 'iran' ) ! matching random numbers is still unresolved
1413                                ! issue
1414                   IF ( k == 1 )  READ ( 13 )  iran, iran_part
1415
1416                CASE ( 'kh' )
1417                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1418                   kh(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =             &
1419                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1420
1421                CASE ( 'kh_av' )
1422                   IF ( .NOT. ALLOCATED( kh_av ) )  THEN
1423                      ALLOCATE( kh_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
1424                   ENDIF
1425                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1426                   kh_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1427                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1428
1429                CASE ( 'km' )
1430                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1431                   km(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =             &
1432                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1433
1434                CASE ( 'km_av' )
1435                   IF ( .NOT. ALLOCATED( km_av ) )  THEN
1436                      ALLOCATE( km_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
1437                   ENDIF
1438                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1439                   km_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1440                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1441
1442                CASE ( 'lpt_av' )
1443                   IF ( .NOT. ALLOCATED( lpt_av ) )  THEN
1444                      ALLOCATE( lpt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
1445                   ENDIF
1446                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1447                   lpt_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =         &
1448                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1449
1450                CASE ( 'lwp_av' )
1451                   IF ( .NOT. ALLOCATED( lwp_av ) )  THEN
1452                      ALLOCATE( lwp_av(nysg:nyng,nxlg:nxrg) )
1453                   ENDIF
1454                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1455                   lwp_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1456                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1457
1458                CASE ( 'p' )
1459                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1460                   p(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =              &
1461                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1462
1463                CASE ( 'p_av' )
1464                   IF ( .NOT. ALLOCATED( p_av ) )  THEN
1465                      ALLOCATE( p_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1466                   ENDIF
1467                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1468                   p_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1469                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1470
1471                CASE ( 'pc_av' )
1472                   IF ( .NOT. ALLOCATED( pc_av ) )  THEN
1473                      ALLOCATE( pc_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1474                   ENDIF
1475                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1476                   pc_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1477                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1478
1479                CASE ( 'pr_av' )
1480                   IF ( .NOT. ALLOCATED( pr_av ) )  THEN
1481                      ALLOCATE( pr_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1482                   ENDIF
1483                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1484                   pr_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1485                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1486
1487                CASE ( 'pt' )
1488                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1489                   pt(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =             &
1490                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1491
1492                CASE ( 'pt_av' )
1493                   IF ( .NOT. ALLOCATED( pt_av ) )  THEN
1494                      ALLOCATE( pt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1495                   ENDIF
1496                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1497                   pt_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1498                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1499
1500                CASE ( 'q' )
1501                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1502                   q(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =              &
1503                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1504
1505                CASE ( 'q_av' )
1506                   IF ( .NOT. ALLOCATED( q_av ) )  THEN
1507                      ALLOCATE( q_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
1508                   ENDIF
1509                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1510                   q_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1511                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1512
1513                CASE ( 'ql' )
1514                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1515                   ql(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =             &
1516                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1517
1518                CASE ( 'ql_av' )
1519                   IF ( .NOT. ALLOCATED( ql_av ) )  THEN
1520                      ALLOCATE( ql_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1521                   ENDIF
1522                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1523                   ql_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1524                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1525
1526                CASE ( 'ql_c_av' )
1527                   IF ( .NOT. ALLOCATED( ql_c_av ) )  THEN
1528                      ALLOCATE( ql_c_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1529                   ENDIF
1530                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1531                   ql_c_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =        &
1532                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1533
1534                CASE ( 'ql_v_av' )
1535                   IF ( .NOT. ALLOCATED( ql_v_av ) )  THEN
1536                      ALLOCATE( ql_v_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1537                   ENDIF
1538                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1539                   ql_v_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =        &
1540                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1541
1542                CASE ( 'ql_vp_av' )
1543                   IF ( .NOT. ALLOCATED( ql_vp_av ) )  THEN
1544                      ALLOCATE( ql_vp_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1545                   ENDIF
1546                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1547                   ql_vp_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =       &
1548                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1549
1550                CASE ( 'qsws_av' )
1551                   IF ( .NOT. ALLOCATED( qsws_av ) )  THEN
1552                      ALLOCATE( qsws_av(nysg:nyng,nxlg:nxrg) )
1553                   ENDIF 
1554                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1555                   qsws_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =         &
1556                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1557
1558                CASE ( 'qv_av' )
1559                   IF ( .NOT. ALLOCATED( qv_av ) )  THEN
1560                      ALLOCATE( qv_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1561                   ENDIF
1562                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1563                   qv_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =          &
1564                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1565
1566                CASE ( 'r_a_av' )
1567                   IF ( .NOT. ALLOCATED( r_a_av ) )  THEN
1568                      ALLOCATE( r_a_av(nysg:nyng,nxlg:nxrg) )
1569                   ENDIF
1570                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1571                   r_a_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1572                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1573
1574                CASE ( 'random_iv' )  ! still unresolved issue
1575                   IF ( k == 1 )  READ ( 13 )  random_iv
1576                   IF ( k == 1 )  READ ( 13 )  random_iy
1577
1578                CASE ( 'seq_random_array' )
1579                   ALLOCATE( tmp_2d_id_random(nys_on_file:nyn_on_file,         &
1580                                              nxl_on_file:nxr_on_file) )
1581                   ALLOCATE( tmp_2d_seq_random(5,nys_on_file:nyn_on_file,      &
1582                                                 nxl_on_file:nxr_on_file) )
1583                   IF ( .NOT. ALLOCATED( id_random_array ) )  THEN
1584                      ALLOCATE( id_random_array(nys:nyn,nxl:nxr) )
1585                   ENDIF
1586                   IF ( .NOT. ALLOCATED( seq_random_array ) )  THEN
1587                      ALLOCATE( seq_random_array(5,nys:nyn,nxl:nxr) )
1588                   ENDIF
1589                   IF ( k == 1 )  READ ( 13 )  tmp_2d_id_random
1590                   IF ( k == 1 )  READ ( 13 )  tmp_2d_seq_random
1591                   id_random_array(nysc:nync,nxlc:nxrc) =                      &
1592                      tmp_2d_id_random(nysf:nynf,nxlf:nxrf)
1593                   seq_random_array(:,nysc:nync,nxlc:nxrc) =                   &
1594                      tmp_2d_seq_random(:,nysf:nynf,nxlf:nxrf)
1595                   DEALLOCATE( tmp_2d_id_random, tmp_2d_seq_random )
1596
1597                CASE ( 's' )
1598                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1599                   s(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =              &
1600                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1601
1602                CASE ( 's_av' )
1603                   IF ( .NOT. ALLOCATED( s_av ) )  THEN
1604                      ALLOCATE( s_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg))
1605                   ENDIF
1606                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1607                   s_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1608                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1609
1610                CASE ( 'shf_av' )
1611                   IF ( .NOT. ALLOCATED( shf_av ) )  THEN
1612                      ALLOCATE( shf_av(nysg:nyng,nxlg:nxrg) )
1613                   ENDIF
1614                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1615                   shf_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =          &
1616                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1617                   
1618                CASE ( 'ssws_av' )
1619                   IF ( .NOT. ALLOCATED( ssws_av ) )  THEN
1620                      ALLOCATE( ssws_av(nysg:nyng,nxlg:nxrg) )
1621                   ENDIF 
1622                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1623                   ssws_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =         &
1624                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1625                 
1626                CASE ( 'ts_av' )
1627                   IF ( .NOT. ALLOCATED( ts_av ) )  THEN
1628                      ALLOCATE( ts_av(nysg:nyng,nxlg:nxrg) )
1629                   ENDIF
1630                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1631                   ts_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =           &
1632                        tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1633
1634                CASE ( 'tsurf_av' )
1635                   IF ( .NOT. ALLOCATED( tsurf_av ) )  THEN
1636                      ALLOCATE( tsurf_av(nysg:nyng,nxlg:nxrg) )
1637                   ENDIF
1638                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1639                   tsurf_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =         &
1640                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1641
1642                CASE ( 'u' )
1643                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1644                   u(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =              &
1645                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1646
1647                CASE ( 'u_av' )
1648                   IF ( .NOT. ALLOCATED( u_av ) )  THEN
1649                      ALLOCATE( u_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1650                   ENDIF
1651                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1652                   u_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1653                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1654
1655                CASE ( 'u_m_l' )
1656                   IF ( k == 1 )  THEN
1657                      ALLOCATE( tmp_3dwul(nzb:nzt+1,                           &
1658                                nys_on_file-nbgp:nyn_on_file+nbgp,1:2) )
1659                      READ ( 13 )  tmp_3dwul
1660                   ENDIF
1661                   IF ( bc_radiation_l )  THEN
1662                      u_m_l(:,nysc-nbgp:nync+nbgp,:) =                         & 
1663                         tmp_3dwul(:,nysf-nbgp:nynf+nbgp,:)
1664                   ENDIF
1665
1666                CASE ( 'u_m_n' )
1667                   IF ( k == 1 )  THEN
1668                      ALLOCATE( tmp_3dwun(nzb:nzt+1,ny-1:ny,                   &
1669                                          nxl_on_file-nbgp:nxr_on_file+nbgp) )
1670                      READ ( 13 )  tmp_3dwun
1671                   ENDIF
1672                   IF ( bc_radiation_n )  THEN
1673                      u_m_n(:,:,nxlc-nbgp:nxrc+nbgp) =                         & 
1674                         tmp_3dwun(:,:,nxlf-nbgp:nxrf+nbgp)
1675                   ENDIF
1676
1677                CASE ( 'u_m_r' )
1678                   IF ( k == 1 )  THEN
1679                      ALLOCATE( tmp_3dwur(nzb:nzt+1,                           &
1680                                nys_on_file-nbgp:nyn_on_file+nbgp,nx-1:nx) )
1681                      READ ( 13 )  tmp_3dwur
1682                   ENDIF
1683                   IF ( bc_radiation_r )  THEN
1684                      u_m_r(:,nysc-nbgp:nync+nbgp,:) =                         & 
1685                         tmp_3dwur(:,nysf-nbgp:nynf+nbgp,:)
1686                   ENDIF
1687
1688                CASE ( 'u_m_s' )
1689                   IF ( k == 1 )  THEN
1690                      ALLOCATE( tmp_3dwus(nzb:nzt+1,0:1,                       &
1691                                          nxl_on_file-nbgp:nxr_on_file+nbgp) )
1692                      READ ( 13 )  tmp_3dwus
1693                   ENDIF
1694                   IF ( bc_radiation_s )  THEN
1695                      u_m_s(:,:,nxlc-nbgp:nxrc+nbgp) =                         &
1696                         tmp_3dwus(:,:,nxlf-nbgp:nxrf+nbgp)
1697                   ENDIF
1698
1699                CASE ( 'us_av' )
1700                   IF ( .NOT. ALLOCATED( us_av ) )  THEN
1701                      ALLOCATE( us_av(nysg:nyng,nxlg:nxrg) )
1702                   ENDIF
1703                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1704                   us_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =           &
1705                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1706
1707                CASE ( 'v' )
1708                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1709                   v(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =              &
1710                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1711
1712                CASE ( 'v_av' )
1713                   IF ( .NOT. ALLOCATED( v_av ) )  THEN
1714                      ALLOCATE( v_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1715                   ENDIF
1716                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1717                   v_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1718                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1719
1720                CASE ( 'v_m_l' )
1721                   IF ( k == 1 )  THEN
1722                      ALLOCATE( tmp_3dwvl(nzb:nzt+1,                           &
1723                                nys_on_file-nbgp:nyn_on_file+nbgp,0:1) )
1724                      READ ( 13 )  tmp_3dwvl
1725                   ENDIF
1726                   IF ( bc_radiation_l )  THEN
1727                      v_m_l(:,nysc-nbgp:nync+nbgp,:) =                         & 
1728                         tmp_3dwvl(:,nysf-nbgp:nynf+nbgp,:)
1729                   ENDIF
1730
1731                CASE ( 'v_m_n' )
1732                   IF ( k == 1 )  THEN
1733                      ALLOCATE( tmp_3dwvn(nzb:nzt+1,ny-1:ny,                   &
1734                                          nxl_on_file-nbgp:nxr_on_file+nbgp) )
1735                      READ ( 13 )  tmp_3dwvn
1736                   ENDIF
1737                   IF ( bc_radiation_n )  THEN
1738                      v_m_n(:,:,nxlc-nbgp:nxrc+nbgp) =                         &
1739                         tmp_3dwvn(:,:,nxlf-nbgp:nxrf+nbgp)
1740                   ENDIF
1741
1742                CASE ( 'v_m_r' )
1743                   IF ( k == 1 )  THEN
1744                      ALLOCATE( tmp_3dwvr(nzb:nzt+1,                           &
1745                                nys_on_file-nbgp:nyn_on_file+nbgp,nx-1:nx) )
1746                      READ ( 13 )  tmp_3dwvr
1747                   ENDIF
1748                   IF ( bc_radiation_r )  THEN
1749                      v_m_r(:,nysc-nbgp:nync+nbgp,:) =                         &
1750                         tmp_3dwvr(:,nysf-nbgp:nynf+nbgp,:)
1751                   ENDIF
1752
1753                CASE ( 'v_m_s' )
1754                   IF ( k == 1 )  THEN
1755                      ALLOCATE( tmp_3dwvs(nzb:nzt+1,1:2,                       &
1756                                          nxl_on_file-nbgp:nxr_on_file+nbgp) )
1757                      READ ( 13 )  tmp_3dwvs
1758                   ENDIF
1759                   IF ( bc_radiation_s )  THEN
1760                      v_m_s(:,:,nxlc-nbgp:nxrc+nbgp) =                         &
1761                         tmp_3dwvs(:,:,nxlf-nbgp:nxrf+nbgp)
1762                   ENDIF
1763
1764                CASE ( 'vpt' )
1765                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1766                   vpt(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =            &
1767                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1768
1769                CASE ( 'vpt_av' )
1770                   IF ( .NOT. ALLOCATED( vpt_av ) )  THEN
1771                      ALLOCATE( vpt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1772                   ENDIF
1773                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1774                   vpt_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =         &
1775                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1776
1777                CASE ( 'w' )
1778                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1779                   w(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =              &
1780                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1781
1782                CASE ( 'w_av' )
1783                   IF ( .NOT. ALLOCATED( w_av ) )  THEN
1784                      ALLOCATE( w_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1785                   ENDIF
1786                   IF ( k == 1 )  READ ( 13 )  tmp_3d
1787                   w_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =           &
1788                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1789
1790                CASE ( 'w_m_l' )
1791                   IF ( k == 1 )  THEN
1792                      ALLOCATE( tmp_3dwwl(nzb:nzt+1,&
1793                                nys_on_file-nbgp:nyn_on_file+nbgp,0:1) )
1794                      READ ( 13 )  tmp_3dwwl
1795                   ENDIF
1796                   IF ( bc_radiation_l )  THEN
1797                      w_m_l(:,nysc-nbgp:nync+nbgp,:) =                         & 
1798                         tmp_3dwwl(:,nysf-nbgp:nynf+nbgp,:)
1799                   ENDIF
1800
1801                CASE ( 'w_m_n' )
1802                   IF ( k == 1 )  THEN
1803                      ALLOCATE( tmp_3dwwn(nzb:nzt+1,ny-1:ny, &
1804                                          nxl_on_file-nbgp:nxr_on_file+nbgp) )
1805                      READ ( 13 )  tmp_3dwwn
1806                   ENDIF
1807                   IF ( bc_radiation_n )  THEN
1808                      w_m_n(:,:,nxlc-nbgp:nxrc+nbgp) =                         &
1809                         tmp_3dwwn(:,:,nxlf-nbgp:nxrf+nbgp)
1810                   ENDIF
1811
1812                CASE ( 'w_m_r' )
1813                   IF ( k == 1 )  THEN
1814                      ALLOCATE( tmp_3dwwr(nzb:nzt+1,&
1815                                nys_on_file-nbgp:nyn_on_file+nbgp,nx-1:nx) )
1816                      READ ( 13 )  tmp_3dwwr
1817                   ENDIF
1818                   IF ( bc_radiation_r )  THEN
1819                      w_m_r(:,nysc-nbgp:nync+nbgp,:) =                         & 
1820                         tmp_3dwwr(:,nysf-nbgp:nynf+nbgp,:)
1821                   ENDIF
1822
1823                CASE ( 'w_m_s' )
1824                   IF ( k == 1 )  THEN
1825                      ALLOCATE( tmp_3dwws(nzb:nzt+1,0:1, &
1826                                          nxl_on_file-nbgp:nxr_on_file+nbgp) )
1827                      READ ( 13 )  tmp_3dwws
1828                   ENDIF
1829                   IF ( bc_radiation_s )  THEN
1830                      w_m_s(:,:,nxlc-nbgp:nxrc+nbgp) =                         & 
1831                         tmp_3dwws(:,:,nxlf-nbgp:nxrf+nbgp)
1832                   ENDIF
1833
1834                CASE ( 'z0_av' )
1835                   IF ( .NOT. ALLOCATED( z0_av ) )  THEN
1836                      ALLOCATE( z0_av(nysg:nyng,nxlg:nxrg) )
1837                   ENDIF
1838                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1839                   z0_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =           &
1840                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1841
1842                CASE ( 'z0h_av' )
1843                   IF ( .NOT. ALLOCATED( z0h_av ) )  THEN
1844                      ALLOCATE( z0h_av(nysg:nyng,nxlg:nxrg) )
1845                   ENDIF
1846                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1847                   z0h_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =          &
1848                       tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1849
1850                CASE ( 'z0q_av' )
1851                   IF ( .NOT. ALLOCATED( z0q_av ) )  THEN
1852                      ALLOCATE( z0q_av(nysg:nyng,nxlg:nxrg) )
1853                   ENDIF
1854                   IF ( k == 1 )  READ ( 13 )  tmp_2d
1855                   z0q_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =          &
1856                       tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
1857
1858                CASE DEFAULT
1859
1860!
1861!--                Read restart data of other modules
1862                   IF ( .NOT. found ) CALL bcm_rrd_local( i, k, nxlf,          &
1863                                           nxlc, nxl_on_file, nxrf, nxrc,      &
1864                                           nxr_on_file, nynf, nync,            &
1865                                           nyn_on_file, nysf, nysc,            &
1866                                           nys_on_file, tmp_2d, tmp_3d, found )
1867
1868                   IF ( .NOT. found ) CALL chem_rrd_local( i, k, nxlf,         &
1869                                           nxlc, nxl_on_file, nxrf, nxrc,      &
1870                                           nxr_on_file, nynf, nync,            & 
1871                                           nyn_on_file, nysf, nysc,            &
1872                                           nys_on_file, tmp_3d, found )
1873
1874                   IF ( .NOT. found ) CALL gust_rrd_local( i, k, nxlf,         &
1875                                           nxlc, nxl_on_file, nxrf, nxrc,      &
1876                                           nxr_on_file, nynf, nync,            &
1877                                           nyn_on_file, nysf, nysc,            &
1878                                           nys_on_file, tmp_2d, tmp_3d, found )
1879
1880                   IF ( .NOT. found ) CALL lsm_rrd_local( i, k, nxlf,          & 
1881                                           nxlc, nxl_on_file, nxrf, nxrc,      &
1882                                           nxr_on_file, nynf, nync,            &
1883                                           nyn_on_file, nysf, nysc,            &
1884                                           nys_on_file, tmp_2d, found )
1885
1886                   IF ( .NOT. found ) CALL ocean_rrd_local( i, k, nxlf,        &
1887                                           nxlc, nxl_on_file, nxrf, nxrc,      &
1888                                           nxr_on_file, nynf, nync,            &
1889                                           nyn_on_file, nysf, nysc,            &
1890                                           nys_on_file, tmp_2d, tmp_3d, found )
1891
1892                   IF ( .NOT. found ) CALL radiation_rrd_local( i, k, nxlf,    &
1893                                           nxlc, nxl_on_file, nxrf, nxrc,      &
1894                                           nxr_on_file, nynf, nync,            &
1895                                           nyn_on_file, nysf, nysc,            &
1896                                           nys_on_file, tmp_2d, tmp_3d, found )
1897
1898                   IF ( .NOT. found ) CALL surface_rrd_local( i, k, nxlf,      &
1899                                           nxlc, nxl_on_file, nxrf, nxrc,      &
1900                                           nxr_on_file, nynf, nync,            & 
1901                                           nyn_on_file, nysf, nysc,            &
1902                                           nys_on_file, found )
1903
1904                   IF ( .NOT. found ) CALL usm_rrd_local( i, k, nxlf,          &
1905                                           nxlc, nxl_on_file, nxrf, nxrc,      &
1906                                           nxr_on_file, nynf, nync,            &
1907                                           nyn_on_file, nysf, nysc,            &
1908                                           nys_on_file, found )
1909
1910!
1911!--                Read user-defined restart data
1912                   IF ( .NOT. found ) CALL user_rrd_local( i, k, nxlf,         &
1913                                           nxlc, nxl_on_file, nxrf, nxrc,      &
1914                                           nxr_on_file, nynf, nync,            &
1915                                           nyn_on_file, nysf, nysc,            &
1916                                           nys_on_file, tmp_3d, found )
1917
1918
1919                   IF ( .NOT. found )  THEN
1920                      WRITE( message_string, * ) 'unknown variable named "',   &
1921                                                 restart_string(1:length),     &
1922                                                '" found in subdomain data ',  & 
1923                                                'from prior run on PE ', myid
1924                      CALL message( 'rrd_local', 'PA0302', 1, 2, 0, 6, 0 )
1925 
1926                   ENDIF
1927
1928             END SELECT
1929
1930          ENDDO ! overlaploop
1931
1932!
1933!--       Deallocate arrays needed for specific variables only
1934          IF ( ALLOCATED( tmp_3dwul ) )  DEALLOCATE( tmp_3dwul )
1935          IF ( ALLOCATED( tmp_3dwun ) )  DEALLOCATE( tmp_3dwun )
1936          IF ( ALLOCATED( tmp_3dwur ) )  DEALLOCATE( tmp_3dwur )
1937          IF ( ALLOCATED( tmp_3dwus ) )  DEALLOCATE( tmp_3dwus )
1938          IF ( ALLOCATED( tmp_3dwvl ) )  DEALLOCATE( tmp_3dwvl )
1939          IF ( ALLOCATED( tmp_3dwvn ) )  DEALLOCATE( tmp_3dwvn )
1940          IF ( ALLOCATED( tmp_3dwvr ) )  DEALLOCATE( tmp_3dwvr )
1941          IF ( ALLOCATED( tmp_3dwvs ) )  DEALLOCATE( tmp_3dwvs )
1942          IF ( ALLOCATED( tmp_3dwwl ) )  DEALLOCATE( tmp_3dwwl )
1943          IF ( ALLOCATED( tmp_3dwwn ) )  DEALLOCATE( tmp_3dwwn )
1944          IF ( ALLOCATED( tmp_3dwwr ) )  DEALLOCATE( tmp_3dwwr )
1945          IF ( ALLOCATED( tmp_3dwws ) )  DEALLOCATE( tmp_3dwws )
1946
1947!
1948!--       Read next character string
1949          READ ( 13 )  length
1950          READ ( 13 )  restart_string(1:length)
1951
1952       ENDDO ! dataloop
1953
1954!
1955!--    Close the restart file
1956       CALL close_file( 13 )
1957
1958       DEALLOCATE( tmp_2d, tmp_3d )
1959
1960    ENDDO  ! loop over restart files
1961
1962
1963!
1964!-- Restore the original filename for the restart file to be written
1965    myid_char = myid_char_save
1966
1967!
1968!-- End of time measuring for reading binary data
1969    CALL cpu_log( log_point_s(14), 'rrd_local', 'stop' )
1970
1971 END SUBROUTINE rrd_local
1972
1973
1974!------------------------------------------------------------------------------!
1975! Description:
1976! ------------
1977!> Skipping the global control variables from restart-file (binary format)
1978!------------------------------------------------------------------------------!
1979
1980    SUBROUTINE rrd_skip_global
1981
1982
1983       IMPLICIT NONE
1984
1985       CHARACTER (LEN=1) ::  cdum
1986
1987
1988       READ ( 13 )  length
1989       READ ( 13 )  restart_string(1:length)
1990
1991       DO  WHILE ( restart_string(1:length) /= 'binary_version_local' )
1992
1993          READ ( 13 )  cdum
1994          READ ( 13 )  length 
1995          READ ( 13 )  restart_string(1:length)
1996
1997       ENDDO
1998
1999       BACKSPACE ( 13 )
2000       BACKSPACE ( 13 )
2001
2002
2003    END SUBROUTINE rrd_skip_global
2004
2005
2006 END MODULE read_restart_data_mod
Note: See TracBrowser for help on using the repository browser.