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

Last change on this file since 3766 was 3766, checked in by raasch, 5 years ago

unused_variables removed, bugfix in im_define_netcdf_grid argument list, trim added to avoid truncation compiler warnings, save attribute added to local targets to avoid outlive pointer target warning, first argument removed from module_interface_rrd_*, file module_interface reformatted with respect to coding standards, bugfix in surface_data_output_rrd_local (variable k removed)

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