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

Last change on this file since 4517 was 4517, checked in by raasch, 4 years ago

added restart with MPI-IO for reading local arrays

  • Property svn:keywords set to Id
File size: 118.0 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!
[4360]17! Copyright 1997-2020 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 4517 2020-05-03 14:29:30Z raasch $
[4514]27! qsurf and ssurf added
28!
29! 4498 2020-04-15 14:26:31Z raasch
[4498]30! argument removed from rd_mpi_io_open
31!
32! 4496 2020-04-15 08:37:26Z raasch
[4496]33! bugfix: MPI barrier removed, coupling character added to input filename
34!
35! 4495 2020-04-13 20:11:20Z raasch
[4495]36! restart data handling with MPI-IO added
37!
38! 4435 2020-03-03 10:38:41Z raasch
[4435]39! bugfix for message that reports about files that are read from in case that the virtual PE grid
40! has chenged (in case of large number of files format was exceeded), detailed messages about the
41! files are now output to the debug file
42!
43! 4431 2020-02-27 23:23:01Z gronemeier
[4431]44! added u_center_av, v_center_av, wspeed_av
45!
46! 4360 2020-01-07 11:25:50Z suehring
[4356]47! Change automatic arrays to allocatable ones in rrd_local, in order to avoid
[4431]48! memory problems due to too small stack size for large jobs with intel
[4356]49! compiler. (J.Resler)
[4431]50!
[4356]51! 4331 2019-12-10 18:25:02Z suehring
[4331]52! Enable restart data for 2-m potential temperature output
[4431]53!
[4331]54! 4301 2019-11-22 12:09:09Z oliver.maas
[4301]55! removed recycling_yshift
[4431]56!
[4301]57! 4227 2019-09-10 18:04:34Z gronemeier
[4227]58! implement new palm_date_time_mod and increased binary version
[4431]59!
[4227]60! 4146 2019-08-07 07:47:36Z gronemeier
[4182]61! Corrected "Former revisions" section
[4431]62!
[4182]63! 4131 2019-08-02 11:06:18Z monakurppa
[4131]64! Allocate hom and hom_sum to allow profile output for salsa variables.
[4431]65!
[4131]66! 4101 2019-07-17 15:14:26Z gronemeier
[4101]67! remove old_dt
[4431]68!
[4101]69! 4039 2019-06-18 10:32:41Z suehring
[4039]70! input of uu_av, vv_av, ww_av added
[4431]71!
[4039]72! 4017 2019-06-06 12:16:46Z schwenkel
[4009]73! bugfix for r3998, allocation of 3d temporary arrays of various dimensions revised
[4431]74!
[4009]75! 3998 2019-05-23 13:38:11Z suehring
[3998]76! Formatting adjustment
[4431]77!
[3998]78! 3994 2019-05-22 18:08:09Z suehring
[3994]79! output of turbulence intensity added
[4431]80!
[3994]81! 3988 2019-05-22 11:32:37Z kanani
[3988]82! + time_virtual_measurement (to enable steering of output interval)
[4431]83!
[3988]84! 3936 2019-04-26 15:38:02Z kanani
[3936]85! Enable time-averaged output of theta_2m* with restarts
[4431]86!
[3936]87! 3767 2019-02-27 08:18:02Z raasch
[3767]88! unused variables removed from rrd-subroutines parameter list
[4431]89!
[3767]90! 3766 2019-02-26 16:23:41Z raasch
[3766]91! first argument removed from module_interface_rrd_*
[4431]92!
[3766]93! 3668 2019-01-14 12:49:24Z maronga
[3668]94! Removed most_method and increased binary version
[4431]95!
[3668]96! 3655 2019-01-07 16:51:22Z knoop
[3637]97! Implementation of the PALM module interface
[4431]98!
[4182]99! 2894 2018-03-15 09:17:58Z Giersch
100! Initial revision
[2894]101!
[4431]102!
[2894]103! Description:
104! ------------
105!> Reads restart data from restart-file(s) (binary format).
[3298]106!>
107!> @todo: Revise max_pr_cs (profiles for chemistry)
[4039]108!> @todo: Modularize reading of restart data for diagnostic quantities, which
109!>        is not possible with the current module-interface structure
[2894]110!------------------------------------------------------------------------------!
111 MODULE read_restart_data_mod
112
113
[3637]114    USE arrays_3d,                                                             &
115        ONLY:  inflow_damping_factor, mean_inflow_profiles, pt_init,           &
116               q_init, ref_state, sa_init, s_init, u_init, ug, v_init, vg,     &
117               e, kh, km, p, pt, q, ql, s, u, u_m_l, u_m_n, u_m_r, u_m_s,      &
118               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]119
[3637]120    USE averaging
121
[4495]122    USE bulk_cloud_model_mod,                                                                      &
123        ONLY:  bulk_cloud_model
124
[3298]125    USE chem_modules,                                                                              &
126       ONLY: max_pr_cs
127
[3637]128    USE control_parameters
[3298]129
[3637]130    USE cpulog,                                                                &
131        ONLY:  cpu_log, log_point_s
132
[3994]133    USE diagnostic_output_quantities_mod,                                      &
[4331]134        ONLY:  pt_2m_av,                                                       &
135               ti_av,                                                          &
[4431]136               u_center_av,                                                    &
[4331]137               uu_av,                                                          &
138               uv_10m_av,                                                      &
[4431]139               v_center_av,                                                    &
[4331]140               vv_av,                                                          &
[4431]141               wspeed_av,                                                      &
[4331]142               ww_av
[3994]143
[3637]144    USE grid_variables,                                                        &
145        ONLY:  dx, dy
146
[4495]147    USE gust_mod,                                                                                  &
148        ONLY:  gust_module_enabled
149
[3637]150    USE indices,                                                               &
151        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, nx_on_file, ny, nys, nysg, nyn, &
152               nyng, ny_on_file, nz, nzb, nzt
153
154    USE kinds
155
156    USE model_1d_mod,                                                          &
157        ONLY:  damp_level_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
158
159    USE module_interface,                                                      &
160        ONLY:  module_interface_rrd_global,                                    &
161               module_interface_rrd_local
162
163    USE netcdf_interface,                                                      &
164        ONLY:  netcdf_precision, output_for_t0
165
[4495]166    USE particle_attributes,                                                                       &
167        ONLY:  particle_advection
168
[3637]169    USE pegrid
170
171    USE radiation_model_mod,                                                   &
172        ONLY:  time_radiation
173
174    USE random_function_mod,                                                   &
175        ONLY:  random_iv, random_iy
176
177    USE random_generator_parallel,                                             &
178        ONLY:  id_random_array, seq_random_array
179
[4495]180    USE restart_data_mpi_io_mod,                                                                   &
181        ONLY:  rd_mpi_io_check_array, rd_mpi_io_close, rd_mpi_io_open, rrd_mpi_io,                 &
182               rrd_mpi_io_global_array
183
[3637]184    USE spectra_mod,                                                           &
185        ONLY:  average_count_sp, spectrum_x, spectrum_y
186
187    USE surface_mod,                                                           &
188        ONLY :  surface_rrd_local
189
190    USE statistics,                                                            &
191        ONLY:  statistic_regions, hom, hom_sum, pr_palm, u_max, u_max_ijk,     &
192               v_max, v_max_ijk, w_max, w_max_ijk, z_i
193
[4495]194    USE user,                                                                                      &
195        ONLY:  user_module_enabled
196
[3637]197    USE vertical_nesting_mod,                                                  &
198        ONLY:  vnest_init
199
[3988]200    USE virtual_measurement_mod,                                               &
201        ONLY:  time_virtual_measurement
[3637]202
[3988]203
[2894]204    IMPLICIT NONE
205
206
207    INTERFACE rrd_global
208       MODULE PROCEDURE rrd_global
209    END INTERFACE rrd_global
210
211    INTERFACE rrd_read_parts_of_global
212       MODULE PROCEDURE rrd_read_parts_of_global
213    END INTERFACE rrd_read_parts_of_global
214
215    INTERFACE rrd_local
216       MODULE PROCEDURE rrd_local
217    END INTERFACE rrd_local
218
219    INTERFACE rrd_skip_global
220       MODULE PROCEDURE rrd_skip_global
221    END INTERFACE rrd_skip_global
222
223
[3294]224    PUBLIC rrd_global, rrd_read_parts_of_global, rrd_local, rrd_skip_global
[2894]225
226
227 CONTAINS
228
[3294]229!------------------------------------------------------------------------------!
[2894]230! Description:
231! ------------
[4431]232!> Reads values of global control variables from restart-file (binary format)
[2894]233!> created by PE0 of the previous run
234!------------------------------------------------------------------------------!
[4495]235 SUBROUTINE rrd_global
[2894]236
237
[4495]238    CHARACTER(LEN=10) ::  binary_version_global  !<
239    CHARACTER(LEN=10) ::  version_on_file        !<
240    CHARACTER(LEN=20) ::  tmp_name               !< temporary variable
[2894]241
[4495]242    INTEGER ::  i                                !< loop index
[2894]243
[4495]244    LOGICAL ::  array_found                      !<
245    LOGICAL ::  found                            !<
[2894]246
[4495]247
248    CALL location_message( 'read global restart data', 'start' )
249
250    IF ( TRIM( restart_data_format_input ) == 'fortran_binary' )  THEN
251!
252!--    Input in Fortran binary format
[2894]253       CALL check_open( 13 )
254!
[3294]255!--    Make version number check first
[2894]256       READ ( 13 )  length
257       READ ( 13 )  restart_string(1:length)
258       READ ( 13 )  version_on_file
259
[4227]260       binary_version_global = '4.9'
[2894]261       IF ( TRIM( version_on_file ) /= TRIM( binary_version_global ) )  THEN
[3045]262          WRITE( message_string, * ) 'version mismatch concerning ',           &
263                                     'binary_version_global:',                 &
[3046]264                                     '&version on file    = "',                &
[2894]265                                     TRIM( version_on_file ), '"',             &
[3046]266                                     '&version on program = "',                &
[2894]267                                     TRIM( binary_version_global ), '"'
268          CALL message( 'rrd_global', 'PA0296', 1, 2, 0, 6, 0 )
269       ENDIF
270
271!
[3294]272!--    Read number of PEs and horizontal index bounds of all PEs used in the
273!--    previous run
[2894]274       READ ( 13 )  length
275       READ ( 13 )  restart_string(1:length)
276
277       IF ( TRIM( restart_string(1:length) ) /= 'numprocs' )  THEN
278          WRITE( message_string, * ) 'numprocs not found in data from prior ', &
279                                     'run on PE ', myid
280          CALL message( 'rrd_global', 'PA0297', 1, 2, 0, 6, 0 )
281       ENDIF
282       READ ( 13 )  numprocs_previous_run
283
284       IF ( .NOT. ALLOCATED( hor_index_bounds_previous_run ) )  THEN
285          ALLOCATE( hor_index_bounds_previous_run(4,0:numprocs_previous_run-1) )
286       ENDIF
287
288       READ ( 13 )  length
289       READ ( 13 )  restart_string(1:length)
290
291       IF ( restart_string(1:length) /= 'hor_index_bounds' )  THEN
292          WRITE( message_string, * ) 'hor_index_bounds not found in data ',    &
293                                     'from prior run on PE ', myid
294          CALL message( 'rrd_global', 'PA0298', 1, 2, 0, 6, 0 )
295       ENDIF
296       READ ( 13 )  hor_index_bounds_previous_run
297
298!
[3294]299!--    Read vertical number of gridpoints and number of different areas used
300!--    for computing statistics. Allocate arrays depending on these values,
301!--    which are needed for the following read instructions.
[2894]302       READ ( 13 )  length
303       READ ( 13 )  restart_string(1:length)
304
305       IF ( restart_string(1:length) /= 'nz' )  THEN
306          WRITE( message_string, * ) 'nz not found in data from prior run ',   &
307                                     'on PE ', myid
308          CALL message( 'rrd_global', 'PA0299', 1, 2, 0, 6, 0 )
309       ENDIF
310       READ ( 13 )  nz
311
312       READ ( 13 )  length
313       READ ( 13 )  restart_string(1:length)
314
315       IF ( restart_string(1:length) /= 'max_pr_user' )  THEN
316          WRITE( message_string, * ) 'max_pr_user not found in data from ',    &
317                                     'prior run on PE ', myid
318          CALL message( 'rrd_global', 'PA0300', 1, 2, 0, 6, 0 )
319       ENDIF
320       READ ( 13 )  max_pr_user    ! This value is checked against the number of
321                                   ! user profiles given for the current run
322                                   ! in routine user_parin (it has to match)
323
324       READ ( 13 )  length
325       READ ( 13 )  restart_string(1:length)
326
327       IF ( restart_string(1:length) /= 'statistic_regions' )  THEN
328          WRITE( message_string, * ) 'statistic_regions not found in data ',   &
329                                     'from prior run on PE ', myid
330          CALL message( 'rrd_global', 'PA0301', 1, 2, 0, 6, 0 )
331       ENDIF
332       READ ( 13 )  statistic_regions
[3294]333
[4495]334!
335!--    The following global arrays (better to say, they have the same size and values on each
336!--    subdomain) are by default allocated in routine parin, but not in case of restarts!
[2894]337       IF ( .NOT. ALLOCATED( ug ) )  THEN
[4495]338          ALLOCATE( ug(0:nz+1), u_init(0:nz+1), vg(0:nz+1),                                        &
339                    v_init(0:nz+1), pt_init(0:nz+1), q_init(0:nz+1),                               &
340                    ref_state(0:nz+1), s_init(0:nz+1), sa_init(0:nz+1),                            &
[4131]341                    hom(0:nz+1,2,pr_palm+max_pr_user+max_pr_cs+max_pr_salsa,0:statistic_regions),  &
342                    hom_sum(0:nz+1,pr_palm+max_pr_user+max_pr_cs+max_pr_salsa,0:statistic_regions) )
[2894]343       ENDIF
344
345!
[3294]346!--    Now read all control parameters:
347!--    Caution: When the following read instructions have been changed, the
348!--    -------  version number stored in the variable binary_version_global has
349!--             to be increased. The same changes must also be done in
350!--             wrd_write_global.
[2894]351       READ ( 13 )  length
352       READ ( 13 )  restart_string(1:length)
353
354       DO WHILE ( restart_string(1:length) /= 'binary_version_local' )
355
356          found = .FALSE.
357
358          SELECT CASE ( restart_string(1:length) )
359
360             CASE ( 'advected_distance_x' )
361                READ ( 13 )  advected_distance_x
362             CASE ( 'advected_distance_y' )
363                READ ( 13 )  advected_distance_y
364             CASE ( 'alpha_surface' )
365                READ ( 13 )  alpha_surface
366             CASE ( 'average_count_pr' )
367                READ ( 13 )  average_count_pr
368             CASE ( 'average_count_sp' )
369                READ ( 13 )  average_count_sp
370             CASE ( 'average_count_3d' )
371                READ ( 13 )  average_count_3d
372             CASE ( 'bc_e_b' )
373                READ ( 13 )  bc_e_b
374             CASE ( 'bc_lr' )
375                READ ( 13 )  bc_lr
376             CASE ( 'bc_ns' )
377                READ ( 13 )  bc_ns
378             CASE ( 'bc_p_b' )
379                READ ( 13 )  bc_p_b
380             CASE ( 'bc_p_t' )
381                READ ( 13 )  bc_p_t
382             CASE ( 'bc_pt_b' )
383                READ ( 13 )  bc_pt_b
384             CASE ( 'bc_pt_t' )
385                READ ( 13 )  bc_pt_t
386             CASE ( 'bc_pt_t_val' )
387                READ ( 13 )  bc_pt_t_val
388             CASE ( 'bc_q_b' )
389                READ ( 13 )  bc_q_b
390             CASE ( 'bc_q_t' )
391                READ ( 13 )  bc_q_t
392             CASE ( 'bc_q_t_val' )
393                READ ( 13 )  bc_q_t_val
394             CASE ( 'bc_s_b' )
395                READ ( 13 )  bc_s_b
396             CASE ( 'bc_s_t' )
397                READ ( 13 )  bc_s_t
398             CASE ( 'bc_uv_b' )
399                READ ( 13 )  bc_uv_b
400             CASE ( 'bc_uv_t' )
401                READ ( 13 )  bc_uv_t
402             CASE ( 'building_height' )
403                READ ( 13 )  building_height
404             CASE ( 'building_length_x' )
405                READ ( 13 )  building_length_x
406             CASE ( 'building_length_y' )
407                READ ( 13 )  building_length_y
408             CASE ( 'building_wall_left' )
409                READ ( 13 )  building_wall_left
410             CASE ( 'building_wall_south' )
411                READ ( 13 )  building_wall_south
412             CASE ( 'call_psolver_at_all_substeps' )
413                READ ( 13 )  call_psolver_at_all_substeps
414             CASE ( 'canyon_height' )
415                READ ( 13 )  canyon_height
416             CASE ( 'canyon_wall_left' )
417                READ ( 13 )  canyon_wall_left
418             CASE ( 'canyon_wall_south' )
419                READ ( 13 )  canyon_wall_south
420             CASE ( 'canyon_width_x' )
421                READ ( 13 )  canyon_width_x
422             CASE ( 'canyon_width_y' )
423                READ ( 13 )  canyon_width_y
424             CASE ( 'cfl_factor' )
425                READ ( 13 )  cfl_factor
426             CASE ( 'cloud_droplets' )
427                READ ( 13 )  cloud_droplets
428             CASE ( 'collective_wait' )
429                READ ( 13 )  collective_wait
430             CASE ( 'conserve_volume_flow' )
431                READ ( 13 )  conserve_volume_flow
432             CASE ( 'conserve_volume_flow_mode' )
433                READ ( 13 )  conserve_volume_flow_mode
434             CASE ( 'constant_flux_layer' )
435                READ ( 13 )  constant_flux_layer
436             CASE ( 'coupling_start_time' )
437                READ ( 13 )  coupling_start_time
438             CASE ( 'current_timestep_number' )
439                READ ( 13 )  current_timestep_number
440             CASE ( 'cycle_mg' )
441                READ ( 13 )  cycle_mg
442             CASE ( 'damp_level_1d' )
443                READ ( 13 )  damp_level_1d
[4227]444             CASE ( 'origin_date_time' )
445                READ ( 13 )  origin_date_time
[2894]446             CASE ( 'dissipation_1d' )
447                READ ( 13 )  dissipation_1d
448             CASE ( 'do2d_xy_time_count' )
449                READ ( 13 )  do2d_xy_time_count
450             CASE ( 'do2d_xz_time_count' )
451                READ ( 13 )  do2d_xz_time_count
452             CASE ( 'do2d_yz_time_count' )
453                READ ( 13 )  do2d_yz_time_count
454             CASE ( 'do3d_time_count' )
455                READ ( 13 )  do3d_time_count
456             CASE ( 'dp_external' )
457                READ ( 13 )  dp_external
458             CASE ( 'dp_level_b' )
459                READ ( 13 )  dp_level_b
460             CASE ( 'dp_smooth' )
461                READ ( 13 )  dp_smooth
462             CASE ( 'dpdxy' )
463                READ ( 13 )  dpdxy
464             CASE ( 'dt_3d' )
465                READ ( 13 )  dt_3d
466             CASE ( 'dt_pr_1d' )
467                READ ( 13 )  dt_pr_1d
468             CASE ( 'dt_run_control_1d' )
469                READ ( 13 )  dt_run_control_1d
470             CASE ( 'dx' )
471                READ ( 13 )  dx
472             CASE ( 'dy' )
473                READ ( 13 )  dy
474             CASE ( 'dz' )
475                READ ( 13 )  dz
476             CASE ( 'dz_max' )
477                READ ( 13 )  dz_max
478             CASE ( 'dz_stretch_factor' )
479                READ ( 13 )  dz_stretch_factor
[3065]480             CASE ( 'dz_stretch_factor_array' )
481                READ ( 13 )  dz_stretch_factor_array
[2894]482             CASE ( 'dz_stretch_level' )
483                READ ( 13 )  dz_stretch_level
[3065]484             CASE ( 'dz_stretch_level_end' )
485                READ ( 13 )  dz_stretch_level_end
486             CASE ( 'dz_stretch_level_start' )
487                READ ( 13 )  dz_stretch_level_start
[2894]488             CASE ( 'e_min' )
489                READ ( 13 )  e_min
490             CASE ( 'end_time_1d' )
491                READ ( 13 )  end_time_1d
492             CASE ( 'fft_method' )
493                READ ( 13 )  fft_method
494             CASE ( 'first_call_lpm' )
495                READ ( 13 )  first_call_lpm
496             CASE ( 'galilei_transformation' )
497                READ ( 13 )  galilei_transformation
498             CASE ( 'hom' )
499                READ ( 13 )  hom
500             CASE ( 'hom_sum' )
501                READ ( 13 )  hom_sum
502             CASE ( 'humidity' )
503                READ ( 13 )  humidity
504             CASE ( 'inflow_damping_factor' )
505                IF ( .NOT. ALLOCATED( inflow_damping_factor ) )  THEN
506                   ALLOCATE( inflow_damping_factor(0:nz+1) )
507                ENDIF
508                READ ( 13 )  inflow_damping_factor
509             CASE ( 'inflow_damping_height' )
510                READ ( 13 )  inflow_damping_height
511             CASE ( 'inflow_damping_width' )
512                READ ( 13 )  inflow_damping_width
513             CASE ( 'inflow_disturbance_begin' )
514                READ ( 13 )  inflow_disturbance_begin
515             CASE ( 'inflow_disturbance_end' )
516                READ ( 13 )  inflow_disturbance_end
517             CASE ( 'km_constant' )
518                READ ( 13 )  km_constant
519             CASE ( 'large_scale_forcing' )
520                READ ( 13 )  large_scale_forcing
521             CASE ( 'large_scale_subsidence' )
522                READ ( 13 )  large_scale_subsidence
523             CASE ( 'latitude' )
524                READ ( 13 )  latitude
525             CASE ( 'longitude' )
526                READ ( 13 )  longitude
527             CASE ( 'loop_optimization' )
528                READ ( 13 )  loop_optimization
529             CASE ( 'masking_method' )
530                READ ( 13 )  masking_method
531             CASE ( 'mean_inflow_profiles' )
532                IF ( .NOT. ALLOCATED( mean_inflow_profiles ) )  THEN
[3288]533                   ALLOCATE( mean_inflow_profiles(0:nz+1,1:num_mean_inflow_profiles) )
[2894]534                ENDIF
535                READ ( 13 )  mean_inflow_profiles
536             CASE ( 'mg_cycles' )
537                READ ( 13 )  mg_cycles
538             CASE ( 'mg_switch_to_pe0_level' )
539                READ ( 13 )  mg_switch_to_pe0_level
540             CASE ( 'mixing_length_1d' )
541                READ ( 13 )  mixing_length_1d
542             CASE ( 'momentum_advec' )
543                READ ( 13 )  momentum_advec
544             CASE ( 'netcdf_precision' )
545                READ ( 13 )  netcdf_precision
546             CASE ( 'neutral' )
547                READ ( 13 )  neutral
548             CASE ( 'ngsrb' )
549                READ ( 13 )  ngsrb
550             CASE ( 'nsor' )
551                READ ( 13 )  nsor
552             CASE ( 'nsor_ini' )
553                READ ( 13 )  nsor_ini
554             CASE ( 'nudging' )
555                READ ( 13 )  nudging
556             CASE ( 'num_leg' )
557                READ ( 13 )  num_leg
558             CASE ( 'nx' )
559                READ ( 13 )  nx
560                nx_on_file = nx
561             CASE ( 'ny' )
562                READ ( 13 )  ny
563                ny_on_file = ny
[3294]564             CASE ( 'ocean_mode' )
565                READ ( 13 )  ocean_mode
[2894]566             CASE ( 'omega' )
567                READ ( 13 )  omega
568             CASE ( 'omega_sor' )
569                READ ( 13 )  omega_sor
570             CASE ( 'output_for_t0' )
571                READ (13)    output_for_t0
572             CASE ( 'passive_scalar' )
573                READ ( 13 )  passive_scalar
574             CASE ( 'prandtl_number' )
575                READ ( 13 )  prandtl_number
576             CASE ( 'psolver' )
577                READ ( 13 )  psolver
578             CASE ( 'pt_damping_factor' )
579                READ ( 13 )  pt_damping_factor
580             CASE ( 'pt_damping_width' )
581                READ ( 13 )  pt_damping_width
582             CASE ( 'pt_init' )
583                READ ( 13 )  pt_init
584             CASE ( 'pt_reference' )
585                READ ( 13 )  pt_reference
586             CASE ( 'pt_surface' )
587                READ ( 13 )  pt_surface
588             CASE ( 'pt_surface_initial_change' )
589                READ ( 13 )  pt_surface_initial_change
590             CASE ( 'pt_vertical_gradient' )
591                READ ( 13 )  pt_vertical_gradient
592             CASE ( 'pt_vertical_gradient_level' )
593                READ ( 13 )  pt_vertical_gradient_level
594             CASE ( 'pt_vertical_gradient_level_ind' )
595                READ ( 13 )  pt_vertical_gradient_level_ind
596             CASE ( 'q_init' )
597                READ ( 13 )  q_init
598             CASE ( 'q_surface' )
599                READ ( 13 )  q_surface
600             CASE ( 'q_surface_initial_change' )
601                READ ( 13 )  q_surface_initial_change
602             CASE ( 'q_vertical_gradient' )
603                READ ( 13 )  q_vertical_gradient
604             CASE ( 'q_vertical_gradient_level' )
605                READ ( 13 )  q_vertical_gradient_level
606             CASE ( 'q_vertical_gradient_level_ind' )
607                READ ( 13 )  q_vertical_gradient_level_ind
608             CASE ( 'random_generator' )
609                READ ( 13 )  random_generator
610             CASE ( 'random_heatflux' )
611                READ ( 13 )  random_heatflux
612             CASE ( 'rans_mode' )
613                READ ( 13 )  rans_mode
614             CASE ( 'rayleigh_damping_factor' )
615                READ ( 13 )  rayleigh_damping_factor
616             CASE ( 'rayleigh_damping_height' )
617                READ ( 13 )  rayleigh_damping_height
618             CASE ( 'recycling_width' )
619                READ ( 13 )  recycling_width
620             CASE ( 'ref_state' )
621                READ ( 13 )  ref_state
622             CASE ( 'reference_state' )
623                READ ( 13 )  reference_state
624             CASE ( 'residual_limit' )
625                READ ( 13 )  residual_limit
626             CASE ( 'roughness_length' )
627                READ ( 13 )  roughness_length
628             CASE ( 'run_coupled' )
629                READ ( 13 )  run_coupled
630             CASE ( 'runnr' )
631                READ ( 13 )  runnr
632             CASE ( 's_init' )
633                READ ( 13 )  s_init
634             CASE ( 's_surface' )
635                READ ( 13 )  s_surface
636             CASE ( 's_surface_initial_change' )
637                READ ( 13 )  s_surface_initial_change
638             CASE ( 's_vertical_gradient' )
639                READ ( 13 )  s_vertical_gradient
640             CASE ( 's_vertical_gradient_level' )
641                READ ( 13 )  s_vertical_gradient_level
642             CASE ( 's_vertical_gradient_level_ind' )
643                READ ( 13 )  s_vertical_gradient_level_ind
644             CASE ( 'scalar_advec' )
645                READ ( 13 )  scalar_advec
646             CASE ( 'simulated_time' )
647                READ ( 13 )  simulated_time
[2956]648             CASE ( 'spectrum_x' )
649                IF ( .NOT. ALLOCATED( spectrum_x ) )  THEN
650                   ALLOCATE( spectrum_x( 1:nx/2, 1:100, 1:10 ) )
651                ENDIF
652                READ ( 13 )  spectrum_x
653             CASE ( 'spectrum_y' )
654                IF ( .NOT. ALLOCATED( spectrum_y ) )  THEN
655                   ALLOCATE( spectrum_y( 1:ny/2, 1:100, 1:10 ) )
656                ENDIF
657                READ ( 13 )  spectrum_y
[2921]658             CASE ( 'spinup_time' )
659                READ ( 13 )  spinup_time
[4495]660             CASE ( 'subs_vertical_gradient' )
661                READ ( 13 )  subs_vertical_gradient
662             CASE ( 'subs_vertical_gradient_level' )
663                READ ( 13 )  subs_vertical_gradient_level
664             CASE ( 'subs_vertical_gradient_level_i' )
665                READ ( 13 )  subs_vertical_gradient_level_i
[2894]666             CASE ( 'surface_heatflux' )
667                READ ( 13 )  surface_heatflux
668             CASE ( 'surface_pressure' )
669                READ ( 13 )  surface_pressure
670             CASE ( 'surface_scalarflux' )
671                READ ( 13 )  surface_scalarflux
672             CASE ( 'surface_waterflux' )
673                READ ( 13 )  surface_waterflux
674             CASE ( 'time_coupling' )
675                READ ( 13 )  time_coupling
676             CASE ( 'time_disturb' )
677                READ ( 13 )  time_disturb
678             CASE ( 'time_do2d_xy' )
679                READ ( 13 )  time_do2d_xy
680             CASE ( 'time_do2d_xz' )
681                READ ( 13 )  time_do2d_xz
682             CASE ( 'time_do2d_yz' )
683                READ ( 13 )  time_do2d_yz
684             CASE ( 'time_do3d' )
685                READ ( 13 )  time_do3d
686             CASE ( 'time_do_av' )
687                READ ( 13 )  time_do_av
688             CASE ( 'time_do_sla' )
689                READ ( 13 )  time_do_sla
690             CASE ( 'time_domask' )
691                READ ( 13 )  time_domask
692             CASE ( 'time_dopr' )
693                READ ( 13 )  time_dopr
694             CASE ( 'time_dopr_av' )
695                READ ( 13 )  time_dopr_av
696             CASE ( 'time_dopr_listing' )
697                READ ( 13 )  time_dopr_listing
698             CASE ( 'time_dopts' )
699                READ ( 13 )  time_dopts
700             CASE ( 'time_dosp' )
701                READ ( 13 )  time_dosp
702             CASE ( 'time_dots' )
703                READ ( 13 )  time_dots
704             CASE ( 'time_radiation' )
705                READ ( 13 )  time_radiation
706             CASE ( 'time_restart' )
707                READ ( 13 )  time_restart
708             CASE ( 'time_run_control' )
709                READ ( 13 )  time_run_control
710             CASE ( 'time_since_reference_point' )
711                READ ( 13 )  time_since_reference_point
[3988]712             CASE ( 'time_virtual_measurement' )
713                READ ( 13 )  time_virtual_measurement
[2894]714             CASE ( 'timestep_scheme' )
715                READ ( 13 )  timestep_scheme
716             CASE ( 'top_heatflux' )
717                READ ( 13 )  top_heatflux
718             CASE ( 'top_momentumflux_u' )
719                READ ( 13 )  top_momentumflux_u
720             CASE ( 'top_momentumflux_v' )
721                READ ( 13 )  top_momentumflux_v
722             CASE ( 'top_scalarflux' )
723                READ ( 13 )  top_scalarflux
724             CASE ( 'topography' )
725                READ ( 13 )  topography
726             CASE ( 'topography_grid_convention' )
727                READ ( 13 )  topography_grid_convention
728             CASE ( 'tsc' )
729                READ ( 13 )  tsc
730             CASE ( 'tunnel_height' )
731                READ ( 13 )  tunnel_height
732             CASE ( 'tunnel_length' )
733                READ ( 13 )  tunnel_length
734             CASE ( 'tunnel_wall_depth' )
735                READ ( 13 )  tunnel_wall_depth
736             CASE ( 'tunnel_width_x' )
737                READ ( 13 )  tunnel_width_x
738             CASE ( 'tunnel_width_y' )
739                READ ( 13 )  tunnel_width_y
740             CASE ( 'turbulence_closure' )
741                READ ( 13 )  turbulence_closure
742             CASE ( 'turbulent_inflow' )
743                READ ( 13 )  turbulent_inflow
744             CASE ( 'u_bulk' )
745                READ ( 13 )  u_bulk
746             CASE ( 'u_init' )
747                READ ( 13 )  u_init
748             CASE ( 'u_max' )
749                READ ( 13 )  u_max
750             CASE ( 'u_max_ijk' )
751                READ ( 13 )  u_max_ijk
752             CASE ( 'ug' )
753                READ ( 13 )  ug
754             CASE ( 'ug_surface' )
755                READ ( 13 )  ug_surface
756             CASE ( 'ug_vertical_gradient' )
757                READ ( 13 )  ug_vertical_gradient
758             CASE ( 'ug_vertical_gradient_level' )
759                READ ( 13 )  ug_vertical_gradient_level
760             CASE ( 'ug_vertical_gradient_level_ind' )
761                READ ( 13 )  ug_vertical_gradient_level_ind
762             CASE ( 'use_surface_fluxes' )
763                READ ( 13 )  use_surface_fluxes
764             CASE ( 'use_top_fluxes' )
765                READ ( 13 )  use_top_fluxes
766             CASE ( 'use_ug_for_galilei_tr' )
767                READ ( 13 )  use_ug_for_galilei_tr
768             CASE ( 'use_upstream_for_tke' )
769                READ ( 13 )  use_upstream_for_tke
770             CASE ( 'v_bulk' )
771                READ ( 13 )  v_bulk
772             CASE ( 'v_init' )
773                READ ( 13 )  v_init
774             CASE ( 'v_max' )
775                READ ( 13 )  v_max
776             CASE ( 'v_max_ijk' )
777                READ ( 13 )  v_max_ijk
778             CASE ( 'vg' )
779                READ ( 13 )  vg
780             CASE ( 'vg_surface' )
781                READ ( 13 )  vg_surface
782             CASE ( 'vg_vertical_gradient' )
783                READ ( 13 )  vg_vertical_gradient
784             CASE ( 'vg_vertical_gradient_level' )
785                READ ( 13 )  vg_vertical_gradient_level
786             CASE ( 'vg_vertical_gradient_level_ind' )
787                READ ( 13 )  vg_vertical_gradient_level_ind
788             CASE ( 'virtual_flight' )
789                READ ( 13 )  virtual_flight
790             CASE ( 'vnest_init' )
791                READ ( 13 )  vnest_init
792             CASE ( 'volume_flow_area' )
793                READ ( 13 )  volume_flow_area
794             CASE ( 'volume_flow_initial' )
795                READ ( 13 )  volume_flow_initial
796             CASE ( 'w_max' )
797                READ ( 13 )  w_max
798             CASE ( 'w_max_ijk' )
799                READ ( 13 )  w_max_ijk
800             CASE ( 'wall_adjustment' )
801                READ ( 13 )  wall_adjustment
802             CASE ( 'wall_heatflux' )
803                READ ( 13 )  wall_heatflux
804             CASE ( 'wall_humidityflux' )
805                READ ( 13 )  wall_humidityflux
806             CASE ( 'wall_scalarflux' )
807                READ ( 13 )  wall_scalarflux
808             CASE ( 'y_shift' )
809                READ ( 13 )  y_shift
810             CASE ( 'z0h_factor' )
811                READ ( 13 )  z0h_factor
812             CASE ( 'zeta_max' )
813                READ ( 13 )  zeta_max
814             CASE ( 'zeta_min' )
815                READ ( 13 )  zeta_min
[3003]816             CASE ( 'z_i' )
817                READ ( 13 )  z_i
[2894]818
819             CASE DEFAULT
[3294]820!
821!--             Read global variables from of other modules
[3766]822                CALL module_interface_rrd_global( found )
[2894]823
824                IF ( .NOT. found )  THEN
825                   WRITE( message_string, * ) 'unknown variable named "',      &
826                                           restart_string(1:length),           &
[4431]827                                          '" found in global data from ',      &
[2894]828                                          'prior run on PE ', myid
829                CALL message( 'rrd_global', 'PA0302', 1, 2, 0, 6, 0 )
[4431]830
[2894]831                ENDIF
832
833          END SELECT
834!
835!--       Read next string
836          READ ( 13 )  length
[4431]837          READ ( 13 )  restart_string(1:length)
[2894]838
[4495]839       ENDDO  ! End of loop for reading the restart string
840
841       CALL close_file( 13 )
842
843    ELSEIF ( TRIM( restart_data_format_input ) == 'mpi' )  THEN
844!
845!--    Read global restart data using MPI-IO
846!--    ATTENTION: Arrays need to be read with routine rrd_mpi_io_global_array!
847!--    Caution: When any of the following read instructions have been changed, the
848!--    -------  version number stored in the variable binary_version_global has
849!--             to be increased. The same changes must also be done in
850!--             wrd_write_global.
851!
852!--    Open the MPI-IO restart file.
[4498]853       CALL rd_mpi_io_open( 'read', 'BININ' // TRIM( coupling_char ) )
[4495]854
855!
856!--    Make version number check first
857       CALL rrd_mpi_io( 'binary_version_global',  version_on_file )
858
859       binary_version_global = '5.0'
860       IF ( TRIM( version_on_file ) /= TRIM( binary_version_global ) )  THEN
861          WRITE( message_string, * ) 'version mismatch concerning binary_version_global:',         &
862                                     '&version on file    = "', TRIM( version_on_file ), '"',      &
863                                     '&version in program = "', TRIM( binary_version_global ), '"'
864          CALL message( 'rrd_global', 'PA0296', 1, 2, 0, 6, 0 )
865       ENDIF
866
867       CALL rrd_mpi_io( 'numprocs',  numprocs_previous_run )
868       CALL rrd_mpi_io( 'nz' , nz )
869       CALL rrd_mpi_io( 'max_pr_user',  max_pr_user )
870       CALL rrd_mpi_io( 'statistic_regions', statistic_regions )
871
872!
873!--    The following global arrays (better to say, they have the same size and values on each
874!--    subdomain) are by default allocated in routine parin, but not in case of restarts!
875       IF ( .NOT. ALLOCATED( ug ) )  THEN
876           ALLOCATE( ug(0:nz+1), u_init(0:nz+1), vg(0:nz+1),                                       &
877                     v_init(0:nz+1), pt_init(0:nz+1), q_init(0:nz+1),                              &
878                     ref_state(0:nz+1), s_init(0:nz+1), sa_init(0:nz+1),                           &
879                     hom(0:nz+1,2,pr_palm+max_pr_user,0:statistic_regions),                        &
880                     hom_sum(0:nz+1,pr_palm+max_pr_user,0:statistic_regions) )
881       ENDIF
882
883       CALL rrd_mpi_io( 'advected_distance_x',  advected_distance_x )
884       CALL rrd_mpi_io( 'advected_distance_y', advected_distance_y )
885       CALL rrd_mpi_io( 'alpha_surface', alpha_surface )
886       CALL rrd_mpi_io( 'average_count_pr', average_count_pr )
887       CALL rrd_mpi_io( 'average_count_sp', average_count_sp )
888       CALL rrd_mpi_io( 'average_count_3d', average_count_3d )
889       CALL rrd_mpi_io( 'bc_e_b', bc_e_b )
890       CALL rrd_mpi_io( 'bc_lr', bc_lr )
891       CALL rrd_mpi_io( 'bc_ns', bc_ns )
892       CALL rrd_mpi_io( 'bc_p_b', bc_p_b )
893       CALL rrd_mpi_io( 'bc_p_t', bc_p_t )
894       CALL rrd_mpi_io( 'bc_pt_b', bc_pt_b )
895       CALL rrd_mpi_io( 'bc_pt_t', bc_pt_t )
896       CALL rrd_mpi_io( 'bc_pt_t_val', bc_pt_t_val )
897       CALL rrd_mpi_io( 'bc_q_b', bc_q_b )
898       CALL rrd_mpi_io( 'bc_q_t', bc_q_t )
899       CALL rrd_mpi_io( 'bc_q_t_val', bc_q_t_val )
900       CALL rrd_mpi_io( 'bc_s_b', bc_s_b )
901       CALL rrd_mpi_io( 'bc_s_t', bc_s_t )
902       CALL rrd_mpi_io( 'bc_uv_b', bc_uv_b )
903       CALL rrd_mpi_io( 'bc_uv_t', bc_uv_t )
904       CALL rrd_mpi_io( 'biometeorology', biometeorology )
905       CALL rrd_mpi_io( 'building_height', building_height )
906       CALL rrd_mpi_io( 'building_length_x', building_length_x )
907       CALL rrd_mpi_io( 'building_length_y', building_length_y )
908       CALL rrd_mpi_io( 'building_wall_left', building_wall_left )
909       CALL rrd_mpi_io( 'building_wall_south', building_wall_south )
910       CALL rrd_mpi_io( 'bulk_cloud_model', bulk_cloud_model )
911       CALL rrd_mpi_io( 'call_psolver_at_all_substeps', call_psolver_at_all_substeps )
912       CALL rrd_mpi_io( 'canyon_height', canyon_height )
913       CALL rrd_mpi_io( 'canyon_wall_left', canyon_wall_left )
914       CALL rrd_mpi_io( 'canyon_wall_south', canyon_wall_south )
915       CALL rrd_mpi_io( 'canyon_width_x',  canyon_width_x )
916       CALL rrd_mpi_io( 'canyon_width_y', canyon_width_y )
917       CALL rrd_mpi_io( 'cfl_factor', cfl_factor )
918       CALL rrd_mpi_io( 'cloud_droplets',  cloud_droplets )
919       CALL rrd_mpi_io( 'collective_wait', collective_wait )
920       CALL rrd_mpi_io( 'conserve_volume_flow', conserve_volume_flow )
921       CALL rrd_mpi_io( 'conserve_volume_flow_mode', conserve_volume_flow_mode )
922       CALL rrd_mpi_io( 'constant_flux_layer', constant_flux_layer )
923       CALL rrd_mpi_io( 'coupling_start_time', coupling_start_time )
924       CALL rrd_mpi_io( 'current_timestep_number', current_timestep_number )
925       CALL rrd_mpi_io( 'cycle_mg', cycle_mg )
926       CALL rrd_mpi_io( 'damp_level_1d', damp_level_1d )
927       CALL rrd_mpi_io( 'dissipation_1d', dissipation_1d )
928       CALL rrd_mpi_io_global_array( 'do2d_xy_time_count', do2d_xy_time_count )
929       CALL rrd_mpi_io_global_array( 'do2d_xz_time_count', do2d_xz_time_count )
930       CALL rrd_mpi_io_global_array( 'do2d_yz_time_count', do2d_yz_time_count )
931       CALL rrd_mpi_io_global_array( 'do3d_time_count', do3d_time_count )
932       CALL rrd_mpi_io( 'dp_external', dp_external )
933       CALL rrd_mpi_io( 'dp_level_b', dp_level_b )
934       CALL rrd_mpi_io( 'dp_smooth', dp_smooth )
935       CALL rrd_mpi_io_global_array( 'dpdxy', dpdxy )
936       CALL rrd_mpi_io( 'dt_3d', dt_3d )
937       CALL rrd_mpi_io( 'dt_pr_1d', dt_pr_1d )
938       CALL rrd_mpi_io( 'dt_run_control_1d', dt_run_control_1d )
939       CALL rrd_mpi_io( 'dx', dx )
940       CALL rrd_mpi_io( 'dy', dy )
941       CALL rrd_mpi_io_global_array( 'dz', dz )
942       CALL rrd_mpi_io( 'dz_max', dz_max )
943       CALL rrd_mpi_io( 'dz_stretch_factor', dz_stretch_factor )
944       CALL rrd_mpi_io_global_array( 'dz_stretch_factor_array', dz_stretch_factor_array )
945       CALL rrd_mpi_io( 'dz_stretch_level', dz_stretch_level )
946       CALL rrd_mpi_io_global_array( 'dz_stretch_level_end', dz_stretch_level_end )
947       CALL rrd_mpi_io_global_array( 'dz_stretch_level_start', dz_stretch_level_start )
948       CALL rrd_mpi_io( 'e_min', e_min )
949       CALL rrd_mpi_io( 'end_time_1d', end_time_1d )
950       CALL rrd_mpi_io( 'fft_method', fft_method )
951       CALL rrd_mpi_io( 'first_call_lpm', first_call_lpm )
952       CALL rrd_mpi_io( 'galilei_transformation', galilei_transformation )
953       CALL rrd_mpi_io( 'gust_module_enabled', gust_module_enabled )
954       CALL rrd_mpi_io_global_array( 'hom', hom )
955       CALL rrd_mpi_io_global_array( 'hom_sum', hom_sum )
956       CALL rrd_mpi_io( 'humidity', humidity )
957       CALL rd_mpi_io_check_array( 'inflow_damping_factor', found = array_found )
958       IF ( array_found )  THEN
959           IF ( .NOT. ALLOCATED( inflow_damping_factor ) )  THEN
960               ALLOCATE( inflow_damping_factor(0:nz+1) )
961           ENDIF
962           CALL rrd_mpi_io_global_array( 'inflow_damping_factor', inflow_damping_factor )
963       ENDIF
964       CALL rrd_mpi_io( 'inflow_damping_height', inflow_damping_height )
965       CALL rrd_mpi_io( 'inflow_damping_width', inflow_damping_width )
966       CALL rrd_mpi_io( 'inflow_disturbance_begin', inflow_disturbance_begin )
967       CALL rrd_mpi_io( 'inflow_disturbance_end', inflow_disturbance_end )
968       CALL rrd_mpi_io( 'km_constant', km_constant )
969       CALL rrd_mpi_io( 'large_scale_forcing', large_scale_forcing )
970       CALL rrd_mpi_io( 'large_scale_subsidence', large_scale_subsidence )
971       CALL rrd_mpi_io( 'latitude', latitude )
972       CALL rrd_mpi_io( 'longitude', longitude )
973       CALL rrd_mpi_io( 'loop_optimization', loop_optimization )
974       CALL rrd_mpi_io( 'masking_method', masking_method )
975       CALL rd_mpi_io_check_array( 'mean_inflow_profiles', found = array_found )
976       IF ( array_found)  THEN
977          IF ( .NOT. ALLOCATED( mean_inflow_profiles ) )  THEN
978             ALLOCATE( mean_inflow_profiles(0:nz+1,7) )
979          ENDIF
980          CALL rrd_mpi_io_global_array( 'mean_inflow_profiles', mean_inflow_profiles )
981       ENDIF
982       CALL rrd_mpi_io( 'mg_cycles', mg_cycles )
983       CALL rrd_mpi_io( 'mg_switch_to_pe0_level', mg_switch_to_pe0_level )
984       CALL rrd_mpi_io( 'mixing_length_1d', mixing_length_1d )
985       CALL rrd_mpi_io( 'momentum_advec', momentum_advec )
986!
987!--    There is no module procedure for CHARACTER arrays
988       DO  i = 1, SIZE( netcdf_precision , 1 )
989          WRITE( tmp_name, '(A,I2.2)' )  'netcdf_precision_', i
990          CALL rrd_mpi_io( TRIM( tmp_name ), netcdf_precision(i) )
[2894]991       ENDDO
[4495]992       CALL rrd_mpi_io( 'neutral', neutral )
993       CALL rrd_mpi_io( 'ngsrb', ngsrb )
994       CALL rrd_mpi_io( 'nsor', nsor )
995       CALL rrd_mpi_io( 'nsor_ini', nsor_ini )
996       CALL rrd_mpi_io( 'nudging', nudging )
997       CALL rrd_mpi_io( 'num_leg', num_leg )
998       CALL rrd_mpi_io( 'nx', nx )
999       nx_on_file = nx
1000       CALL rrd_mpi_io( 'ny', ny )
1001       ny_on_file = ny
1002       CALL rrd_mpi_io( 'ocean_mode', ocean_mode )
1003       CALL rrd_mpi_io( 'omega', omega )
1004       CALL rrd_mpi_io( 'omega_sor', omega_sor )
1005       CALL rrd_mpi_io( 'origin_data_time', origin_date_time )
1006       CALL rrd_mpi_io( 'output_for_t0', output_for_t0 )
1007       CALL rrd_mpi_io( 'particle_advection', particle_advection )
1008       CALL rrd_mpi_io( 'passive_scalar', passive_scalar )
1009       CALL rrd_mpi_io( 'prandtl_number', prandtl_number )
1010       CALL rrd_mpi_io( 'psolver', psolver )
1011       CALL rrd_mpi_io( 'pt_damping_factor', pt_damping_factor )
1012       CALL rrd_mpi_io( 'pt_damping_width', pt_damping_width )
1013       CALL rrd_mpi_io_global_array( 'pt_init', pt_init )
1014       CALL rrd_mpi_io( 'pt_reference', pt_reference )
1015       CALL rrd_mpi_io( 'pt_surface', pt_surface )
1016       CALL rrd_mpi_io( 'pt_surface_initial_change', pt_surface_initial_change )
1017       CALL rrd_mpi_io_global_array( 'pt_vertical_gradient', pt_vertical_gradient )
1018       CALL rrd_mpi_io_global_array( 'pt_vertical_gradient_level', pt_vertical_gradient_level )
1019       CALL rrd_mpi_io_global_array( 'pt_vertical_gradient_level_ind', pt_vertical_gradient_level_ind )
1020       CALL rrd_mpi_io_global_array( 'q_init', q_init )
1021       CALL rrd_mpi_io( 'q_surface', q_surface )
1022       CALL rrd_mpi_io( 'q_surface_initial_change', q_surface_initial_change )
1023       CALL rrd_mpi_io_global_array( 'q_vertical_gradient', q_vertical_gradient )
1024       CALL rrd_mpi_io_global_array( 'q_vertical_gradient_level', q_vertical_gradient_level )
1025       CALL rrd_mpi_io_global_array( 'q_vertical_gradient_level_ind', q_vertical_gradient_level_ind )
1026       CALL rrd_mpi_io( 'random_generator', random_generator )
1027       CALL rrd_mpi_io( 'random_heatflux', random_heatflux )
1028       CALL rrd_mpi_io( 'rans_mode', rans_mode )
1029       CALL rrd_mpi_io( 'rayleigh_damping_factor', rayleigh_damping_factor )
1030       CALL rrd_mpi_io( 'rayleigh_damping_height', rayleigh_damping_height )
1031       CALL rrd_mpi_io( 'recycling_width', recycling_width )
1032       CALL rrd_mpi_io_global_array( 'ref_state', ref_state )
1033       CALL rrd_mpi_io( 'reference_state', reference_state )
1034       CALL rrd_mpi_io( 'residual_limit', residual_limit )
1035       CALL rrd_mpi_io( 'roughness_length', roughness_length )
1036       CALL rrd_mpi_io( 'run_coupled', run_coupled )
1037       CALL rrd_mpi_io( 'runnr', runnr )
1038       CALL rrd_mpi_io_global_array( 's_init', s_init )
1039       CALL rrd_mpi_io( 's_surface', s_surface )
1040       CALL rrd_mpi_io( 's_surface_initial_change', s_surface_initial_change )
1041       CALL rrd_mpi_io_global_array( 's_vertical_gradient', s_vertical_gradient )
1042       CALL rrd_mpi_io_global_array( 's_vertical_gradient_level', s_vertical_gradient_level )
1043       CALL rrd_mpi_io_global_array( 's_vertical_gradient_level_ind', s_vertical_gradient_level_ind )
1044       CALL rrd_mpi_io( 'scalar_advec', scalar_advec )
1045       CALL rrd_mpi_io( 'simulated_time', simulated_time )
1046       CALL rd_mpi_io_check_array( 'spectrum_x', found = array_found )
1047       IF (array_found )  THEN
1048           IF ( .NOT. ALLOCATED( spectrum_x ) )  THEN
1049              ALLOCATE( spectrum_x( 1:nx/2, 1:100, 1:10 ) )
1050           ENDIF
1051           CALL rrd_mpi_io( 'spectrum_y', spectrum_y )
1052       ENDIF
1053       CALL rd_mpi_io_check_array( 'spectrum_y', found = array_found )
1054       IF ( array_found )  THEN
1055           IF ( .NOT. ALLOCATED( spectrum_y ) )  THEN
1056              ALLOCATE( spectrum_y( 1:ny/2, 1:100, 1:10 ) )
1057           ENDIF
1058           CALL rrd_mpi_io( 'spectrum_y', spectrum_y )
1059       ENDIF
1060       CALL rrd_mpi_io( 'spinup_time ', spinup_time )
1061       CALL rrd_mpi_io_global_array( 'subs_vertical_gradient', subs_vertical_gradient )
1062       CALL rrd_mpi_io_global_array( 'subs_vertical_gradient_level', subs_vertical_gradient_level )
1063       CALL rrd_mpi_io_global_array( 'subs_vertical_gradient_level_i', subs_vertical_gradient_level_i )
1064       CALL rrd_mpi_io( 'surface_heatflux', surface_heatflux )
1065       CALL rrd_mpi_io( 'surface_pressure', surface_pressure )
1066       CALL rrd_mpi_io( 'surface_output', surface_output )
1067       CALL rrd_mpi_io( 'surface_scalarflux', surface_scalarflux )
1068       CALL rrd_mpi_io( 'surface_waterflux', surface_waterflux )
1069       CALL rrd_mpi_io( 'syn_turb_gen', syn_turb_gen )
1070       CALL rrd_mpi_io( 'time_coupling', time_coupling )
1071       CALL rrd_mpi_io( 'time_disturb', time_disturb )
1072       CALL rrd_mpi_io( 'time_do2d_xy', time_do2d_xy )
1073       CALL rrd_mpi_io( 'time_do2d_xz', time_do2d_xz )
1074       CALL rrd_mpi_io( 'time_do2d_yz', time_do2d_yz )
1075       CALL rrd_mpi_io( 'time_do3d', time_do3d )
1076       CALL rrd_mpi_io( 'time_do_av', time_do_av )
1077       CALL rrd_mpi_io( 'time_do_sla', time_do_sla )
1078       CALL rrd_mpi_io_global_array( 'time_domask', time_domask )
1079       CALL rrd_mpi_io( 'time_dopr', time_dopr )
1080       CALL rrd_mpi_io( 'time_dopr_av', time_dopr_av )
1081       CALL rrd_mpi_io( 'time_dopr_listing', time_dopr_listing )
1082       CALL rrd_mpi_io( 'time_dopts', time_dopts )
1083       CALL rrd_mpi_io( 'time_dosp', time_dosp )
1084       CALL rrd_mpi_io( 'time_dots', time_dots )
1085       CALL rrd_mpi_io( 'time_radiation', time_radiation )
1086       CALL rrd_mpi_io( 'time_restart', time_restart )
1087       CALL rrd_mpi_io( 'time_run_control', time_run_control )
1088       CALL rrd_mpi_io( 'time_since_reference_point', time_since_reference_point )
1089       CALL rrd_mpi_io( 'time_virtual_measurement', time_virtual_measurement )
1090       CALL rrd_mpi_io( 'timestep_scheme', timestep_scheme )
1091       CALL rrd_mpi_io( 'top_heatflux', top_heatflux )
1092       CALL rrd_mpi_io( 'top_momentumflux_u', top_momentumflux_u )
1093       CALL rrd_mpi_io( 'top_momentumflux_v', top_momentumflux_v )
1094       CALL rrd_mpi_io( 'top_scalarflux', top_scalarflux )
1095       CALL rrd_mpi_io( 'topography', topography )
1096       CALL rrd_mpi_io( 'topography_grid_convention', topography_grid_convention )
1097       CALL rrd_mpi_io_global_array( 'tsc', tsc )
1098       CALL rrd_mpi_io( 'tunnel_height', tunnel_height )
1099       CALL rrd_mpi_io( 'tunnel_length', tunnel_length )
1100       CALL rrd_mpi_io( 'tunnel_wall_depth', tunnel_wall_depth )
1101       CALL rrd_mpi_io( 'tunnel_width_x', tunnel_width_x )
1102       CALL rrd_mpi_io( 'tunnel_width_y', tunnel_width_y )
1103       CALL rrd_mpi_io( 'turbulence_closure', turbulence_closure )
1104       CALL rrd_mpi_io( 'turbulent_inflow', turbulent_inflow )
1105       CALL rrd_mpi_io( 'u_bulk', u_bulk )
1106       CALL rrd_mpi_io_global_array( 'u_init', u_init )
1107       CALL rrd_mpi_io( 'u_max', u_max )
1108       CALL rrd_mpi_io_global_array( 'u_max_ijk', u_max_ijk )
1109       CALL rrd_mpi_io_global_array( 'ug', ug )
1110       CALL rrd_mpi_io( 'ug_surface', ug_surface )
1111       CALL rrd_mpi_io_global_array( 'ug_vertical_gradient', ug_vertical_gradient )
1112       CALL rrd_mpi_io_global_array( 'ug_vertical_gradient_level', ug_vertical_gradient_level )
1113       CALL rrd_mpi_io_global_array( 'ug_vertical_gradient_level_ind', ug_vertical_gradient_level_ind )
1114       CALL rrd_mpi_io( 'use_surface_fluxes', use_surface_fluxes )
1115       CALL rrd_mpi_io( 'use_top_fluxes', use_top_fluxes )
1116       CALL rrd_mpi_io( 'use_ug_for_galilei_tr', use_ug_for_galilei_tr )
1117       CALL rrd_mpi_io( 'use_upstream_for_tke', use_upstream_for_tke )
1118       CALL rrd_mpi_io( 'user_module_enabled', user_module_enabled )
1119       CALL rrd_mpi_io( 'v_bulk', v_bulk )
1120       CALL rrd_mpi_io_global_array( 'v_init', v_init )
1121       CALL rrd_mpi_io( 'v_max', v_max )
1122       CALL rrd_mpi_io_global_array( 'v_max_ijk', v_max_ijk )
1123       CALL rrd_mpi_io_global_array( 'vg', vg )
1124       CALL rrd_mpi_io( 'vg_surface', vg_surface )
1125       CALL rrd_mpi_io_global_array( 'vg_vertical_gradient', vg_vertical_gradient )
1126       CALL rrd_mpi_io_global_array( 'vg_vertical_gradient_level', vg_vertical_gradient_level )
1127       CALL rrd_mpi_io_global_array( 'vg_vertical_gradient_level_ind', vg_vertical_gradient_level_ind )
1128       CALL rrd_mpi_io( 'virtual_flight', virtual_flight )
1129       CALL rrd_mpi_io( 'vnest_init', vnest_init )
1130       CALL rrd_mpi_io_global_array( 'volume_flow_area', volume_flow_area )
1131       CALL rrd_mpi_io_global_array( 'volume_flow_initial', volume_flow_initial )
1132       CALL rrd_mpi_io( 'w_max', w_max )
1133       CALL rrd_mpi_io_global_array( 'w_max_ijk', w_max_ijk )
1134       CALL rrd_mpi_io( 'wall_adjustment', wall_adjustment )
1135       CALL rrd_mpi_io_global_array( 'wall_heatflux', wall_heatflux )
1136       CALL rrd_mpi_io_global_array( 'wall_humidityflux', wall_humidityflux )
1137       CALL rrd_mpi_io_global_array( 'wall_scalarflux', wall_scalarflux )
1138       CALL rrd_mpi_io( 'y_shift', y_shift )
1139       CALL rrd_mpi_io( 'z0h_factor', z0h_factor )
1140       CALL rrd_mpi_io( 'zeta_max', zeta_max )
1141       CALL rrd_mpi_io( 'zeta_min', zeta_min )
1142       CALL rrd_mpi_io_global_array( 'z_i', z_i )
[2894]1143
[4495]1144!
1145!--    Read global variables from of other modules
1146       CALL module_interface_rrd_global
[4431]1147
[4495]1148!
[4517]1149!--    Close restart file
[4495]1150       CALL rd_mpi_io_close
[2894]1151
[4495]1152    ENDIF
[2894]1153
[4495]1154    CALL location_message( 'read global restart data', 'finished' )
[2894]1155
[4495]1156 END SUBROUTINE rrd_global
[2894]1157
[4495]1158
1159
[2894]1160!------------------------------------------------------------------------------!
1161! Description:
1162! ------------
1163!> Skipping the global control variables from restart-file (binary format)
1164!> except some information needed when reading restart data from a previous
1165!> run which used a smaller total domain or/and a different domain decomposition
1166!> (initializing_actions  == 'cyclic_fill').
1167!------------------------------------------------------------------------------!
1168
1169    SUBROUTINE rrd_read_parts_of_global
1170
1171
1172       CHARACTER (LEN=10) ::  version_on_file
1173       CHARACTER (LEN=20) ::  momentum_advec_check
1174       CHARACTER (LEN=20) ::  scalar_advec_check
1175       CHARACTER (LEN=1)  ::  cdum
1176
1177       INTEGER(iwp) ::  max_pr_user_on_file
1178       INTEGER(iwp) ::  nz_on_file
1179       INTEGER(iwp) ::  statistic_regions_on_file
1180       INTEGER(iwp) ::  tmp_mpru
1181       INTEGER(iwp) ::  tmp_sr
1182
1183       REAL(wp), DIMENSION(:,:,:),   ALLOCATABLE ::  hom_sum_on_file
1184       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  hom_on_file
1185
1186
1187       CALL check_open( 13 )
1188
1189       READ ( 13 )  length
1190       READ ( 13 )  restart_string(1:length)
1191       READ ( 13 )  version_on_file
1192
1193!
1194!-- Read number of PEs and horizontal index bounds of all PEs used in previous
1195!-- run
1196       READ ( 13 )  length
1197       READ ( 13 )  restart_string(1:length)
1198
1199       IF ( restart_string(1:length) /= 'numprocs' )  THEN
1200          WRITE( message_string, * ) 'numprocs not found in data from prior ', &
1201                                     'run on PE ', myid
1202          CALL message( 'rrd_read_parts_of_global', 'PA0297', 1, 2, 0, 6, 0 )
1203       ENDIF
1204       READ ( 13 )  numprocs_previous_run
1205
1206       IF ( .NOT. ALLOCATED( hor_index_bounds_previous_run ) )  THEN
1207          ALLOCATE( hor_index_bounds_previous_run(4,0:numprocs_previous_run-1) )
1208       ENDIF
1209
1210       READ ( 13 )  length
1211       READ ( 13 )  restart_string(1:length)
1212
1213       IF ( restart_string(1:length) /= 'hor_index_bounds' )  THEN
1214          WRITE( message_string, * ) 'hor_index_bounds not found in data ',    &
1215                                     'from prior run on PE ', myid
1216          CALL message( 'rrd_read_parts_of_global', 'PA0298', 1, 2, 0, 6, 0 )
1217       ENDIF
1218       READ ( 13 )  hor_index_bounds_previous_run
1219
1220!
1221!-- Read vertical number of gridpoints and number of different areas used
1222!-- for computing statistics. Allocate arrays depending on these values,
1223!-- which are needed for the following read instructions.
1224       READ ( 13 )  length
1225       READ ( 13 )  restart_string(1:length)
1226
1227       IF ( restart_string(1:length) /= 'nz' )  THEN
1228          message_string = 'nz not found in restart data file'
1229          CALL message( 'rrd_read_parts_of_global', 'PA0303', 1, 2, 0, 6, 0 )
1230       ENDIF
1231       READ ( 13 )  nz_on_file
1232       IF ( nz_on_file /= nz )  THEN
1233          WRITE( message_string, * ) 'mismatch concerning number of ',         &
[3045]1234                                     'gridpoints along z:',                    &
[3046]1235                                     '&nz on file    = "', nz_on_file, '"',    &
1236                                     '&nz from run   = "', nz, '"'
[2894]1237          CALL message( 'rrd_read_parts_of_global', 'PA0304', 1, 2, 0, 6, 0 )
1238       ENDIF
1239
1240       READ ( 13 )  length
1241       READ ( 13 )  restart_string(1:length)
1242
1243       IF ( restart_string(1:length) /= 'max_pr_user' )  THEN
1244          message_string = 'max_pr_user not found in restart data file'
1245          CALL message( 'rrd_read_parts_of_global', 'PA0305', 1, 2, 0, 6, 0 )
1246       ENDIF
1247       READ ( 13 )  max_pr_user_on_file
1248       IF ( max_pr_user_on_file /= max_pr_user )  THEN
1249          WRITE( message_string, * ) 'number of user profiles on res',         &
1250                                     'tart data file differs from the ',       &
[3046]1251                                     'current run:&max_pr_user on file    = "',&
[2894]1252                                     max_pr_user_on_file, '"',                 &
[3046]1253                                     '&max_pr_user from run   = "',            &
[2894]1254                                     max_pr_user, '"'
1255          CALL message( 'rrd_read_parts_of_global', 'PA0306', 0, 0, 0, 6, 0 )
1256          tmp_mpru = MIN( max_pr_user_on_file, max_pr_user )
1257       ELSE
1258          tmp_mpru = max_pr_user
1259       ENDIF
1260
1261       READ ( 13 )  length
1262       READ ( 13 )  restart_string(1:length)
1263
1264       IF ( restart_string(1:length) /= 'statistic_regions' )  THEN
1265          message_string = 'statistic_regions not found in restart data file'
1266          CALL message( 'rrd_read_parts_of_global', 'PA0307', 1, 2, 0, 6, 0 )
1267       ENDIF
1268       READ ( 13 )  statistic_regions_on_file
1269       IF ( statistic_regions_on_file /= statistic_regions )  THEN
1270          WRITE( message_string, * ) 'statistic regions on restart data file ',&
[3045]1271                                     'differ from the current run:',           &
[3046]1272                                     '&statistic regions on file    = "',      &
[2894]1273                                     statistic_regions_on_file, '"',           &
[3046]1274                                     '&statistic regions from run   = "',      &
[2894]1275                                      statistic_regions, '"',                  &
[3046]1276                                     '&statistic data may be lost!'
[2894]1277          CALL message( 'rrd_read_parts_of_global', 'PA0308', 0, 1, 0, 6, 0 )
1278          tmp_sr = MIN( statistic_regions_on_file, statistic_regions )
1279       ELSE
1280          tmp_sr = statistic_regions
1281       ENDIF
1282
1283!
1284!-- Now read and check some control parameters and skip the rest
1285       READ ( 13 )  length
1286       READ ( 13 )  restart_string(1:length)
1287
1288       DO  WHILE ( restart_string(1:length) /= 'binary_version_local' )
1289
1290          SELECT CASE ( restart_string(1:length) )
1291
1292             CASE ( 'average_count_pr' )
1293                READ ( 13 )  average_count_pr
1294                IF ( average_count_pr /= 0 )  THEN
1295                   WRITE( message_string, * ) 'inflow profiles not ',          &
[3046]1296                                  'temporally averaged. &Averaging will be ',  &
[3637]1297                                  'done now using', average_count_pr,          &
[2894]1298                                  ' samples.'
1299                   CALL message( 'rrd_read_parts_of_global', 'PA0309',         &
1300                                 0, 1, 0, 6, 0 )
1301                ENDIF
1302
1303             CASE ( 'hom' )
1304                ALLOCATE( hom_on_file(0:nz+1,2,pr_palm+max_pr_user_on_file,    &
1305                          0:statistic_regions_on_file) )
1306                READ ( 13 )  hom_on_file
1307                hom(:,:,1:pr_palm+tmp_mpru,0:tmp_sr) =                         &
1308                             hom_on_file(:,:,1:pr_palm+tmp_mpru,0:tmp_sr)
1309                DEALLOCATE( hom_on_file )
1310
1311             CASE ( 'hom_sum' )
1312                ALLOCATE( hom_sum_on_file(0:nz+1,pr_palm+max_pr_user_on_file,  &
1313                          0:statistic_regions_on_file) )
1314                READ ( 13 )  hom_sum_on_file
1315                hom_sum(:,1:pr_palm+tmp_mpru,0:tmp_sr) =                       &
1316                             hom_sum_on_file(:,1:pr_palm+tmp_mpru,0:tmp_sr)
1317                DEALLOCATE( hom_sum_on_file )
1318
1319             CASE ( 'momentum_advec' )
1320                momentum_advec_check = momentum_advec
1321                READ ( 13 )  momentum_advec
1322                IF ( TRIM( momentum_advec_check ) /= TRIM( momentum_advec ) )  &
1323                THEN
1324                   WRITE( message_string, * ) 'momentum_advec of the restart ',&
1325                                  'run differs from momentum_advec of the ',   &
1326                                  'initial run.'
1327                   CALL message( 'rrd_read_parts_of_global', 'PA0100',         &
1328                                 1, 2, 0, 6, 0 )
1329                ENDIF
1330
1331             CASE ( 'nx' )
1332                READ ( 13 )  nx_on_file
1333
1334             CASE ( 'ny' )
1335                READ ( 13 )  ny_on_file
1336
1337             CASE ( 'ref_state' )
1338                READ ( 13 )  ref_state
1339
1340             CASE ( 'scalar_advec' )
1341                scalar_advec_check = scalar_advec
1342                READ ( 13 )  scalar_advec
1343                IF ( TRIM( scalar_advec_check ) /= TRIM( scalar_advec ) )      &
1344                THEN
1345                   WRITE( message_string, * ) 'scalar_advec of the restart ',  &
1346                                  'run differs from scalar_advec of the ',     &
1347                                  'initial run.'
1348                   CALL message( 'rrd_read_parts_of_global', 'PA0101',         &
1349                                 1, 2, 0, 6, 0 )
1350                ENDIF
1351
1352             CASE DEFAULT
1353
1354                READ ( 13 )  cdum
1355
1356          END SELECT
1357
1358          READ ( 13 )  length
1359          READ ( 13 )  restart_string(1:length)
1360
1361       ENDDO
1362
1363!
1364!-- Calculate the temporal average of vertical profiles, if neccessary
1365    IF ( average_count_pr /= 0 )  THEN
1366       hom_sum = hom_sum / REAL( average_count_pr, KIND=wp )
1367    ENDIF
1368
1369
1370    CALL close_file( 13 )
1371
1372
1373    END SUBROUTINE rrd_read_parts_of_global
1374
1375
1376! Description:
1377! ------------
[4517]1378!> Reads processor (subdomain) specific data of variables and arrays from restart file
[2894]1379!> (binary format).
1380!------------------------------------------------------------------------------!
[3637]1381 SUBROUTINE rrd_local
[2894]1382
1383
1384    CHARACTER (LEN=7)  ::  myid_char_save
1385    CHARACTER (LEN=10) ::  binary_version_local
1386    CHARACTER (LEN=10) ::  version_on_file
[4517]1387    CHARACTER (LEN=20) ::  tmp_name               !< temporary variable
[2894]1388
1389    INTEGER(iwp) ::  files_to_be_opened  !<
1390    INTEGER(iwp) ::  i                   !<
1391    INTEGER(iwp) ::  j                   !<
1392    INTEGER(iwp) ::  k                   !<
1393    INTEGER(iwp) ::  myid_on_file        !<
1394    INTEGER(iwp) ::  numprocs_on_file    !<
1395    INTEGER(iwp) ::  nxlc                !<
1396    INTEGER(iwp) ::  nxlf                !<
1397    INTEGER(iwp) ::  nxlpr               !<
1398    INTEGER(iwp) ::  nxl_on_file         !<
1399    INTEGER(iwp) ::  nxrc                !<
1400    INTEGER(iwp) ::  nxrf                !<
1401    INTEGER(iwp) ::  nxrpr               !<
1402    INTEGER(iwp) ::  nxr_on_file         !<
1403    INTEGER(iwp) ::  nync                !<
1404    INTEGER(iwp) ::  nynf                !<
1405    INTEGER(iwp) ::  nynpr               !<
1406    INTEGER(iwp) ::  nyn_on_file         !<
1407    INTEGER(iwp) ::  nysc                !<
1408    INTEGER(iwp) ::  nysf                !<
1409    INTEGER(iwp) ::  nyspr               !<
1410    INTEGER(iwp) ::  nys_on_file         !<
1411    INTEGER(iwp) ::  nzb_on_file         !<
1412    INTEGER(iwp) ::  nzt_on_file         !<
1413    INTEGER(iwp) ::  offset_x            !<
1414    INTEGER(iwp) ::  offset_y            !<
1415    INTEGER(iwp) ::  shift_x             !<
1416    INTEGER(iwp) ::  shift_y             !<
1417
1418    INTEGER(iwp), DIMENSION(numprocs_previous_run) ::  file_list       !<
1419    INTEGER(iwp), DIMENSION(numprocs_previous_run) ::  overlap_count   !<
1420
[4356]1421    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nxlfa      !<
1422    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nxrfa      !<
1423    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nynfa      !<
1424    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nysfa      !<
1425    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  offset_xa  !<
1426    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  offset_ya  !<
[2894]1427
1428    INTEGER(isp), DIMENSION(:,:),   ALLOCATABLE ::  tmp_2d_id_random   !< temporary array for storing random generator data
1429    INTEGER(isp), DIMENSION(:,:,:), ALLOCATABLE ::  tmp_2d_seq_random  !< temporary array for storing random generator data
1430
[4517]1431    LOGICAL ::  array_found                      !<
1432    LOGICAL ::  found                            !<
[2894]1433
[3998]1434    REAL(wp), DIMENSION(:,:),   ALLOCATABLE   ::  tmp_2d         !< temporary array for storing 2D data
1435    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3d         !< temporary array for storing 3D data
[4009]1436    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3d_non_standard !< temporary array for storing 3D data
1437                                                                 !< with non standard dimensions
[2894]1438
1439!
1440!-- Read data from previous model run.
1441    CALL cpu_log( log_point_s(14), 'rrd_local', 'start' )
[4517]1442
1443    IF ( TRIM( restart_data_format_input ) == 'fortran_binary' )  THEN
[4356]1444!
[4517]1445!--    Input in Fortran binary format
[2894]1446
1447!
[4517]1448!--    Allocate temporary buffer arrays. In previous versions, there were
1449!--    declared as automated arrays, causing memory problems when these
1450!--    were allocate on stack.
1451       ALLOCATE( nxlfa(numprocs_previous_run,1000) )
1452       ALLOCATE( nxrfa(numprocs_previous_run,1000) )
1453       ALLOCATE( nynfa(numprocs_previous_run,1000) )
1454       ALLOCATE( nysfa(numprocs_previous_run,1000) )
1455       ALLOCATE( offset_xa(numprocs_previous_run,1000) )
1456       ALLOCATE( offset_ya(numprocs_previous_run,1000) )
[2894]1457
1458!
[4517]1459!--    Check which of the restart files contain data needed for the subdomain
1460!--    of this PE
1461       files_to_be_opened = 0
[2894]1462
[4517]1463       DO  i = 1, numprocs_previous_run
[2894]1464!
[4517]1465!--       Store array bounds of the previous run ("pr") in temporary scalars
1466          nxlpr = hor_index_bounds_previous_run(1,i-1)
1467          nxrpr = hor_index_bounds_previous_run(2,i-1)
1468          nyspr = hor_index_bounds_previous_run(3,i-1)
1469          nynpr = hor_index_bounds_previous_run(4,i-1)
[2894]1470
1471!
[4517]1472!--       Determine the offsets. They may be non-zero in case that the total domain
1473!--       on file is smaller than the current total domain.
1474          offset_x = ( nxl / ( nx_on_file + 1 ) ) * ( nx_on_file + 1 )
1475          offset_y = ( nys / ( ny_on_file + 1 ) ) * ( ny_on_file + 1 )
[4431]1476
[4517]1477!
1478!--       Start with this offset and then check, if the subdomain on file
1479!--       matches another time(s) in the current subdomain by shifting it
1480!--       for nx_on_file+1, ny_on_file+1 respectively
[2894]1481
[4517]1482          shift_y = 0
1483          j       = 0
1484          DO WHILE (  nyspr+shift_y <= nyn-offset_y )
[4431]1485
[4517]1486             IF ( nynpr+shift_y >= nys-offset_y ) THEN
[4431]1487
[4517]1488                shift_x = 0
1489                DO WHILE ( nxlpr+shift_x <= nxr-offset_x )
1490
1491                   IF ( nxrpr+shift_x >= nxl-offset_x ) THEN
1492                      j = j +1
1493                      IF ( j > 1000 )  THEN
[2894]1494!
[4517]1495!--                      Array bound exceeded
1496                         message_string = 'data from subdomain of previous' //                        &
1497                                          ' run mapped more than 1000 times'
1498                         CALL message( 'rrd_local', 'PA0284', 2, 2, -1, 6, 1 )
1499                      ENDIF
[2894]1500
[4517]1501                      IF ( j == 1 )  THEN
1502                         files_to_be_opened = files_to_be_opened + 1
1503                         file_list(files_to_be_opened) = i-1
1504                      ENDIF
[4431]1505
[4517]1506                      offset_xa(files_to_be_opened,j) = offset_x + shift_x
1507                      offset_ya(files_to_be_opened,j) = offset_y + shift_y
[2894]1508!
[4517]1509!--                   Index bounds of overlapping data
1510                      nxlfa(files_to_be_opened,j) = MAX( nxl-offset_x-shift_x, nxlpr )
1511                      nxrfa(files_to_be_opened,j) = MIN( nxr-offset_x-shift_x, nxrpr )
1512                      nysfa(files_to_be_opened,j) = MAX( nys-offset_y-shift_y, nyspr )
1513                      nynfa(files_to_be_opened,j) = MIN( nyn-offset_y-shift_y, nynpr )
[2894]1514
[4517]1515                   ENDIF
[2894]1516
[4517]1517                   shift_x = shift_x + ( nx_on_file + 1 )
1518                ENDDO
[4431]1519
[4517]1520             ENDIF
[4431]1521
[4517]1522             shift_y = shift_y + ( ny_on_file + 1 )
1523          ENDDO
[4431]1524
[4517]1525          IF ( j > 0 )  overlap_count(files_to_be_opened) = j
[4431]1526
[4517]1527       ENDDO
[4431]1528
[2894]1529!
[4517]1530!--    Save the id-string of the current process, since myid_char may now be used
1531!--    to open files created by PEs with other id.
1532       myid_char_save = myid_char
[2894]1533
[4517]1534       IF ( files_to_be_opened /= 1  .OR.  numprocs /= numprocs_previous_run )  THEN
1535          WRITE( message_string, * ) 'number of PEs or virtual PE-grid changed in restart run. & ',   &
1536                                     'Set debug_output =.T. to get a list of files from which the & ',&
1537                                     'single PEs will read respectively'
1538          CALL message( 'rrd_local', 'PA0285', 0, 0, 0, 6, 0 )
1539          IF ( debug_output )  THEN
1540             IF ( files_to_be_opened <= 120 )  THEN
1541                WRITE( debug_string, '(2A,1X,120(I6.6,1X))' )                                         &
1542                     'number of PEs or virtual PE-grid changed in restart run.  PE will read from ',  &
1543                     'files ', file_list(1:files_to_be_opened)
1544             ELSE
1545                WRITE( debug_string, '(3A,1X,120(I6.6,1X),A)' )                                      &
1546                     'number of PEs or virtual PE-grid changed in restart run.  PE will read from ',  &
1547                     'files ', file_list(1:120), '... and more'
1548             ENDIF
1549             CALL debug_message( 'rrd_local', 'info' )
[4435]1550          ENDIF
1551       ENDIF
[2894]1552
1553!
[4517]1554!--    Read data from all restart files determined above
1555       DO  i = 1, files_to_be_opened
[4431]1556
[4517]1557          j = file_list(i)
[2894]1558!
[4517]1559!--       Set the filename (underscore followed by four digit processor id)
1560          WRITE (myid_char,'(''_'',I6.6)')  j
[2894]1561
1562!
[4517]1563!--       Open the restart file. If this file has been created by PE0 (_000000),
1564!--       the global variables at the beginning of the file have to be skipped
1565!--       first.
1566          CALL check_open( 13 )
1567          IF ( j == 0 )  CALL rrd_skip_global
[2894]1568
1569!
[4517]1570!--       First compare the version numbers
1571          READ ( 13 )  length
1572          READ ( 13 )  restart_string(1:length)
1573          READ ( 13 )  version_on_file
[2894]1574
[4517]1575          binary_version_local = '4.7'
1576          IF ( TRIM( version_on_file ) /= TRIM( binary_version_local ) )  THEN
1577             WRITE( message_string, * ) 'version mismatch concerning ',                               &
1578                                        'binary_version_local:',                                      &
1579                                        '&version on file    = "', TRIM( version_on_file ), '"',      &
1580                                        '&version in program = "', TRIM( binary_version_local ), '"'
1581             CALL message( 'rrd_local', 'PA0286', 1, 2, 0, 6, 0 )
1582          ENDIF
[2894]1583
1584!
[4517]1585!--       Read number of processors, processor-id, and array ranges.
1586!--       Compare the array ranges with those stored in the index bound array.
1587          READ ( 13 )  numprocs_on_file, myid_on_file, nxl_on_file, nxr_on_file, nys_on_file,         &
1588                       nyn_on_file, nzb_on_file, nzt_on_file
[2894]1589
[4517]1590          IF ( nxl_on_file /= hor_index_bounds_previous_run(1,j) )  THEN
1591             WRITE( message_string, * ) 'problem with index bound nxl on ',                           &
1592                                        'restart file "', myid_char, '"',                             &
1593                                        '&nxl = ', nxl_on_file, ' but it should be',                  &
1594                                        '&= ', hor_index_bounds_previous_run(1,j),                    &
1595                                        '&from the index bound information array'
1596             CALL message( 'rrd_local', 'PA0287', 2, 2, -1, 6, 1 )
1597          ENDIF
[2894]1598
[4517]1599          IF ( nxr_on_file /= hor_index_bounds_previous_run(2,j) )  THEN
1600              WRITE( message_string, * ) 'problem with index bound nxr on ',                          &
1601                                         'restart file "', myid_char, '"'  ,                          &
1602                                         ' nxr = ', nxr_on_file, ' but it should be',                 &
1603                                         ' = ', hor_index_bounds_previous_run(2,j),                   &
1604                                         ' from the index bound information array'
1605             CALL message( 'rrd_local', 'PA0288', 2, 2, -1, 6, 1 )
[2894]1606
[4517]1607          ENDIF
[2894]1608
[4517]1609          IF ( nys_on_file /= hor_index_bounds_previous_run(3,j) )  THEN
1610             WRITE( message_string, * ) 'problem with index bound nys on ',                           &
1611                                        'restart file "', myid_char, '"',                             &
1612                                        '&nys = ', nys_on_file, ' but it should be',                  &
1613                                        '&= ', hor_index_bounds_previous_run(3,j),                    &
1614                                        '&from the index bound information array'
1615             CALL message( 'rrd_local', 'PA0289', 2, 2, -1, 6, 1 )
1616          ENDIF
[2894]1617
[4517]1618          IF ( nyn_on_file /= hor_index_bounds_previous_run(4,j) )  THEN
1619             WRITE( message_string, * ) 'problem with index bound nyn on ',                           &
1620                                        'restart file "', myid_char, '"',                             &
1621                                        '&nyn = ', nyn_on_file, ' but it should be',                  &
1622                                        '&= ', hor_index_bounds_previous_run(4,j),                    &
1623                                        '&from the index bound information array'
1624             CALL message( 'rrd_local', 'PA0290', 2, 2, -1, 6, 1 )
1625          ENDIF
[2894]1626
[4517]1627          IF ( nzb_on_file /= nzb )  THEN
1628             WRITE( message_string, * ) 'mismatch between actual data and data ',                     &
1629                                        'from prior run on PE ', myid,                                &
1630                                        '&nzb on file = ', nzb_on_file,                               &
1631                                        '&nzb         = ', nzb
1632             CALL message( 'rrd_local', 'PA0291', 1, 2, 0, 6, 0 )
1633          ENDIF
[2894]1634
[4517]1635          IF ( nzt_on_file /= nzt )  THEN
1636             WRITE( message_string, * ) 'mismatch between actual data and data ',                     &
1637                                        'from prior run on PE ', myid,                                &
1638                                        '&nzt on file = ', nzt_on_file,                               &
1639                                        '&nzt         = ', nzt
1640             CALL message( 'rrd_local', 'PA0292', 1, 2, 0, 6, 0 )
1641          ENDIF
[2894]1642
1643!
[4517]1644!--       Allocate temporary arrays sized as the arrays on the restart file
1645          ALLOCATE( tmp_2d(nys_on_file-nbgp:nyn_on_file+nbgp,nxl_on_file-nbgp:nxr_on_file+nbgp),      &
1646                    tmp_3d(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,                               &
1647                           nxl_on_file-nbgp:nxr_on_file+nbgp) )
[2894]1648
1649!
[4517]1650!--       Read arrays
1651!--       ATTENTION: If the following read commands have been altered, the
1652!--       ---------- version number of the variable binary_version_local must
1653!--                  be altered, too. Furthermore, the output list of arrays in
1654!--                  wrd_write_local must also be altered
1655!--                  accordingly.
1656          READ ( 13 )  length
1657          READ ( 13 )  restart_string(1:length)
[2894]1658
[4431]1659
[2894]1660!
[4517]1661!--       Loop over processor specific field data
1662          DO  WHILE ( restart_string(1:length) /= '*** end ***' )
[2894]1663
1664!
[4517]1665!--          Map data on file as often as needed (data are read only for k=1)
1666             DO  k = 1, overlap_count(i)
[2894]1667
[4517]1668                found = .FALSE.
[4431]1669
[2894]1670!
[4517]1671!--             Get the index range of the subdomain on file which overlap with
1672!--             the current subdomain
1673                nxlf = nxlfa(i,k)
1674                nxlc = nxlfa(i,k) + offset_xa(i,k)
1675                nxrf = nxrfa(i,k)
1676                nxrc = nxrfa(i,k) + offset_xa(i,k)
1677                nysf = nysfa(i,k)
1678                nysc = nysfa(i,k) + offset_ya(i,k)
1679                nynf = nynfa(i,k)
1680                nync = nynfa(i,k) + offset_ya(i,k)
[2894]1681
1682
[4517]1683                SELECT CASE ( restart_string(1:length) )
[2894]1684
[4517]1685                   CASE ( 'ghf_av' )
1686                      IF ( .NOT. ALLOCATED( ghf_av ) )  THEN
1687                         ALLOCATE( ghf_av(nysg:nyng,nxlg:nxrg) )
1688                      ENDIF
1689                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1690                      ghf_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
1691                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1692
[4517]1693                   CASE ( 'e' )
1694                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1695                      e(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
1696                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1697
[4517]1698                   CASE ( 'e_av' )
1699                      IF ( .NOT. ALLOCATED( e_av ) )  THEN
1700                         ALLOCATE( e_av(nzb:nzt+1,nys-nbgp:nyn+nbgp,                                  &
1701                                        nxl-nbgp:nxr+nbgp) )
1702                      ENDIF
1703                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1704                      e_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
1705                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1706
[4517]1707                   CASE ( 'kh' )
1708                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1709                      kh(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                 &
1710                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1711
[4517]1712                   CASE ( 'kh_av' )
1713                      IF ( .NOT. ALLOCATED( kh_av ) )  THEN
1714                         ALLOCATE( kh_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
1715                      ENDIF
1716                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1717                      kh_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                              &
1718                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1719
[4517]1720                   CASE ( 'km' )
1721                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1722                      km(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                 &
1723                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1724
[4517]1725                   CASE ( 'km_av' )
1726                      IF ( .NOT. ALLOCATED( km_av ) )  THEN
1727                         ALLOCATE( km_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
1728                      ENDIF
1729                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1730                      km_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                              &
1731                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1732
[4517]1733                   CASE ( 'lpt_av' )
1734                      IF ( .NOT. ALLOCATED( lpt_av ) )  THEN
1735                         ALLOCATE( lpt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
1736                      ENDIF
1737                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1738                      lpt_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                             &
1739                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1740
[4517]1741                   CASE ( 'lwp_av' )
1742                      IF ( .NOT. ALLOCATED( lwp_av ) )  THEN
1743                         ALLOCATE( lwp_av(nysg:nyng,nxlg:nxrg) )
1744                      ENDIF
1745                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1746                      lwp_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
1747                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1748
[4517]1749                   CASE ( 'p' )
1750                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1751                      p(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
1752                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1753
[4517]1754                   CASE ( 'p_av' )
1755                      IF ( .NOT. ALLOCATED( p_av ) )  THEN
1756                         ALLOCATE( p_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1757                      ENDIF
1758                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1759                      p_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
1760                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1761
[4517]1762                   CASE ( 'pt' )
1763                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1764                      pt(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                 &
1765                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1766
[4517]1767                   CASE ( 'pt_av' )
1768                      IF ( .NOT. ALLOCATED( pt_av ) )  THEN
1769                         ALLOCATE( pt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1770                      ENDIF
1771                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1772                      pt_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                              &
1773                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1774
[4517]1775                   CASE ( 'pt_2m_av' )
1776                      IF ( .NOT. ALLOCATED( pt_2m_av ) )  THEN
1777                         ALLOCATE( pt_2m_av(nysg:nyng,nxlg:nxrg) )
1778                      ENDIF
1779                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1780                      pt_2m_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                            &
1781                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[3936]1782
[4517]1783                   CASE ( 'q' )
1784                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1785                      q(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
1786                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1787
[4517]1788                   CASE ( 'q_av' )
1789                      IF ( .NOT. ALLOCATED( q_av ) )  THEN
1790                         ALLOCATE( q_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
1791                      ENDIF
1792                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1793                      q_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
1794                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1795
[4517]1796                   CASE ( 'ql' )
1797                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1798                      ql(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                 &
1799                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1800
[4517]1801                   CASE ( 'ql_av' )
1802                      IF ( .NOT. ALLOCATED( ql_av ) )  THEN
1803                         ALLOCATE( ql_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1804                      ENDIF
1805                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1806                      ql_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                              &
1807                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1808
[4517]1809                   CASE ( 'qsurf_av' )
1810                      IF ( .NOT. ALLOCATED( qsurf_av ) )  THEN
1811                         ALLOCATE( qsurf_av(nysg:nyng,nxlg:nxrg) )
1812                      ENDIF
1813                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1814                      qsurf_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                             &
1815                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[4514]1816
[4517]1817                   CASE ( 'qsws_av' )
1818                      IF ( .NOT. ALLOCATED( qsws_av ) )  THEN
1819                         ALLOCATE( qsws_av(nysg:nyng,nxlg:nxrg) )
1820                      ENDIF
1821                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1822                      qsws_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                             &
1823                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1824
[4517]1825                   CASE ( 'qv_av' )
1826                      IF ( .NOT. ALLOCATED( qv_av ) )  THEN
1827                         ALLOCATE( qv_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1828                      ENDIF
1829                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1830                      qv_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                              &
1831                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1832
[4517]1833                   CASE ( 'r_a_av' )
1834                      IF ( .NOT. ALLOCATED( r_a_av ) )  THEN
1835                         ALLOCATE( r_a_av(nysg:nyng,nxlg:nxrg) )
1836                      ENDIF
1837                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1838                      r_a_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
1839                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1840
[4517]1841                   CASE ( 'random_iv' )  ! still unresolved issue
1842                      IF ( k == 1 )  READ ( 13 )  random_iv
1843                      IF ( k == 1 )  READ ( 13 )  random_iy
[2894]1844
[4517]1845                   CASE ( 'seq_random_array' )
1846                      ALLOCATE( tmp_2d_id_random(nys_on_file:nyn_on_file,nxl_on_file:nxr_on_file) )
1847                      ALLOCATE( tmp_2d_seq_random(5,nys_on_file:nyn_on_file,nxl_on_file:nxr_on_file) )
1848                      IF ( .NOT. ALLOCATED( id_random_array ) )  THEN
1849                         ALLOCATE( id_random_array(nys:nyn,nxl:nxr) )
1850                      ENDIF
1851                      IF ( .NOT. ALLOCATED( seq_random_array ) )  THEN
1852                         ALLOCATE( seq_random_array(5,nys:nyn,nxl:nxr) )
1853                      ENDIF
1854                      IF ( k == 1 )  READ ( 13 )  tmp_2d_id_random
1855                      IF ( k == 1 )  READ ( 13 )  tmp_2d_seq_random
1856                      id_random_array(nysc:nync,nxlc:nxrc) = tmp_2d_id_random(nysf:nynf,nxlf:nxrf)
1857                      seq_random_array(:,nysc:nync,nxlc:nxrc) = tmp_2d_seq_random(:,nysf:nynf,nxlf:nxrf)
1858                      DEALLOCATE( tmp_2d_id_random, tmp_2d_seq_random )
[2894]1859
[4517]1860                   CASE ( 's' )
1861                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1862                      s(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
1863                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1864
[4517]1865                   CASE ( 's_av' )
1866                      IF ( .NOT. ALLOCATED( s_av ) )  THEN
1867                         ALLOCATE( s_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg))
1868                      ENDIF
1869                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1870                      s_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
1871                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1872
[4517]1873                   CASE ( 'shf_av' )
1874                      IF ( .NOT. ALLOCATED( shf_av ) )  THEN
1875                         ALLOCATE( shf_av(nysg:nyng,nxlg:nxrg) )
1876                      ENDIF
1877                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1878                      shf_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                              &
1879                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[4431]1880
[4517]1881                   CASE ( 'ssurf_av' )
1882                      IF ( .NOT. ALLOCATED( ssurf_av ) )  THEN
1883                         ALLOCATE( ssurf_av(nysg:nyng,nxlg:nxrg) )
1884                      ENDIF
1885                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1886                      ssurf_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                             &
1887                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[4514]1888
[4517]1889                   CASE ( 'ssws_av' )
1890                      IF ( .NOT. ALLOCATED( ssws_av ) )  THEN
1891                         ALLOCATE( ssws_av(nysg:nyng,nxlg:nxrg) )
1892                      ENDIF
1893                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1894                      ssws_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                             &
1895                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[3994]1896
[4517]1897                   CASE ( 'ti_av' )
1898                      IF ( .NOT. ALLOCATED( ti_av ) )  THEN
1899                         ALLOCATE( ti_av(nzb:nzt+1,nys:nyn,nxl:nxr) )
1900                      ENDIF
1901                      IF ( k == 1 )  THEN
1902                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file:nyn_on_file,             &
1903                                                       nxl_on_file:nxr_on_file) )
1904                         READ ( 13 )  tmp_3d_non_standard
1905                      ENDIF
1906                      ti_av(:,nysc:nync,nxlc:nxrc) = tmp_3d_non_standard(:,nysf:nynf,nxlf:nxrf)
[3994]1907
[4517]1908                   CASE ( 'ts_av' )
1909                      IF ( .NOT. ALLOCATED( ts_av ) )  THEN
1910                         ALLOCATE( ts_av(nysg:nyng,nxlg:nxrg) )
1911                      ENDIF
1912                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1913                      ts_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                               &
1914                           tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1915
[4517]1916                   CASE ( 'tsurf_av' )
1917                      IF ( .NOT. ALLOCATED( tsurf_av ) )  THEN
1918                         ALLOCATE( tsurf_av(nysg:nyng,nxlg:nxrg) )
1919                      ENDIF
1920                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1921                      tsurf_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                             &
1922                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1923
[4517]1924                   CASE ( 'u' )
1925                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1926                      u(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
1927                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]1928
[4517]1929                   CASE ( 'u_av' )
1930                      IF ( .NOT. ALLOCATED( u_av ) )  THEN
1931                         ALLOCATE( u_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
1932                      ENDIF
1933                      IF ( k == 1 )  READ ( 13 )  tmp_3d
1934                      u_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
1935                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[4431]1936
[4517]1937                   CASE ( 'u_center_av' )
1938                      IF ( .NOT. ALLOCATED( u_center_av ) )  THEN
1939                         ALLOCATE( u_center_av(nzb:nzt+1,nys:nyn,nxl:nxr) )
1940                      ENDIF
1941                      IF ( k == 1 )  THEN
1942                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file:nyn_on_file,             &
1943                                                       nxl_on_file:nxr_on_file) )
1944                         READ ( 13 )  tmp_3d_non_standard
1945                      ENDIF
1946                      u_center_av(:,nysc:nync,nxlc:nxrc) = tmp_3d_non_standard(:,nysf:nynf,nxlf:nxrf)
[4431]1947
[4517]1948                   CASE ( 'uu_av' )
1949                      IF ( .NOT. ALLOCATED( uu_av ) )  THEN
1950                         ALLOCATE( uu_av(nzb:nzt+1,nys:nyn,nxl:nxr) )
1951                      ENDIF
1952                      IF ( k == 1 )  THEN
1953                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file:nyn_on_file,             &
1954                                                       nxl_on_file:nxr_on_file) )
1955                         READ ( 13 )  tmp_3d_non_standard
1956                      ENDIF
1957                      uu_av(:,nysc:nync,nxlc:nxrc) = tmp_3d_non_standard(:,nysf:nynf,nxlf:nxrf)
[2894]1958
[4517]1959                   CASE ( 'uv_10m_av' )
1960                      IF ( .NOT. ALLOCATED( uv_10m_av ) )  THEN
1961                         ALLOCATE( uv_10m_av(nysg:nyng,nxlg:nxrg) )
1962                      ENDIF
1963                      IF ( k == 1 )  READ ( 13 )  tmp_2d
1964                      uv_10m_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                           &
1965                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[4331]1966
[4517]1967                   CASE ( 'u_m_l' )
1968                      IF ( k == 1 )  THEN
1969                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,   &
1970                                                       1:2) )
1971                         READ ( 13 )  tmp_3d_non_standard
1972                      ENDIF
1973                      IF ( bc_radiation_l )  THEN
1974                         u_m_l(:,nysc-nbgp:nync+nbgp,:) =  tmp_3d_non_standard(:,nysf-nbgp:nynf+nbgp,:)
1975                      ENDIF
[2894]1976
[4517]1977                   CASE ( 'u_m_n' )
1978                      IF ( k == 1 )  THEN
1979                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,ny-1:ny,                             &
1980                                                       nxl_on_file-nbgp:nxr_on_file+nbgp) )
1981                         READ ( 13 )  tmp_3d_non_standard
1982                      ENDIF
1983                      IF ( bc_radiation_n )  THEN
1984                         u_m_n(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3d_non_standard(:,:,nxlf-nbgp:nxrf+nbgp)
1985                      ENDIF
[2894]1986
[4517]1987                   CASE ( 'u_m_r' )
1988                      IF ( k == 1 )  THEN
1989                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,   &
1990                                                       nx-1:nx) )
1991                         READ ( 13 )  tmp_3d_non_standard
1992                      ENDIF
1993                      IF ( bc_radiation_r )  THEN
1994                         u_m_r(:,nysc-nbgp:nync+nbgp,:) = tmp_3d_non_standard(:,nysf-nbgp:nynf+nbgp,:)
1995                      ENDIF
[2894]1996
[4517]1997                   CASE ( 'u_m_s' )
1998                      IF ( k == 1 )  THEN
1999                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,0:1,                                 &
2000                                                       nxl_on_file-nbgp:nxr_on_file+nbgp) )
2001                         READ ( 13 )  tmp_3d_non_standard
2002                      ENDIF
2003                      IF ( bc_radiation_s )  THEN
2004                         u_m_s(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3d_non_standard(:,:,nxlf-nbgp:nxrf+nbgp)
2005                      ENDIF
[2894]2006
[4517]2007                   CASE ( 'us_av' )
2008                      IF ( .NOT. ALLOCATED( us_av ) )  THEN
2009                         ALLOCATE( us_av(nysg:nyng,nxlg:nxrg) )
2010                      ENDIF
2011                      IF ( k == 1 )  READ ( 13 )  tmp_2d
2012                      us_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                               &
2013                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]2014
[4517]2015                   CASE ( 'v' )
2016                      IF ( k == 1 )  READ ( 13 )  tmp_3d
2017                      v(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
2018                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]2019
[4517]2020                   CASE ( 'v_av' )
2021                      IF ( .NOT. ALLOCATED( v_av ) )  THEN
2022                         ALLOCATE( v_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2023                      ENDIF
2024                      IF ( k == 1 )  READ ( 13 )  tmp_3d
2025                      v_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
2026                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[4431]2027
[4517]2028                   CASE ( 'v_center_av' )
2029                      IF ( .NOT. ALLOCATED( v_center_av ) )  THEN
2030                         ALLOCATE( v_center_av(nzb:nzt+1,nys:nyn,nxl:nxr) )
2031                      ENDIF
2032                      IF ( k == 1 )  THEN
2033                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file:nyn_on_file,             &
2034                                                       nxl_on_file:nxr_on_file) )
2035                         READ ( 13 )  tmp_3d_non_standard
2036                      ENDIF
2037                      v_center_av(:,nysc:nync,nxlc:nxrc) = tmp_3d_non_standard(:,nysf:nynf,nxlf:nxrf)
[4431]2038
[4517]2039                   CASE ( 'vv_av' )
2040                      IF ( .NOT. ALLOCATED( vv_av ) )  THEN
[4039]2041                      ALLOCATE( vv_av(nzb:nzt+1,nys:nyn,nxl:nxr) )
[4517]2042                      ENDIF
2043                      IF ( k == 1 )  THEN
2044                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file:nyn_on_file,             &
2045                                                       nxl_on_file:nxr_on_file) )
2046                         READ ( 13 )  tmp_3d_non_standard
2047                      ENDIF
2048                      vv_av(:,nysc:nync,nxlc:nxrc) = tmp_3d_non_standard(:,nysf:nynf,nxlf:nxrf)
[2894]2049
[4517]2050                   CASE ( 'v_m_l' )
2051                      IF ( k == 1 )  THEN
2052                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,   &
2053                                                       0:1) )
2054                         READ ( 13 )  tmp_3d_non_standard
2055                      ENDIF
2056                      IF ( bc_radiation_l )  THEN
2057                         v_m_l(:,nysc-nbgp:nync+nbgp,:) = tmp_3d_non_standard(:,nysf-nbgp:nynf+nbgp,:)
2058                      ENDIF
[2894]2059
[4517]2060                   CASE ( 'v_m_n' )
2061                      IF ( k == 1 )  THEN
2062                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,ny-1:ny,                             &
2063                                                       nxl_on_file-nbgp:nxr_on_file+nbgp) )
2064                         READ ( 13 )  tmp_3d_non_standard
2065                      ENDIF
2066                      IF ( bc_radiation_n )  THEN
2067                         v_m_n(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3d_non_standard(:,:,nxlf-nbgp:nxrf+nbgp)
2068                      ENDIF
[2894]2069
[4517]2070                   CASE ( 'v_m_r' )
2071                      IF ( k == 1 )  THEN
2072                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,   &
2073                                                       nx-1:nx) )
2074                         READ ( 13 )  tmp_3d_non_standard
2075                      ENDIF
2076                      IF ( bc_radiation_r )  THEN
2077                         v_m_r(:,nysc-nbgp:nync+nbgp,:) = tmp_3d_non_standard(:,nysf-nbgp:nynf+nbgp,:)
2078                      ENDIF
[2894]2079
[4517]2080                   CASE ( 'v_m_s' )
2081                      IF ( k == 1 )  THEN
2082                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,1:2,                                 &
2083                                                       nxl_on_file-nbgp:nxr_on_file+nbgp) )
2084                         READ ( 13 )  tmp_3d_non_standard
2085                      ENDIF
2086                      IF ( bc_radiation_s )  THEN
2087                         v_m_s(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3d_non_standard(:,:,nxlf-nbgp:nxrf+nbgp)
2088                      ENDIF
[2894]2089
[4517]2090                   CASE ( 'vpt' )
2091                      IF ( k == 1 )  READ ( 13 )  tmp_3d
2092                      vpt(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                &
2093                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]2094
[4517]2095                   CASE ( 'vpt_av' )
2096                      IF ( .NOT. ALLOCATED( vpt_av ) )  THEN
2097                         ALLOCATE( vpt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2098                      ENDIF
2099                      IF ( k == 1 )  READ ( 13 )  tmp_3d
2100                      vpt_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                             &
2101                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]2102
[4517]2103                   CASE ( 'w' )
2104                      IF ( k == 1 )  READ ( 13 )  tmp_3d
2105                      w(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                                  &
2106                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]2107
[4517]2108                   CASE ( 'w_av' )
2109                      IF ( .NOT. ALLOCATED( w_av ) )  THEN
2110                         ALLOCATE( w_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2111                      ENDIF
2112                      IF ( k == 1 )  READ ( 13 )  tmp_3d
2113                      w_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) =                               &
2114                         tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[4431]2115
[4517]2116                   CASE ( 'ww_av' )
2117                      IF ( .NOT. ALLOCATED( ww_av ) )  THEN
2118                         ALLOCATE( ww_av(nzb:nzt+1,nys:nyn,nxl:nxr) )
2119                      ENDIF
2120                      IF ( k == 1 )  THEN
2121                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file:nyn_on_file,             &
2122                                                       nxl_on_file:nxr_on_file) )
2123                         READ ( 13 )  tmp_3d_non_standard
2124                      ENDIF
2125                      ww_av(:,nysc:nync,nxlc:nxrc) = tmp_3d_non_standard(:,nysf:nynf,nxlf:nxrf)
[2894]2126
[4517]2127                   CASE ( 'w_m_l' )
2128                      IF ( k == 1 )  THEN
2129                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,   &
2130                                                       0:1) )
2131                         READ ( 13 )  tmp_3d_non_standard
2132                      ENDIF
2133                      IF ( bc_radiation_l )  THEN
2134                         w_m_l(:,nysc-nbgp:nync+nbgp,:) = tmp_3d_non_standard(:,nysf-nbgp:nynf+nbgp,:)
2135                      ENDIF
[2894]2136
[4517]2137                   CASE ( 'w_m_n' )
2138                      IF ( k == 1 )  THEN
2139                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,ny-1:ny,                             &
2140                                                       nxl_on_file-nbgp:nxr_on_file+nbgp) )
2141                         READ ( 13 )  tmp_3d_non_standard
2142                      ENDIF
2143                      IF ( bc_radiation_n )  THEN
2144                         w_m_n(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3d_non_standard(:,:,nxlf-nbgp:nxrf+nbgp)
2145                      ENDIF
[2894]2146
[4517]2147                   CASE ( 'w_m_r' )
2148                      IF ( k == 1 )  THEN
2149                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp,   &
2150                                                       nx-1:nx) )
2151                         READ ( 13 )  tmp_3d_non_standard
2152                      ENDIF
2153                      IF ( bc_radiation_r )  THEN
2154                         w_m_r(:,nysc-nbgp:nync+nbgp,:) = tmp_3d_non_standard(:,nysf-nbgp:nynf+nbgp,:)
2155                      ENDIF
[2894]2156
[4517]2157                   CASE ( 'w_m_s' )
2158                      IF ( k == 1 )  THEN
2159                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,0:1,                                 &
2160                                                       nxl_on_file-nbgp:nxr_on_file+nbgp) )
2161                         READ ( 13 )  tmp_3d_non_standard
2162                      ENDIF
2163                      IF ( bc_radiation_s )  THEN
2164                         w_m_s(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3d_non_standard(:,:,nxlf-nbgp:nxrf+nbgp)
2165                      ENDIF
[2894]2166
[4517]2167                   CASE ( 'wspeed_av' )
2168                      IF ( .NOT. ALLOCATED( wspeed_av ) )  THEN
2169                         ALLOCATE( wspeed_av(nzb:nzt+1,nys:nyn,nxl:nxr) )
2170                      ENDIF
2171                      IF ( k == 1 )  THEN
2172                         ALLOCATE( tmp_3d_non_standard(nzb:nzt+1,nys_on_file:nyn_on_file,             &
2173                                                       nxl_on_file:nxr_on_file) )
2174                         READ ( 13 )  tmp_3d_non_standard
2175                      ENDIF
2176                      wspeed_av(:,nysc:nync,nxlc:nxrc) = tmp_3d_non_standard(:,nysf:nynf,nxlf:nxrf)
[4431]2177
[4517]2178                   CASE ( 'z0_av' )
2179                      IF ( .NOT. ALLOCATED( z0_av ) )  THEN
2180                         ALLOCATE( z0_av(nysg:nyng,nxlg:nxrg) )
2181                      ENDIF
2182                      IF ( k == 1 )  READ ( 13 )  tmp_2d
2183                      z0_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                               &
2184                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]2185
[4517]2186                   CASE ( 'z0h_av' )
2187                      IF ( .NOT. ALLOCATED( z0h_av ) )  THEN
2188                         ALLOCATE( z0h_av(nysg:nyng,nxlg:nxrg) )
2189                      ENDIF
2190                      IF ( k == 1 )  READ ( 13 )  tmp_2d
2191                      z0h_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                              &
2192                          tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]2193
[4517]2194                   CASE ( 'z0q_av' )
2195                      IF ( .NOT. ALLOCATED( z0q_av ) )  THEN
2196                         ALLOCATE( z0q_av(nysg:nyng,nxlg:nxrg) )
2197                      ENDIF
2198                      IF ( k == 1 )  READ ( 13 )  tmp_2d
2199                      z0q_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  =                              &
2200                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
[2894]2201
[4517]2202                   CASE DEFAULT
[2894]2203
2204!
[4517]2205!--                   Read restart data of surfaces
2206                      IF ( .NOT. found )  CALL surface_rrd_local( k, nxlf, nxlc, nxl_on_file, nxrf,   &
2207                                                                  nxr_on_file, nynf, nyn_on_file,     &
2208                                                                  nysf, nysc, nys_on_file, found )
[2912]2209!
[4517]2210!--                   Read restart data of other modules
2211                      IF ( .NOT. found ) CALL module_interface_rrd_local(                             &
2212                                                                  k, nxlf, nxlc, nxl_on_file, nxrf,   &
2213                                                                  nxrc, nxr_on_file, nynf, nync,      &
2214                                                                  nyn_on_file, nysf, nysc,            &
2215                                                                  nys_on_file, tmp_2d, tmp_3d, found )
[2894]2216
2217
[4517]2218                      IF ( .NOT. found )  THEN
2219                         WRITE( message_string, * ) 'unknown variable named "',                       &
2220                                                    restart_string(1:length),                         &
2221                                                   '" found in subdomain data ',                      &
2222                                                   'from prior run on PE ', myid
2223                         CALL message( 'rrd_local', 'PA0302', 1, 2, 0, 6, 0 )
[4431]2224
[4517]2225                      ENDIF
[2894]2226
[4517]2227                END SELECT
[2894]2228
[4517]2229             ENDDO ! overlaploop
[2894]2230
2231!
[4517]2232!--          Deallocate non standard array needed for specific variables only
2233             IF ( ALLOCATED( tmp_3d_non_standard ) )  DEALLOCATE( tmp_3d_non_standard )
[2894]2234
2235!
[4517]2236!--          Read next character string
2237             READ ( 13 )  length
2238             READ ( 13 )  restart_string(1:length)
[2894]2239
[4517]2240          ENDDO ! dataloop
[2894]2241!
[4517]2242!--       Close the restart file
2243          CALL close_file( 13 )
[2894]2244
[4517]2245          DEALLOCATE( tmp_2d, tmp_3d )
[2894]2246
[4517]2247       ENDDO  ! loop over restart files
[2894]2248!
[4517]2249!--    Deallocate temporary buffer arrays
2250       DEALLOCATE( nxlfa )
2251       DEALLOCATE( nxrfa )
2252       DEALLOCATE( nynfa )
2253       DEALLOCATE( nysfa )
2254       DEALLOCATE( offset_xa )
2255       DEALLOCATE( offset_ya )
[4356]2256!
[4517]2257!--    Restore the original filename for the restart file to be written
2258       myid_char = myid_char_save
[2894]2259
[4517]2260
2261    ELSEIF ( TRIM( restart_data_format_input ) == 'mpi' )  THEN
2262
[2894]2263!
[4517]2264!--    Read global restart data using MPI-IO
2265!
2266!--    Open the MPI-IO restart file.
2267       CALL rd_mpi_io_open( 'read', 'BININ' // TRIM( coupling_char ) )
2268
2269
2270       CALL rd_mpi_io_check_array( 'ghf_av' , found = array_found )
2271       IF ( array_found )  THEN
2272          IF (.NOT. ALLOCATED( ghf_av ) )  ALLOCATE( ghf_av(nysg:nyng,nxlg:nxrg) )
2273          CALL rrd_mpi_io( 'ghf_av', ghf_av )
2274       ENDIF
2275
2276       CALL rrd_mpi_io( 'e', e )
2277
2278       CALL rd_mpi_io_check_array( 'e_av' , found = array_found )
2279       IF ( array_found  )  THEN
2280          IF ( .NOT. ALLOCATED( e_av ) )  ALLOCATE( e_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2281          CALL rrd_mpi_io( 'e_av', e_av )
2282       ENDIF
2283
2284       CALL rrd_mpi_io( 'kh', kh )
2285
2286       CALL rd_mpi_io_check_array( 'kh_av' , found = array_found )
2287       IF ( array_found )  THEN
2288          IF ( .NOT. ALLOCATED( kh_av ) )  ALLOCATE( kh_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2289          CALL rrd_mpi_io( 'kh_av', kh_av )
2290       ENDIF
2291
2292       CALL rrd_mpi_io( 'km' , km)
2293
2294       CALL rd_mpi_io_check_array( 'km_av' , found = array_found )
2295       IF ( array_found )  THEN
2296          IF ( .NOT. ALLOCATED( km_av ) )  ALLOCATE( km_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2297          CALL rrd_mpi_io( 'km_av', km_av )
2298       ENDIF
2299
2300       CALL rd_mpi_io_check_array( 'lpt_av' , found = array_found )
2301       IF ( array_found )  THEN
2302          IF ( .NOT. ALLOCATED( lpt_av ) )  ALLOCATE( lpt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2303          CALL rrd_mpi_io( 'lpt_av', lpt_av )
2304       ENDIF
2305
2306       CALL rd_mpi_io_check_array( 'lwp_av' , found = array_found )
2307       IF ( array_found )  THEN
2308          IF ( .NOT. ALLOCATED( lwp_av ) )  ALLOCATE( lwp_av(nysg:nyng,nxlg:nxrg) )
2309          CALL rrd_mpi_io( 'lwp_av', lwp_av )
2310       ENDIF
2311
2312       CALL rrd_mpi_io( 'p', p)
2313
2314       CALL rd_mpi_io_check_array( 'p_av' , found = array_found )
2315       IF ( array_found )  THEN
2316          IF ( .NOT. ALLOCATED( p_av ) )  ALLOCATE( p_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2317          CALL rrd_mpi_io( 'p_av', p_av )
2318       ENDIF
2319
2320       CALL rrd_mpi_io( 'pt', pt)
2321
2322       CALL rd_mpi_io_check_array( 'pt_av' , found = array_found )
2323       IF ( array_found )  THEN
2324          IF ( .NOT. ALLOCATED( pt_av ) )  ALLOCATE( pt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2325          CALL rrd_mpi_io( 'pt_av', pt_av )
2326       ENDIF
2327
2328       CALL rd_mpi_io_check_array( 'pt_2m_av' , found = array_found )
2329       IF ( array_found )  THEN
2330          IF ( .NOT. ALLOCATED( pt_2m_av ) )  ALLOCATE( pt_2m_av(nysg:nyng,nxlg:nxrg) )
2331          CALL rrd_mpi_io( 'pt_2m_av', pt_2m_av )
2332       ENDIF
2333
2334       CALL rd_mpi_io_check_array( 'q' , found = array_found )
2335       IF ( array_found )  THEN
2336          CALL rrd_mpi_io( 'q', q )
2337       ENDIF
2338
2339       CALL rd_mpi_io_check_array( 'q_av' , found = array_found )
2340       IF ( array_found )  THEN
2341          IF ( .NOT. ALLOCATED( q_av ) )  ALLOCATE( q_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2342          CALL rrd_mpi_io( 'q_av', q_av )
2343       ENDIF
2344
2345       CALL rd_mpi_io_check_array( 'ql' , found = array_found )
2346       IF ( array_found )  THEN
2347          CALL rrd_mpi_io( 'ql', ql )
2348       ENDIF
2349
2350       CALL rd_mpi_io_check_array( 'ql_av' , found = array_found )
2351       IF ( array_found )  THEN
2352          IF ( .NOT. ALLOCATED( ql_av ) )  ALLOCATE( ql_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2353          CALL rrd_mpi_io( 'ql_av', ql_av )
2354       ENDIF
2355
2356       CALL rd_mpi_io_check_array( 'qsurf_av' , found = array_found )
2357       IF ( array_found )  THEN
2358          IF ( .NOT. ALLOCATED( qsurf_av ) )  ALLOCATE( qsurf_av(nysg:nyng,nxlg:nxrg) )
2359          CALL rrd_mpi_io( 'qsurf_av', qsurf_av )
2360       ENDIF
2361
2362       CALL rd_mpi_io_check_array( 'qsws_av' , found = array_found )
2363       IF ( array_found )  THEN
2364          IF ( .NOT. ALLOCATED( qsws_av ) )  ALLOCATE( qsws_av(nysg:nyng,nxlg:nxrg) )
2365          CALL rrd_mpi_io( 'qsws_av', qsws_av )
2366       ENDIF
2367
2368       CALL rd_mpi_io_check_array( 'qv_av' , found = array_found )
2369       IF ( array_found )  THEN
2370          IF ( .NOT. ALLOCATED( qv_av ) )  ALLOCATE( qv_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2371          CALL rrd_mpi_io( 'qv_av', qv_av )
2372       ENDIF
2373
2374       CALL rd_mpi_io_check_array( 'r_a_av' , found = array_found )
2375       IF ( array_found )  THEN
2376          IF ( .NOT. ALLOCATED( r_a_av ) )  ALLOCATE( r_a_av(nysg:nyng,nxlg:nxrg) )
2377          CALL rrd_mpi_io( 'r_a_av', r_a_av )
2378       ENDIF
2379
2380!
2381!--    ATTENTION: The random seeds are global data! If independent values for every PE are required,
2382!--    the general approach of PE indendent restart will be lost. That means that in general the
2383!--    parallel random number generator in random_generator_parallel_mod should be used!
2384       CALL rrd_mpi_io_global_array( 'random_iv', random_iv )
2385       CALL rrd_mpi_io( 'random_iy', random_iy )
2386
2387       CALL rd_mpi_io_check_array( 'id_random_array' , found = array_found )
2388       IF ( array_found )  THEN
2389          IF ( .NOT. ALLOCATED( id_random_array ) )  ALLOCATE( id_random_array(nys:nyn,nxl:nxr) )
2390          IF ( .NOT. ALLOCATED( seq_random_array ) )  ALLOCATE( seq_random_array(5,nys:nyn,nxl:nxr) )
2391          CALL rrd_mpi_io( 'id_random_array', id_random_array)
2392          DO  i = 1, SIZE( seq_random_array, 1 )
2393             WRITE( tmp_name, '(A,I2.2)' )  'seq_random_array', i
2394             CALL rrd_mpi_io( TRIM(tmp_name), seq_random_array(i,:,:) )
2395          ENDDO
2396       ENDIF
2397
2398       CALL rd_mpi_io_check_array( 's' , found = array_found )
2399       IF ( array_found )  THEN
2400          CALL rrd_mpi_io( 's', s )
2401       ENDIF
2402
2403       CALL rd_mpi_io_check_array( 's_av' , found = array_found )
2404       IF ( array_found )  THEN
2405          IF ( .NOT. ALLOCATED( s_av ) )  ALLOCATE( s_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2406          CALL rrd_mpi_io( 's_av', s_av )
2407       ENDIF
2408
2409       CALL rd_mpi_io_check_array( 'shf_av' , found = array_found )
2410       IF ( array_found )  THEN
2411          IF ( .NOT. ALLOCATED( shf_av ) )  ALLOCATE( shf_av(nysg:nyng,nxlg:nxrg) )
2412          CALL rrd_mpi_io( 'shf_av', shf_av )
2413       ENDIF
2414
2415       CALL rd_mpi_io_check_array( 'ssurf_av' , found = array_found )
2416       IF ( array_found )  THEN
2417          IF ( .NOT. ALLOCATED( ssurf_av ) )  ALLOCATE( ssurf_av(nysg:nyng,nxlg:nxrg) )
2418          CALL rrd_mpi_io( 'ssurf_av', ssurf_av )
2419       ENDIF
2420
2421       CALL rd_mpi_io_check_array( 'ssws_av' , found = array_found )
2422       IF ( array_found )  THEN
2423          IF ( .NOT. ALLOCATED( ssws_av ) )  ALLOCATE( ssws_av(nysg:nyng,nxlg:nxrg) )
2424          CALL rrd_mpi_io( 'ssws_av', ssws_av )
2425       ENDIF
2426
2427       CALL rd_mpi_io_check_array( 'ti_av' , found = array_found )
2428       IF ( array_found )  THEN
2429          IF ( .NOT. ALLOCATED( ti_av ) )  ALLOCATE( ti_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2430          CALL rrd_mpi_io( 'ti_av', ti_av )
2431       ENDIF
2432
2433       CALL rd_mpi_io_check_array( 'ts_av' , found = array_found )
2434       IF ( array_found )  THEN
2435          IF ( .NOT. ALLOCATED( ts_av ) )  ALLOCATE( ts_av(nysg:nyng,nxlg:nxrg) )
2436          CALL rrd_mpi_io( 'ts_av', ts_av )
2437       ENDIF
2438
2439       CALL rd_mpi_io_check_array( 'tsurf_av' , found = array_found )
2440       IF ( array_found )  THEN
2441          IF ( .NOT. ALLOCATED( tsurf_av ) )  ALLOCATE( tsurf_av(nysg:nyng,nxlg:nxrg) )
2442          CALL rrd_mpi_io( 'tsurf_av', tsurf_av )
2443       ENDIF
2444
2445       CALL rrd_mpi_io( 'u', u)
2446
2447       CALL rd_mpi_io_check_array( 'u_av' , found = array_found )
2448       IF ( array_found )  THEN
2449          IF ( .NOT. ALLOCATED( u_av ) )  ALLOCATE( u_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2450          CALL rrd_mpi_io( 'u_av', u_av )
2451       ENDIF
2452
2453       CALL rd_mpi_io_check_array( 'u_center_av' , found = array_found )
2454       IF ( array_found )  THEN
2455          IF ( .NOT. ALLOCATED( u_center_av ) )  ALLOCATE( u_center_av(nzb:nzt+1,nys:nyn,nxl:nxr) )
2456          CALL rrd_mpi_io( 'u_center_av', u_center_av )
2457       ENDIF
2458
2459       CALL rd_mpi_io_check_array( 'uu_av' , found = array_found )
2460       IF ( array_found )  THEN
2461          IF ( .NOT. ALLOCATED( uu_av ) )  ALLOCATE( uu_av(nzb:nzt+1,nys:nyn,nxl:nxr) )
2462          CALL rrd_mpi_io( 'uu_av', uu_av )
2463       ENDIF
2464
2465       CALL rd_mpi_io_check_array( 'uv_10m_av' , found = array_found )
2466       IF ( array_found )  THEN
2467          IF ( .NOT. ALLOCATED( uv_10m_av ) )  ALLOCATE( uv_10m_av(nysg:nyng,nxlg:nxrg) )
2468          CALL rrd_mpi_io( 'uv_10m_av', uv_10m_av )
2469       ENDIF
2470
2471       CALL rd_mpi_io_check_array( 'u_m_l' , found = array_found )
2472       IF ( array_found )  THEN
2473          IF ( .NOT. ALLOCATED( u_m_l ) )  ALLOCATE( u_m_l(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2474          CALL rrd_mpi_io( 'u_m_l', u_m_l )
2475       ENDIF
2476
2477       CALL rd_mpi_io_check_array( 'u_m_n' , found = array_found )
2478       IF ( array_found )  THEN
2479          IF ( .NOT. ALLOCATED( u_m_n ) )  ALLOCATE( u_m_n(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2480          CALL rrd_mpi_io( 'u_m_n', u_m_n )
2481       ENDIF
2482
2483       CALL rd_mpi_io_check_array( 'u_m_r' , found = array_found )
2484       IF ( array_found )  THEN
2485          IF ( .NOT. ALLOCATED( u_m_r ) )  ALLOCATE( u_m_r(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2486          CALL rrd_mpi_io( 'u_m_r', u_m_r )
2487       ENDIF
2488
2489       CALL rd_mpi_io_check_array( 'u_m_s' , found = array_found )
2490       IF ( array_found )  THEN
2491          IF ( .NOT. ALLOCATED( u_m_s ) )  ALLOCATE( u_m_s(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2492          CALL rrd_mpi_io( 'u_m_s', u_m_s )
2493       ENDIF
2494
2495       CALL rd_mpi_io_check_array( 'us_av' , found = array_found )
2496       IF ( array_found )  THEN
2497          IF ( .NOT. ALLOCATED( us_av ) )  ALLOCATE( us_av(nysg:nyng,nxlg:nxrg) )
2498          CALL rrd_mpi_io( 'us_av', us_av )
2499       ENDIF
2500
2501       CALL rrd_mpi_io( 'v', v )
2502
2503       CALL rd_mpi_io_check_array( 'v_av' , found = array_found )
2504       IF ( array_found )  THEN
2505          IF ( .NOT. ALLOCATED( v_av ) )  ALLOCATE( v_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2506          CALL rrd_mpi_io( 'v_av', v_av )
2507       ENDIF
2508
2509       CALL rd_mpi_io_check_array( 'v_center_av' , found = array_found )
2510       IF ( array_found )  THEN
2511          IF ( .NOT. ALLOCATED( v_center_av ) )  ALLOCATE( v_center_av(nzb:nzt+1,nys:nyn,nxl:nxr) )
2512          CALL rrd_mpi_io( 'v_center_av', v_center_av )
2513       ENDIF
2514
2515       CALL rd_mpi_io_check_array( 'vv_av' , found = array_found )
2516       IF ( array_found )  THEN
2517          IF ( .NOT. ALLOCATED( vv_av ) )  ALLOCATE( vv_av(nzb:nzt+1,nys:nyn,nxl:nxr) )
2518          CALL rrd_mpi_io( 'vv_av', vv_av )
2519       ENDIF
2520
2521       CALL rd_mpi_io_check_array( 'v_m_l' , found = array_found )
2522       IF ( array_found )  THEN
2523          IF ( .NOT. ALLOCATED( v_m_l ) )  ALLOCATE( v_m_l(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2524          CALL rrd_mpi_io( 'v_m_l', v_m_l )
2525       ENDIF
2526
2527       CALL rd_mpi_io_check_array( 'v_m_n' , found = array_found )
2528       IF ( array_found )  THEN
2529          IF ( .NOT. ALLOCATED( v_m_n ) )  ALLOCATE( v_m_n(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2530          CALL rrd_mpi_io( 'v_m_n', v_m_n )
2531       ENDIF
2532
2533       CALL rd_mpi_io_check_array( 'v_m_r' , found = array_found )
2534       IF ( array_found )  THEN
2535          IF ( .NOT. ALLOCATED( v_m_r ) )  ALLOCATE( v_m_r(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2536          CALL rrd_mpi_io( 'v_m_r', v_m_r )
2537       ENDIF
2538
2539       CALL rd_mpi_io_check_array( 'v_m_s' , found = array_found )
2540       IF ( array_found )  THEN
2541          IF ( .NOT. ALLOCATED( v_m_s ) )  ALLOCATE( v_m_s(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2542          CALL rrd_mpi_io( 'v_m_s', v_m_s )
2543       ENDIF
2544
2545       CALL rd_mpi_io_check_array( 'vpt' , found = array_found )
2546       IF ( array_found )  THEN
2547          CALL rrd_mpi_io( 'vpt',  vpt)
2548       ENDIF
2549
2550       CALL rd_mpi_io_check_array( 'vpt_av' , found = array_found )
2551       IF ( array_found )  THEN
2552          IF ( .NOT. ALLOCATED( vpt_av ) )  ALLOCATE( vpt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2553          CALL rrd_mpi_io( 'vpt_av', vpt_av )
2554       ENDIF
2555
2556       CALL rrd_mpi_io( 'w', w)
2557
2558       CALL rd_mpi_io_check_array( 'w_av' , found = array_found )
2559       IF ( array_found )  THEN
2560          IF ( .NOT. ALLOCATED( w_av ) )  ALLOCATE( w_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2561          CALL rrd_mpi_io( 'w_av', w_av )
2562       ENDIF
2563
2564       CALL rd_mpi_io_check_array( 'ww_av' , found = array_found )
2565       IF ( array_found )  THEN
2566          IF ( .NOT. ALLOCATED( ww_av ) )  ALLOCATE( w_av(nzb:nzt+1,nys:nyn,nxl:nxr) )
2567          CALL rrd_mpi_io( 'ww_av', ww_av )
2568       ENDIF
2569
2570       CALL rd_mpi_io_check_array( 'w_m_l' , found = array_found )
2571       IF ( array_found )  THEN
2572          IF ( .NOT. ALLOCATED( w_m_l ) )  ALLOCATE( w_m_l(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2573          CALL rrd_mpi_io( 'w_m_l', w_m_l )
2574       ENDIF
2575
2576       CALL rd_mpi_io_check_array( 'w_m_n' , found = array_found )
2577       IF ( array_found )  THEN
2578          IF ( .NOT. ALLOCATED( w_m_n ) )  ALLOCATE( w_m_n(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2579          CALL rrd_mpi_io( 'w_m_n', w_m_n )
2580       ENDIF
2581
2582       CALL rd_mpi_io_check_array( 'w_m_r' , found = array_found )
2583       IF ( array_found )  THEN
2584          IF ( .NOT. ALLOCATED( w_m_r ) )  ALLOCATE( w_m_r(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2585          CALL rrd_mpi_io( 'w_m_r', w_m_r )
2586       ENDIF
2587
2588       CALL rd_mpi_io_check_array( 'w_m_s' , found = array_found )
2589       IF ( array_found )  THEN
2590          IF ( .NOT. ALLOCATED( w_m_s ) )  ALLOCATE( w_m_s(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
2591          CALL rrd_mpi_io( 'w_m_s', w_m_s )
2592       ENDIF
2593
2594       CALL rd_mpi_io_check_array( 'wspeed_av' , found = array_found )
2595       IF ( array_found )  THEN
2596          IF ( .NOT. ALLOCATED( wspeed_av ) )  ALLOCATE( wspeed_av(nzb:nzt+1,nys:nyn,nxl:nxr) )
2597          CALL rrd_mpi_io( 'wspeed_av', wspeed_av )
2598       ENDIF
2599
2600       CALL rd_mpi_io_check_array( 'z0_av' , found = array_found )
2601       IF ( array_found )  THEN
2602          IF ( .NOT. ALLOCATED( z0_av ) )  ALLOCATE( z0_av(nysg:nyng,nxlg:nxrg) )
2603          CALL rrd_mpi_io( 'z0_av', z0_av )
2604       ENDIF
2605
2606       CALL rd_mpi_io_check_array( 'z0h_av' , found = array_found )
2607       IF ( array_found )  THEN
2608          IF ( .NOT. ALLOCATED( z0h_av ) )  ALLOCATE( z0h_av(nysg:nyng,nxlg:nxrg) )
2609          CALL rrd_mpi_io( 'z0h_av', z0h_av )
2610       ENDIF
2611
2612       CALL rd_mpi_io_check_array( 'z0q_av' , found = array_found )
2613       IF ( array_found )  THEN
2614          IF ( .NOT. ALLOCATED( z0q_av ) )  ALLOCATE( z0q_av(nysg:nyng,nxlg:nxrg) )
2615          CALL rrd_mpi_io( 'z0q_av', z0q_av )
2616       ENDIF
2617
2618!
2619!--    Read restart data of surfaces
2620       CALL surface_rrd_local
2621
2622!
2623!--    Read restart data of other modules
2624       CALL module_interface_rrd_local
2625
2626!
2627!--    Close restart file
2628       CALL rd_mpi_io_close
2629
2630    ENDIF
2631
2632!
[2894]2633!-- End of time measuring for reading binary data
2634    CALL cpu_log( log_point_s(14), 'rrd_local', 'stop' )
2635
2636 END SUBROUTINE rrd_local
2637
2638
2639!------------------------------------------------------------------------------!
2640! Description:
2641! ------------
2642!> Skipping the global control variables from restart-file (binary format)
2643!------------------------------------------------------------------------------!
[4495]2644 SUBROUTINE rrd_skip_global
[2894]2645
2646
[4495]2647    CHARACTER (LEN=1) ::  cdum
[2894]2648
2649
[4495]2650    READ ( 13 )  length
2651    READ ( 13 )  restart_string(1:length)
[2894]2652
[4495]2653    DO  WHILE ( restart_string(1:length) /= 'binary_version_local' )
2654
2655       READ ( 13 )  cdum
[2894]2656       READ ( 13 )  length
2657       READ ( 13 )  restart_string(1:length)
2658
[4495]2659    ENDDO
[2894]2660
[4495]2661    BACKSPACE ( 13 )
2662    BACKSPACE ( 13 )
[2894]2663
2664
[4495]2665 END SUBROUTINE rrd_skip_global
[2894]2666
2667
2668 END MODULE read_restart_data_mod
Note: See TracBrowser for help on using the repository browser.