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

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