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

Last change on this file since 3291 was 3289, checked in by suehring, 6 years ago

last commit documented

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