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

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

Bugfix in allocation of mean_inflow_profiles in case of restarts

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