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

Last change on this file since 2938 was 2921, checked in by Giersch, 6 years ago

further inipar parameter has been added to restart data, bugfix in spinup mechanism

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