source: palm/trunk/SOURCE/read_3d_binary.f90 @ 667

Last change on this file since 667 was 667, checked in by suehring, 13 years ago

summary:


Gryschka:

  • Coupling with different resolution and different numbers of PEs in ocean and atmosphere is available
  • Exchange of u and v from ocean surface to atmosphere surface
  • Mirror boundary condition for u and v at the bottom are replaced by dirichlet boundary conditions
  • Inflow turbulence is now defined by flucuations around spanwise mean
  • Bugfixes for cyclic_fill and constant_volume_flow

Suehring:

  • New advection added ( Wicker and Skamarock 5th order ), therefore:
    • New module advec_ws.f90
    • Modified exchange of ghost boundaries.
    • Modified evaluation of turbulent fluxes
    • New index bounds nxlg, nxrg, nysg, nyng

advec_ws.f90


Advection scheme for scalars and momentum using the flux formulation of
Wicker and Skamarock 5th order.
Additionally the module contains of a routine using for initialisation and
steering of the statical evaluation. The computation of turbulent fluxes takes
place inside the advection routines.
In case of vector architectures Dirichlet and Radiation boundary conditions are
outstanding and not available. Furthermore simulations within topography are
not possible so far. A further routine local_diss_ij is available and is used
if a control of dissipative fluxes is desired.

check_parameters.f90


Exchange of parameters between ocean and atmosphere via PE0
Check for illegal combination of ws-scheme and timestep scheme.
Check for topography and ws-scheme.
Check for not cyclic boundary conditions in combination with ws-scheme and
loop_optimization = 'vector'.
Check for call_psolver_at_all_substeps and ws-scheme for momentum_advec.

Different processor/grid topology in atmosphere and ocean is now allowed!
Bugfixes in checking for conserve_volume_flow_mode.

exchange_horiz.f90


Dynamic exchange of ghost points with nbgp_local to ensure that no useless
ghost points exchanged in case of multigrid. type_yz(0) and type_xz(0) used for
normal grid, the remaining types used for the several grid levels.
Exchange is done via MPI-Vectors with a dynamic value of ghost points which
depend on the advection scheme. Exchange of left and right PEs is 10% faster
with MPI-Vectors than without.

flow_statistics.f90


When advection is computed with ws-scheme, turbulent fluxes are already
computed in the respective advection routines and buffered in arrays
sums_xxxx_ws_l(). This is due to a consistent treatment of statistics
with the numerics and to avoid unphysical kinks near the surface. So some if-
requests has to be done to dicern between fluxes from ws-scheme other advection
schemes. Furthermore the computation of z_i is only done if the heat flux
exceeds a minimum value. This affects only simulations of a neutral boundary
layer and is due to reasons of computations in the advection scheme.

inflow_turbulence.f90


Using nbgp recycling planes for a better resolution of the turbulent flow near
the inflow.

init_grid.f90


Definition of new array bounds nxlg, nxrg, nysg, nyng on each PE.
Furthermore the allocation of arrays and steering of loops is done with these
parameters. Call of exchange_horiz are modified.
In case of dirichlet bounday condition at the bottom zu(0)=0.0
dzu_mg has to be set explicitly for a equally spaced grid near bottom.
ddzu_pres added to use a equally spaced grid near bottom.

init_pegrid.f90


Moved determination of target_id's from init_coupling
Determination of parameters needed for coupling (coupling_topology, ngp_a, ngp_o)
with different grid/processor-topology in ocean and atmosphere

Adaption of ngp_xy, ngp_y to a dynamic number of ghost points.
The maximum_grid_level changed from 1 to 0. 0 is the normal grid, 1 to
maximum_grid_level the grids for multigrid, in which 0 and 1 are normal grids.
This distinction is due to reasons of data exchange and performance for the
normal grid and grids in poismg.
The definition of MPI-Vectors adapted to a dynamic numer of ghost points.
New MPI-Vectors for data exchange between left and right boundaries added.
This is due to reasons of performance (10% faster).

ATTENTION: nnz_x undefined problem still has to be solved!!!!!!!!
TEST OUTPUT (TO BE REMOVED) logging mpi2 ierr values

parin.f90


Steering parameter dissipation_control added in inipar.

Makefile


Module advec_ws added.

Modules


Removed u_nzb_p1_for_vfc and v_nzb_p1_for_vfc

For coupling with different resolution in ocean and atmophere:
+nx_a, +nx_o, ny_a, +ny_o, ngp_a, ngp_o, +total_2d_o, +total_2d_a,
+coupling_topology

Buffer arrays for the left sided advective fluxes added in arrays_3d.
+flux_s_u, +flux_s_v, +flux_s_w, +diss_s_u, +diss_s_v, +diss_s_w,
+flux_s_pt, +diss_s_pt, +flux_s_e, +diss_s_e, +flux_s_q, +diss_s_q,
+flux_s_sa, +diss_s_sa
3d arrays for dissipation control added. (only necessary for vector arch.)
+var_x, +var_y, +var_z, +gamma_x, +gamma_y, +gamma_z
Default of momentum_advec and scalar_advec changed to 'ws-scheme' .
+exchange_mg added in control_parameters to steer the data exchange.
Parameters +nbgp, +nxlg, +nxrg, +nysg, +nyng added in indices.
flag array +boundary_flags added in indices to steer the degradation of order
of the advective fluxes when non-cyclic boundaries are used.
MPI-datatypes +type_y, +type_y_int and +type_yz for data_exchange added in
pegrid.
+sums_wsus_ws_l, +sums_wsvs_ws_l, +sums_us2_ws_l, +sums_vs2_ws_l,
+sums_ws2_ws_l, +sums_wspts_ws_l, +sums_wssas_ws_l, +sums_wsqs_ws_l
and +weight_substep added in statistics to steer the statistical evaluation
of turbulent fluxes in the advection routines.
LOGICALS +ws_scheme_sca and +ws_scheme_mom added to get a better performance
in prognostic_equations.
LOGICAL +dissipation_control control added to steer numerical dissipation
in ws-scheme.

Changed length of string run_description_header

pres.f90


New allocation of tend when ws-scheme and multigrid is used. This is due to
reasons of perforance of the data_exchange. The same is done with p after
poismg is called.
nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng when no
multigrid is used. Calls of exchange_horiz are modified.

bugfix: After pressure correction no volume flow correction in case of
non-cyclic boundary conditions
(has to be done only before pressure correction)

Call of SOR routine is referenced with ddzu_pres.

prognostic_equations.f90


Calls of the advection routines with WS5 added.
Calls of ws_statistics added to set the statistical arrays to zero after each
time step.

advec_particles.f90


Declaration of de_dx, de_dy, de_dz adapted to additional ghost points.
Furthermore the calls of exchange_horiz were modified.

asselin_filter.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

average_3d_data.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

boundary_conds.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng
Removed mirror boundary conditions for u and v at the bottom in case of
ibc_uv_b == 0. Instead, dirichelt boundary conditions (u=v=0) are set
in init_3d_model

calc_liquid_water_content.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

calc_spectra.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng for
allocation of tend.

check_open.f90


Output of total array size was adapted to nbgp.

data_output_2d.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng in loops and
allocation of arrays local_2d and total_2d.
Calls of exchange_horiz are modified.

data_output_2d.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng in loops and
allocation of arrays. Calls of exchange_horiz are modified.
Skip-value skip_do_avs changed to a dynamic adaption of ghost points.

data_output_mask.f90


Calls of exchange_horiz are modified.

diffusion_e.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

diffusion_s.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

diffusion_u.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

diffusion_v.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

diffusion_w.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

diffusivities.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

diffusivities.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.
Calls of exchange_horiz are modified.

exchange_horiz_2d.f90


Dynamic exchange of ghost points with nbgp, which depends on the advection
scheme. Exchange between left and right PEs is now done with MPI-vectors.

global_min_max.f90


Adapting of the index arrays, because MINLOC assumes lowerbound
at 1 and not at nbgp.

init_3d_model.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng in loops and
allocation of arrays. Calls of exchange_horiz are modified.
Call ws_init to initialize arrays needed for statistical evaluation and
optimization when ws-scheme is used.
Initial volume flow is now calculated by using the variable hom_sum.
Therefore the correction of initial volume flow for non-flat topography
removed (removed u_nzb_p1_for_vfc and v_nzb_p1_for_vfc)
Changed surface boundary conditions for u and v in case of ibc_uv_b == 0 from
mirror bc to dirichlet boundary conditions (u=v=0), so that k=nzb is
representative for the height z0

Bugfix: type conversion of '1' to 64bit for the MAX function (ngp_3d_inner)

init_coupling.f90


determination of target_id's moved to init_pegrid

init_pt_anomaly.f90


Call of exchange_horiz are modified.

init_rankine.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.
Calls of exchange_horiz are modified.

init_slope.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.

header.f90


Output of advection scheme.

poismg.f90


Calls of exchange_horiz are modified.

prandtl_fluxes.f90


Changed surface boundary conditions for u and v from mirror bc to dirichelt bc,
therefore u(uzb,:,:) and v(nzb,:,:) is now representative for the height z0
nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

production_e.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng

read_3d_binary.f90


+/- 1 replaced with +/- nbgp when swapping and allocating variables.

sor.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.
Call of exchange_horiz are modified.
bug removed in declaration of ddzw(), nz replaced by nzt+1

subsidence.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.

sum_up_3d_data.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.

surface_coupler.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng in
MPI_SEND() and MPI_RECV.
additional case for nonequivalent processor and grid topopolgy in ocean and
atmosphere added (coupling_topology = 1)

Added exchange of u and v from Ocean to Atmosphere

time_integration.f90


Calls of exchange_horiz are modified.
Adaption to slooping surface.

timestep.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.

user_3d_data_averaging.f90, user_data_output_2d.f90, user_data_output_3d.f90,
user_actions.f90, user_init.f90, user_init_plant_canopy.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.

user_read_restart_data.f90


Allocation with nbgp.

wall_fluxes.f90


nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng.

write_compressed.f90


Array bounds and nx, ny adapted with nbgp.

sor.f90


bug removed in declaration of ddzw(), nz replaced by nzt+1

  • Property svn:keywords set to Id
File size: 43.6 KB
Line 
1 SUBROUTINE read_3d_binary
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6! +/- 1 replaced with +/- nbgp when swapping and allocating variables.
7! Bugfix: When using initializing_actions = 'cyclic_fill' in some cases
8! not the whole model domain was filled with data of the prerun.
9!
10! Former revisions:
11! -----------------
12! $Id: read_3d_binary.f90 667 2010-12-23 12:06:00Z suehring $
13!
14! 410 2009-12-04 17:05:40Z letzel
15! format changed in test output from I2 to I4
16!
17! 367 2009-08-25 08:35:52Z maronga
18! Output of messages replaced by message handling routine.
19! +shf_av, qsws_av
20!
21! 220 2008-12-18 07:00:36Z raasch
22! reading mechanism completely revised (subdomain/total domain size can vary
23! arbitrarily between current and previous run)
24! Bugfix: reading of spectrum_x|y from restart files ignored if total numbers
25! of grid points do not match
26!
27! 150 2008-02-29 08:19:58Z raasch
28! Files from which restart data are to be read are determined and subsequently
29! opened. The total domain on the restart file is allowed to be smaller than
30! the current total domain. In this case it will be periodically mapped on the
31! current domain (needed for recycling method).
32! +call of user_read_restart_data, -dopr_time_count,
33! hom_sum, volume_flow_area, volume_flow_initial moved to read_var_list,
34! reading of old profil parameters (cross_..., dopr_crossindex, profile_***)
35! removed, initialization of spectrum_x|y removed
36!
37! 102 2007-07-27 09:09:17Z raasch
38! +uswst, uswst_m, vswst, vswst_m
39!
40! 96 2007-06-04 08:07:41Z raasch
41! +rho_av, sa, sa_av, saswsb, saswst
42!
43! 73 2007-03-20 08:33:14Z raasch
44! +precipitation_amount, precipitation_rate_av, rif_wall, u_m_l, u_m_r, etc.,
45! z0_av
46!
47! 19 2007-02-23 04:53:48Z raasch
48! +qswst, qswst_m, tswst, tswst_m
49!
50! RCS Log replace by Id keyword, revision history cleaned up
51!
52! Revision 1.4  2006/08/04 15:02:32  raasch
53! +iran, iran_part
54!
55! Revision 1.1  2004/04/30 12:47:27  raasch
56! Initial revision
57!
58!
59! Description:
60! ------------
61! Binary input of variables and arrays from restart file
62!------------------------------------------------------------------------------!
63
64    USE arrays_3d
65    USE averaging
66    USE cloud_parameters
67    USE control_parameters
68    USE cpulog
69    USE indices
70    USE interfaces
71    USE particle_attributes
72    USE pegrid
73    USE profil_parameter
74    USE random_function_mod
75    USE statistics
76
77    IMPLICIT NONE
78
79    CHARACTER (LEN=5)  ::  myid_char_save
80    CHARACTER (LEN=10) ::  binary_version, version_on_file
81    CHARACTER (LEN=20) ::  field_chr
82
83    INTEGER ::  files_to_be_opened, i, j, k, myid_on_file,                    &
84                numprocs_on_file, nxlc, nxlf, nxlpr, nxl_on_file, nxrc, nxrf, &
85                nxrpr, nxr_on_file, nync, nynf, nynpr, nyn_on_file, nysc,     &
86                nysf, nyspr, nys_on_file, nzb_on_file, nzt_on_file, offset_x, &
87                offset_y, shift_x, shift_y
88
89    INTEGER, DIMENSION(numprocs_previous_run) ::  file_list, overlap_count
90
91    INTEGER, DIMENSION(numprocs_previous_run,1000) ::  nxlfa, nxrfa, nynfa, &
92                                                       nysfa, offset_xa, &
93                                                       offset_ya
94    REAL ::  rdummy
95
96    REAL, DIMENSION(:,:), ALLOCATABLE     ::  tmp_2d
97    REAL, DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3d, tmp_3dwul, tmp_3dwun,    &
98                                              tmp_3dwur, tmp_3dwus, tmp_3dwvl, &
99                                              tmp_3dwvn, tmp_3dwvr, tmp_3dwvs, &
100                                              tmp_3dwwl, tmp_3dwwn, tmp_3dwwr, &
101                                              tmp_3dwws
102    REAL, DIMENSION(:,:,:,:), ALLOCATABLE ::  tmp_4d
103
104
105!
106!-- Read data from previous model run.
107    CALL cpu_log( log_point_s(14), 'read_3d_binary', 'start' )
108
109!
110!-- Check which of the restart files contain data needed for the subdomain
111!-- of this PE
112    files_to_be_opened = 0
113
114    DO  i = 1, numprocs_previous_run
115!
116!--    Store array bounds of the previous run ("pr") in temporary scalars
117       nxlpr = hor_index_bounds_previous_run(1,i-1)
118       nxrpr = hor_index_bounds_previous_run(2,i-1)
119       nyspr = hor_index_bounds_previous_run(3,i-1)
120       nynpr = hor_index_bounds_previous_run(4,i-1)
121
122!
123!--    Determine the offsets. They may be non-zero in case that the total domain
124!--    on file is smaller than the current total domain.
125       offset_x = ( nxl / ( nx_on_file + 1 ) ) * ( nx_on_file + 1 )
126       offset_y = ( nys / ( ny_on_file + 1 ) ) * ( ny_on_file + 1 )
127
128!
129!--    Start with this offset and then check, if the subdomain on file
130!--    matches another time(s) in the current subdomain by shifting it
131!--    for nx_on_file+1, ny_on_file+1 respectively
132   
133       shift_y = 0
134       j       = 0
135       DO WHILE (  nyspr+shift_y <= nyn-offset_y )
136         
137          IF ( nynpr+shift_y >= nys-offset_y ) THEN
138
139             shift_x = 0
140             DO WHILE ( nxlpr+shift_x <= nxr-offset_x )
141               
142                IF ( nxrpr+shift_x >= nxl-offset_x ) THEN
143                   j = j +1
144                   IF ( j > 1000 )  THEN
145!
146!--                   Array bound exceeded
147                      message_string = 'data from subdomain of previous' // &
148                                       ' run mapped more than 1000 times'
149                      CALL message( 'read_3d_binary', 'PA0284', 2, 2, -1,   &
150                                       6, 1 )
151                   ENDIF
152
153                   IF ( j == 1 )  THEN
154                      files_to_be_opened = files_to_be_opened + 1
155                      file_list(files_to_be_opened) = i-1
156                   ENDIF
157                     
158                   offset_xa(files_to_be_opened,j) = offset_x + shift_x
159                   offset_ya(files_to_be_opened,j) = offset_y + shift_y
160!
161!--                Index bounds of overlapping data
162                   nxlfa(files_to_be_opened,j) = MAX( nxl-offset_x-shift_x, nxlpr )
163                   nxrfa(files_to_be_opened,j) = MIN( nxr-offset_x-shift_x, nxrpr )
164                   nysfa(files_to_be_opened,j) = MAX( nys-offset_y-shift_y, nyspr )
165                   nynfa(files_to_be_opened,j) = MIN( nyn-offset_y-shift_y, nynpr )
166
167                ENDIF
168
169                shift_x = shift_x + ( nx_on_file + 1 )
170             ENDDO
171       
172          ENDIF
173             
174          shift_y = shift_y + ( ny_on_file + 1 )             
175       ENDDO
176         
177       IF ( j > 0 )  overlap_count(files_to_be_opened) = j
178
179!
180!--    Test output, to be removed later
181       IF ( j > 0 )  THEN
182          WRITE (9,*) '*** reading from file: ', i, j, ' times'
183          WRITE (9,*) '    nxl = ', nxl, ' nxr = ', nxr, ' nys = ', & 
184                                    nys, ' nyn = ', nyn
185          WRITE (9,*) ' '
186          DO  k = 1, j
187             WRITE (9,*) 'k = ', k
188             WRITE (9,'(6(A,I4))') 'nxlfa = ', nxlfa(files_to_be_opened,k),&
189                     ' nxrfa = ', nxrfa(files_to_be_opened,k), &
190                     ' offset_xa = ', offset_xa(files_to_be_opened,k), &
191                     ' nysfa = ', nysfa(files_to_be_opened,k), &
192                     ' nynfa = ', nynfa(files_to_be_opened,k), &
193                     ' offset_ya = ', offset_ya(files_to_be_opened,k)
194          ENDDO
195          CALL local_flush( 9 )
196       ENDIF
197
198         
199    ENDDO
200   
201!
202!-- Save the id-string of the current process, since myid_char may now be used
203!-- to open files created by PEs with other id.
204          myid_char_save = myid_char
205
206!
207!-- Test output (remove later)
208         
209    DO i = 1, numprocs_previous_run
210       WRITE (9,*) 'i=',i-1, ' ibs= ',hor_index_bounds_previous_run(1:4,i-1)
211    ENDDO
212    CALL local_flush( 9 )
213
214    IF ( files_to_be_opened /= 1  .OR.  numprocs /= numprocs_previous_run ) &
215    THEN
216       WRITE( message_string, * ) 'number of PEs or virtual PE-grid changed ', &
217                        'in restart run&  PE', myid, ' will read from files ', &
218                         file_list(1:files_to_be_opened)
219       CALL message( 'read_3d_binary', 'PA0285', 0, 0, 0, 6, 0 )
220    ENDIF
221
222!
223!-- Read data from all restart files determined above
224    DO  i = 1, files_to_be_opened
225
226       j = file_list(i)
227!
228!--    Set the filename (underscore followed by four digit processor id)
229       WRITE (myid_char,'(''_'',I4.4)')  j
230       WRITE (9,*) 'myid=',myid,' opening file "',myid_char,'"'
231       CALL local_flush( 9 )
232
233!
234!--    Open the restart file. If this file has been created by PE0 (_0000),
235!--    the global variables at the beginning of the file have to be skipped
236!--    first.
237       CALL check_open( 13 )
238       WRITE (9,*) 'before skipping'
239       CALL local_flush( 9 )
240       IF ( j == 0 )  CALL skip_var_list
241       WRITE (9,*) 'skipping done'
242       CALL local_flush( 9 )
243
244!
245!--    First compare the version numbers
246       READ ( 13 )  version_on_file
247       binary_version = '3.1'
248       IF ( TRIM( version_on_file ) /= TRIM( binary_version ) )  THEN
249          WRITE( message_string, * ) 'version mismatch concerning data ',      &
250                      'from prior run',                                        &
251                      '&version on file    = "', TRIM( version_on_file ), '"', &
252                      '&version in program = "', TRIM( binary_version ), '"'
253          CALL message( 'read_3d_binary', 'PA0286', 1, 2, 0, 6, 0 )
254       ENDIF
255
256!
257!--    Read number of processors, processor-id, and array ranges.
258!--    Compare the array ranges with those stored in the index bound array.
259       READ ( 13 )  numprocs_on_file, myid_on_file, nxl_on_file, nxr_on_file, &
260                    nys_on_file, nyn_on_file, nzb_on_file, nzt_on_file
261
262       IF ( nxl_on_file /= hor_index_bounds_previous_run(1,j) )  THEN
263          WRITE( message_string, * ) 'problem with index bound nxl on ',  &
264                            'restart file "', myid_char, '"',             &
265                            '&nxl = ', nxl_on_file, ' but it should be',  &
266                            '&= ', hor_index_bounds_previous_run(1,j),    &
267                            '&from the index bound information array'
268          CALL message( 'read_3d_binary', 'PA0287', 2, 2, -1, 6, 1 )
269       ENDIF
270
271       IF ( nxr_on_file /= hor_index_bounds_previous_run(2,j) )  THEN
272           WRITE( message_string, * ) 'problem with index bound nxr on ',   &
273                               'restart file "', myid_char, '"'  ,          &
274                               '&nxr = ', nxr_on_file, ' but it should be', &
275                               '&= ', hor_index_bounds_previous_run(2,j),   &
276                               '&from the index bound information array' 
277          CALL message( 'read_3d_binary', 'PA0288', 2, 2, -1, 6, 1 )
278
279       ENDIF
280
281       IF ( nys_on_file /= hor_index_bounds_previous_run(3,j) )  THEN
282          WRITE( message_string, * ) 'problem with index bound nys on ',      &
283                                 'restart file "', myid_char, '"',            &
284                                 '&nys = ', nys_on_file, ' but it should be', &
285                                 '&= ', hor_index_bounds_previous_run(3,j),   &
286                                     '&from the index bound information array'
287          CALL message( 'read_3d_binary', 'PA0289', 2, 2, -1, 6, 1 ) 
288       ENDIF
289
290       IF ( nyn_on_file /= hor_index_bounds_previous_run(4,j) )  THEN
291          WRITE( message_string, * ) 'problem with index bound nyn on ',    &
292                               'restart file "', myid_char, '"',            &
293                               '&nyn = ', nyn_on_file, ' but it should be', &
294                               '&= ', hor_index_bounds_previous_run(4,j),   &
295                               '&from the index bound information array'
296          CALL message( 'read_3d_binary', 'PA0290', 2, 2, -1, 6, 1 ) 
297       ENDIF
298
299       IF ( nzb_on_file /= nzb )  THEN
300          WRITE( message_string, * ) 'mismatch between actual data and data ', &
301                                     '&from prior run on PE ', myid,           &
302                                     '&nzb on file = ', nzb_on_file,           &
303                                     '&nzb         = ', nzb
304          CALL message( 'read_3d_binary', 'PA0291', 1, 2, 0, 6, 0 ) 
305       ENDIF
306
307       IF ( nzt_on_file /= nzt )  THEN
308          WRITE( message_string, * ) 'mismatch between actual data and data ', &
309                                     '&from prior run on PE ', myid,           &
310                                     '&nzt on file = ', nzt_on_file,           &
311                                     '&nzt         = ', nzt
312          CALL message( 'read_3d_binary', 'PA0292', 1, 2, 0, 6, 0 ) 
313       ENDIF
314
315!
316!--    Allocate temporary arrays sized as the arrays on the restart file
317       ALLOCATE( tmp_2d(nys_on_file-nbgp:nyn_on_file+nbgp,           &
318                        nxl_on_file-nbgp:nxr_on_file+nbgp),          &
319                 tmp_3d(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp, &
320                        nxl_on_file-nbgp:nxr_on_file+nbgp) )
321
322!
323!--    Read arrays
324!--    ATTENTION: If the following read commands have been altered, the
325!--    ---------- version number of the variable binary_version must be altered,
326!--               too. Furthermore, the output list of arrays in write_3d_binary
327!--               must also be altered accordingly.
328       READ ( 13 )  field_chr
329       DO  WHILE ( TRIM( field_chr ) /= '*** end ***' )
330
331!
332!--       Map data on file as often as needed (data are read only for k=1)
333          DO  k = 1, overlap_count(i)
334
335!
336!--          Get the index range of the subdomain on file which overlap with the
337!--          current subdomain
338             nxlf = nxlfa(i,k)
339             nxlc = nxlfa(i,k) + offset_xa(i,k)
340             nxrf = nxrfa(i,k)
341             nxrc = nxrfa(i,k) + offset_xa(i,k)
342             nysf = nysfa(i,k)
343             nysc = nysfa(i,k) + offset_ya(i,k)
344             nynf = nynfa(i,k)
345             nync = nynfa(i,k) + offset_ya(i,k)
346
347
348             WRITE (9,*) 'var = ', field_chr
349             CALL local_flush( 9 )
350
351             SELECT CASE ( TRIM( field_chr ) )
352
353                CASE ( 'e' )
354                   IF ( k == 1 )  READ ( 13 )  tmp_3d
355                   e(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
356                           tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
357
358                CASE ( 'e_av' )
359                   IF ( .NOT. ALLOCATED( e_av ) )  THEN
360                      ALLOCATE( e_av(nzb:nzt+1,nys-nbgp:nyn+nbgp,nxl-nbgp:nxr+nbgp) )
361                   ENDIF
362                   IF ( k == 1 )  READ ( 13 )  tmp_3d
363                   e_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
364                            tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
365
366                CASE ( 'e_m' )
367                   IF ( k == 1 )  READ ( 13 )  tmp_3d
368                   e_m(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
369                             tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
370
371                CASE ( 'iran' ) ! matching random numbers is still unresolved
372                                ! issue
373                   IF ( k == 1 )  READ ( 13 )  iran, iran_part
374
375                CASE ( 'kh' )
376                   IF ( k == 1 )  READ ( 13 )  tmp_3d
377                   kh(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
378                             tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
379
380                CASE ( 'kh_m' )
381                   IF ( k == 1 )  READ ( 13 )  tmp_3d
382                   kh_m(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
383                              tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
384
385                CASE ( 'km' )
386                   IF ( k == 1 )  READ ( 13 )  tmp_3d
387                   km(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
388                               tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
389
390                CASE ( 'km_m' )
391                   IF ( k == 1 )  READ ( 13 )  tmp_3d
392                   km_m(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
393                                tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
394
395                CASE ( 'lwp_av' )
396                   IF ( .NOT. ALLOCATED( lwp_av ) )  THEN
397                      ALLOCATE( lwp_av(nysg:nyng,nxlg:nxrg) )
398                   ENDIF
399                   IF ( k == 1 )  READ ( 13 )  tmp_2d
400                   lwp_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
401                                  tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
402
403                CASE ( 'p' )
404                   IF ( k == 1 )  READ ( 13 )  tmp_3d
405                   p(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
406                                 tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
407
408                CASE ( 'p_av' )
409                   IF ( .NOT. ALLOCATED( p_av ) )  THEN
410                      ALLOCATE( p_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
411                   ENDIF
412                   IF ( k == 1 )  READ ( 13 )  tmp_3d
413                   p_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
414                                  tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
415
416                CASE ( 'pc_av' )
417                   IF ( .NOT. ALLOCATED( pc_av ) )  THEN
418                      ALLOCATE( pc_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
419                   ENDIF
420                   IF ( k == 1 )  READ ( 13 )  tmp_3d
421                   pc_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
422                                  tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
423
424                CASE ( 'pr_av' )
425                   IF ( .NOT. ALLOCATED( pr_av ) )  THEN
426                      ALLOCATE( pr_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
427                   ENDIF
428                   IF ( k == 1 )  READ ( 13 )  tmp_3d
429                   pr_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
430                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
431
432                CASE ( 'precipitation_amount' )
433                   IF ( k == 1 )  READ ( 13 )  tmp_2d
434                   precipitation_amount(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
435                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
436
437                CASE ( 'precipitation_rate_a' )
438                   IF ( .NOT. ALLOCATED( precipitation_rate_av ) )  THEN
439                      ALLOCATE( precipitation_rate_av(nysg:nyng,nxlg:nxrg) )
440                   ENDIF
441                   IF ( k == 1 )  READ ( 13 )  tmp_2d
442                   precipitation_rate_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
443                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
444
445                CASE ( 'pt' )
446                   IF ( k == 1 )  READ ( 13 )  tmp_3d
447                   pt(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
448                                   tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
449
450                CASE ( 'pt_av' )
451                   IF ( .NOT. ALLOCATED( pt_av ) )  THEN
452                      ALLOCATE( pt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
453                   ENDIF
454                   IF ( k == 1 )  READ ( 13 )  tmp_3d
455                   pt_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
456                                    tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
457
458                CASE ( 'pt_m' )
459                   IF ( k == 1 )  READ ( 13 )  tmp_3d
460                   pt_m(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
461                                    tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
462
463                CASE ( 'q' )
464                   IF ( k == 1 )  READ ( 13 )  tmp_3d
465                   q(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
466                                    tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
467
468                CASE ( 'q_av' )
469                   IF ( .NOT. ALLOCATED( q_av ) )  THEN
470                      ALLOCATE( q_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg ))
471                   ENDIF
472                   IF ( k == 1 )  READ ( 13 )  tmp_3d
473                   q_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
474                                     tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
475
476                CASE ( 'q_m' )
477                   IF ( k == 1 )  READ ( 13 )  tmp_3d
478                   q_m(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
479                                      tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
480
481                CASE ( 'ql' )
482                   IF ( k == 1 )  READ ( 13 )  tmp_3d
483                   ql(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
484                                       tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
485
486                CASE ( 'ql_av' )
487                   IF ( .NOT. ALLOCATED( ql_av ) )  THEN
488                      ALLOCATE( ql_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
489                   ENDIF
490                   IF ( k == 1 )  READ ( 13 )  tmp_3d
491                   ql_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
492                                       tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
493
494                CASE ( 'ql_c_av' )
495                   IF ( .NOT. ALLOCATED( ql_c_av ) )  THEN
496                      ALLOCATE( ql_c_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
497                   ENDIF
498                   IF ( k == 1 )  READ ( 13 )  tmp_3d
499                   ql_c_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
500                                        tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
501
502                CASE ( 'ql_v_av' )
503                   IF ( .NOT. ALLOCATED( ql_v_av ) )  THEN
504                      ALLOCATE( ql_v_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
505                   ENDIF
506                   IF ( k == 1 )  READ ( 13 )  tmp_3d
507                   ql_v_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
508                                        tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
509
510                CASE ( 'ql_vp_av' )
511                   IF ( .NOT. ALLOCATED( ql_vp_av ) )  THEN
512                      ALLOCATE( ql_vp_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
513                   ENDIF
514                   IF ( k == 1 )  READ ( 13 )  tmp_3d
515                   ql_vp_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
516                                        tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
517
518                CASE ( 'qs' )
519                   IF ( k == 1 )  READ ( 13 )  tmp_2d
520                   qs(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
521                                          tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
522
523                CASE ( 'qsws' )
524                   IF ( k == 1 )  READ ( 13 )  tmp_2d
525                   qsws(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
526                                          tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
527
528                CASE ( 'qsws_m' )
529                   IF ( k == 1 )  READ ( 13 )  tmp_2d
530                   qsws_m(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
531                                          tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
532
533                CASE ( 'qsws_av' )
534                   IF ( .NOT. ALLOCATED( qsws_av ) )  THEN
535                      ALLOCATE( qsws_av(nysg:nyng,nxlg:nxrg) )
536                   ENDIF 
537                   IF ( k == 1 )  READ ( 13 )  tmp_2d
538                   qsws_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
539                                          tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
540
541                CASE ( 'qswst' )
542                   IF ( k == 1 )  READ ( 13 )  tmp_2d
543                   qswst(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
544                                          tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
545
546                CASE ( 'qswst_m' )
547                   IF ( k == 1 )  READ ( 13 )  tmp_2d
548                   qswst_m(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
549                                          tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
550
551                CASE ( 'qv_av' )
552                   IF ( .NOT. ALLOCATED( qv_av ) )  THEN
553                      ALLOCATE( qv_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
554                   ENDIF
555                   IF ( k == 1 )  READ ( 13 )  tmp_3d
556                   qv_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
557                             tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
558
559                CASE ( 'random_iv' )  ! still unresolved issue
560                   IF ( k == 1 )  READ ( 13 )  random_iv
561                   IF ( k == 1 )  READ ( 13 )  random_iy
562
563                CASE ( 'rho_av' )
564                   IF ( .NOT. ALLOCATED( rho_av ) )  THEN
565                      ALLOCATE( rho_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
566                   ENDIF
567                   IF ( k == 1 )  READ ( 13 )  tmp_3d
568                   rho_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
569                                tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
570
571                CASE ( 'rif' )
572                   IF ( k == 1 )  READ ( 13 )  tmp_2d
573                   rif(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
574                                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
575
576                CASE ( 'rif_m' )
577                   IF ( k == 1 )  READ ( 13 )  tmp_2d
578                   rif_m(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
579                        tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
580
581                CASE ( 'rif_wall' )
582                   IF ( k == 1 )  THEN
583                      ALLOCATE( tmp_4d(nzb:nzt+1,nys_on_file-nbgp:nyn_on_file+nbgp, &
584                                       nxl_on_file-nbgp:nxr_on_file+nbgp,1:4) )
585                      READ ( 13 )  tmp_4d
586                   ENDIF
587                   rif_wall(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp,:) = &
588                            tmp_4d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp,:)
589
590                CASE ( 's_av' )
591                   IF ( .NOT. ALLOCATED( s_av ) )  THEN
592                      ALLOCATE( s_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg))
593                   ENDIF
594                   IF ( k == 1 )  READ ( 13 )  tmp_3d
595                   s_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
596                                 tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
597
598                CASE ( 'sa' )
599                   IF ( k == 1 )  READ ( 13 )  tmp_3d
600                   sa(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
601                                  tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
602
603                CASE ( 'sa_av' )
604                   IF ( .NOT. ALLOCATED( sa_av ) )  THEN
605                      ALLOCATE( sa_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
606                   ENDIF
607                   IF ( k == 1 )  READ ( 13 )  tmp_3d
608                   sa_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
609                                    tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
610
611                CASE ( 'saswsb' )
612                   IF ( k == 1 )  READ ( 13 )  tmp_2d
613                   saswsb(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
614                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
615
616                CASE ( 'saswst' )
617                   IF ( k == 1 )  READ ( 13 )  tmp_2d
618                   saswst(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
619                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
620
621                CASE ( 'shf' )
622                   IF ( k == 1 )  READ ( 13 )  tmp_2d
623                   shf(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
624                      tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
625
626                CASE ( 'shf_m' )
627                   IF ( k == 1 )  READ ( 13 )  tmp_2d
628                   shf_m(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
629                        tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
630                CASE ( 'shf_av' )
631                   IF ( .NOT. ALLOCATED( shf_av ) )  THEN
632                      ALLOCATE( shf_av(nysg:nyng,nxlg:nxrg) )
633                   ENDIF
634                   IF ( k == 1 )  READ ( 13 )  tmp_2d
635                   shf_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
636                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
637                CASE ( 'spectrum_x' )
638                   IF ( k == 1 )  THEN
639                      IF ( nx_on_file /= nx )  THEN
640                         message_string = 'read_3d_binary: spectrum_x ' // &
641                                     'on restart file ignored because' // &
642                                     '&total numbers of grid points (nx) ' // &
643                                     'do not match'
644                         CALL message( 'read_3d_binary', 'PA0293',&
645                                                                 0, 1, 0, 6, 0 )
646                         READ ( 13 )  rdummy
647                      ELSE
648                         READ ( 13 )  spectrum_x
649                      ENDIF
650                   ENDIF
651
652                CASE ( 'spectrum_y' )
653                   IF ( k == 1 )  THEN
654                      IF ( ny_on_file /= ny )  THEN
655                         message_string = 'read_3d_binary: spectrum_y ' //   &
656                                     'on restart file ignored because' //    &
657                                     '&total numbers of grid points (ny) '// &
658                                     'do not match'
659                         CALL message( 'read_3d_binary', 'PA0294', &
660                                                                 0, 1, 0, 6, 0 )
661                      READ ( 13 )  rdummy
662                      ELSE
663                         READ ( 13 )  spectrum_y
664                      ENDIF
665                   ENDIF
666
667                CASE ( 'ts' )
668                   IF ( k == 1 )  READ ( 13 )  tmp_2d
669                   ts(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
670                     tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
671
672                CASE ( 'ts_av' )
673                   IF ( .NOT. ALLOCATED( ts_av ) )  THEN
674                      ALLOCATE( ts_av(nysg:nyng,nxlg:nxrg) )
675                   ENDIF
676                   IF ( k == 1 )  READ ( 13 )  tmp_2d
677                   ts_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
678                        tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
679
680                CASE ( 'tswst' )
681                   IF ( k == 1 )  READ ( 13 )  tmp_2d
682                   tswst(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
683                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
684
685                CASE ( 'tswst_m' )
686                   IF ( k == 1 )  READ ( 13 )  tmp_2d
687                   tswst_m(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
688                          tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
689
690                CASE ( 'u' )
691                   IF ( k == 1 )  READ ( 13 )  tmp_3d
692                   u(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
693                             tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
694
695                CASE ( 'u_av' )
696                   IF ( .NOT. ALLOCATED( u_av ) )  THEN
697                      ALLOCATE( u_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
698                   ENDIF
699                   IF ( k == 1 )  READ ( 13 )  tmp_3d
700                   u_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
701                               tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
702
703                CASE ( 'u_m' )
704                   IF ( k == 1 )  READ ( 13 )  tmp_3d
705                   u_m(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
706                                 tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
707
708                CASE ( 'u_m_l' )
709                   IF ( k == 1 )  THEN
710                      ALLOCATE( tmp_3dwul(nzb:nzt+1, &
711                                          nys_on_file-nbgp:nyn_on_file+nbgp,1:2) )
712                      READ ( 13 )  tmp_3dwul
713                   ENDIF
714                   IF ( outflow_l )  THEN
715                      u_m_l(:,nysc-nbgp:nync+nbgp,:) = tmp_3dwul(:,nysf-nbgp:nynf+nbgp,:)
716                   ENDIF
717
718                CASE ( 'u_m_n' )
719                   IF ( k == 1 )  THEN
720                      ALLOCATE( tmp_3dwun(nzb:nzt+1,ny-1:ny, &
721                                          nxl_on_file-nbgp:nxr_on_file+nbgp) )
722                      READ ( 13 )  tmp_3dwun
723                   ENDIF
724                   IF ( outflow_n )  THEN
725                      u_m_n(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3dwun(:,:,nxlf-nbgp:nxrf+nbgp)
726                   ENDIF
727
728                CASE ( 'u_m_r' )
729                   IF ( k == 1 )  THEN
730                      ALLOCATE( tmp_3dwur(nzb:nzt+1,&
731                                          nys_on_file-nbgp:nyn_on_file+nbgp,nx-1:nx) )
732                      READ ( 13 )  tmp_3dwur
733                   ENDIF
734                   IF ( outflow_r )  THEN
735                      u_m_r(:,nysc-nbgp:nync+nbgp,:) = tmp_3dwur(:,nysf-nbgp:nynf+nbgp,:)
736                   ENDIF
737
738                CASE ( 'u_m_s' )
739                   IF ( k == 1 )  THEN
740                      ALLOCATE( tmp_3dwus(nzb:nzt+1,0:1, &
741                                          nxl_on_file-nbgp:nxr_on_file+nbgp) )
742                      READ ( 13 )  tmp_3dwus
743                   ENDIF
744                   IF ( outflow_s )  THEN
745                      u_m_s(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3dwus(:,:,nxlf-nbgp:nxrf+nbgp)
746                   ENDIF
747
748                CASE ( 'us' )
749                   IF ( k == 1 )  READ ( 13 )  tmp_2d
750                   us(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
751                     tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
752
753                CASE ( 'usws' )
754                   IF ( k == 1 )  READ ( 13 )  tmp_2d
755                   usws(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
756                       tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
757
758                CASE ( 'uswst' )
759                   IF ( k == 1 )  READ ( 13 )  tmp_2d
760                   uswst(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
761                        tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
762
763                CASE ( 'usws_m' )
764                   IF ( k == 1 )  READ ( 13 )  tmp_2d
765                   usws_m(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
766                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
767
768                CASE ( 'uswst_m' )
769                   IF ( k == 1 )  READ ( 13 )  tmp_2d
770                   uswst_m(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
771                          tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
772
773                CASE ( 'us_av' )
774                   IF ( .NOT. ALLOCATED( us_av ) )  THEN
775                      ALLOCATE( us_av(nysg:nyng,nxlg:nxrg) )
776                   ENDIF
777                   IF ( k == 1 )  READ ( 13 )  tmp_2d
778                   us_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
779                        tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
780
781                CASE ( 'v' )
782                   IF ( k == 1 )  READ ( 13 )  tmp_3d
783                   v(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
784                              tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
785
786                CASE ( 'v_av' )
787                   IF ( .NOT. ALLOCATED( v_av ) )  THEN
788                      ALLOCATE( v_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
789                   ENDIF
790                   IF ( k == 1 )  READ ( 13 )  tmp_3d
791                   v_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
792                               tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
793
794                CASE ( 'v_m' )
795                   IF ( k == 1 )  READ ( 13 )  tmp_3d
796                   v_m(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
797                                tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
798
799                CASE ( 'v_m_l' )
800                   IF ( k == 1 )  THEN
801                      ALLOCATE( tmp_3dwvl(nzb:nzt+1,&
802                                          nys_on_file-nbgp:nyn_on_file+nbgp,0:1) )
803                      READ ( 13 )  tmp_3dwvl
804                   ENDIF
805                   IF ( outflow_l )  THEN
806                      v_m_l(:,nysc-nbgp:nync+nbgp,:) = tmp_3dwvl(:,nysf-nbgp:nynf+nbgp,:)
807                   ENDIF
808
809                CASE ( 'v_m_n' )
810                   IF ( k == 1 )  THEN
811                      ALLOCATE( tmp_3dwvn(nzb:nzt+1,ny-1:ny, &
812                                          nxl_on_file-nbgp:nxr_on_file+nbgp) )
813                      READ ( 13 )  tmp_3dwvn
814                   ENDIF
815                   IF ( outflow_n )  THEN
816                      v_m_n(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3dwvn(:,:,nxlf-nbgp:nxrf+nbgp)
817                   ENDIF
818
819                CASE ( 'v_m_r' )
820                   IF ( k == 1 )  THEN
821                      ALLOCATE( tmp_3dwvr(nzb:nzt+1,&
822                                          nys_on_file-nbgp:nyn_on_file+nbgp,nx-1:nx) )
823                      READ ( 13 )  tmp_3dwvr
824                   ENDIF
825                   IF ( outflow_r )  THEN
826                      v_m_r(:,nysc-nbgp:nync+nbgp,:) = tmp_3dwvr(:,nysf-nbgp:nynf+nbgp,:)
827                   ENDIF
828
829                CASE ( 'v_m_s' )
830                   IF ( k == 1 )  THEN
831                      ALLOCATE( tmp_3dwvs(nzb:nzt+1,1:2, &
832                                          nxl_on_file-nbgp:nxr_on_file+nbgp) )
833                      READ ( 13 )  tmp_3dwvs
834                   ENDIF
835                   IF ( outflow_s )  THEN
836                      v_m_s(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3dwvs(:,:,nxlf-nbgp:nxrf+nbgp)
837                   ENDIF
838
839                CASE ( 'vpt' )
840                   IF ( k == 1 )  READ ( 13 )  tmp_3d
841                   vpt(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
842                               tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
843
844                CASE ( 'vpt_av' )
845                   IF ( .NOT. ALLOCATED( vpt_av ) )  THEN
846                      ALLOCATE( vpt_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
847                   ENDIF
848                   IF ( k == 1 )  READ ( 13 )  tmp_3d
849                   vpt_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
850                               tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
851
852                CASE ( 'vpt_m' )
853                   IF ( k == 1 )  READ ( 13 )  tmp_3d
854                   vpt_m(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
855                                tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
856
857                CASE ( 'vsws' )
858                   IF ( k == 1 )  READ ( 13 )  tmp_2d
859                   vsws(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
860                       tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
861
862                CASE ( 'vswst' )
863                   IF ( k == 1 )  READ ( 13 )  tmp_2d
864                   vswst(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
865                        tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
866
867                CASE ( 'vsws_m' )
868                   IF ( k == 1 )  READ ( 13 )  tmp_2d
869                   vsws_m(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
870                         tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
871
872                CASE ( 'vswst_m' )
873                   IF ( k == 1 )  READ ( 13 )  tmp_2d
874                   vswst_m(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
875                          tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
876
877                CASE ( 'w' )
878                   IF ( k == 1 )  READ ( 13 )  tmp_3d
879                   w(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
880                             tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
881
882                CASE ( 'w_av' )
883                   IF ( .NOT. ALLOCATED( w_av ) )  THEN
884                      ALLOCATE( w_av(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
885                   ENDIF
886                   IF ( k == 1 )  READ ( 13 )  tmp_3d
887                   w_av(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
888                               tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
889
890                CASE ( 'w_m' )
891                   IF ( k == 1 )  READ ( 13 )  tmp_3d
892                   w_m(:,nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp) = &
893                                tmp_3d(:,nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
894
895                CASE ( 'w_m_l' )
896                   IF ( k == 1 )  THEN
897                      ALLOCATE( tmp_3dwwl(nzb:nzt+1,&
898                                          nys_on_file-nbgp:nyn_on_file+nbgp,0:1) )
899                      READ ( 13 )  tmp_3dwwl
900                   ENDIF
901                   IF ( outflow_l )  THEN
902                      w_m_l(:,nysc-nbgp:nync+nbgp,:) = tmp_3dwwl(:,nysf-nbgp:nynf+nbgp,:)
903                   ENDIF
904
905                CASE ( 'w_m_n' )
906                   IF ( k == 1 )  THEN
907                      ALLOCATE( tmp_3dwwn(nzb:nzt+1,ny-1:ny, &
908                                          nxl_on_file-nbgp:nxr_on_file+nbgp) )
909                      READ ( 13 )  tmp_3dwwn
910                   ENDIF
911                   IF ( outflow_n )  THEN
912                      w_m_n(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3dwwn(:,:,nxlf-nbgp:nxrf+nbgp)
913                   ENDIF
914
915                CASE ( 'w_m_r' )
916                   IF ( k == 1 )  THEN
917                      ALLOCATE( tmp_3dwwr(nzb:nzt+1,&
918                                          nys_on_file-nbgp:nyn_on_file+nbgp,nx-1:nx) )
919                      READ ( 13 )  tmp_3dwwr
920                   ENDIF
921                   IF ( outflow_r )  THEN
922                      w_m_r(:,nysc-nbgp:nync+nbgp,:) = tmp_3dwwr(:,nysf-nbgp:nynf+nbgp,:)
923                   ENDIF
924
925                CASE ( 'w_m_s' )
926                   IF ( k == 1 )  THEN
927                      ALLOCATE( tmp_3dwws(nzb:nzt+1,0:1, &
928                                          nxl_on_file-nbgp:nxr_on_file+nbgp) )
929                      READ ( 13 )  tmp_3dwws
930                   ENDIF
931                   IF ( outflow_s )  THEN
932                      w_m_s(:,:,nxlc-nbgp:nxrc+nbgp) = tmp_3dwws(:,:,nxlf-nbgp:nxrf+nbgp)
933                   ENDIF
934                   DEALLOCATE( tmp_3dwws )
935
936                CASE ( 'z0' )
937                   IF ( k == 1 )  READ ( 13 )  tmp_2d
938                   z0(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
939                     tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
940
941                CASE ( 'z0_av' )
942                   IF ( .NOT. ALLOCATED( z0_av ) )  THEN
943                      ALLOCATE( z0_av(nysg:nyng,nxlg:nxrg) )
944                   ENDIF
945                   IF ( k == 1 )  READ ( 13 )  tmp_2d
946                   z0_av(nysc-nbgp:nync+nbgp,nxlc-nbgp:nxrc+nbgp)  = &
947                       tmp_2d(nysf-nbgp:nynf+nbgp,nxlf-nbgp:nxrf+nbgp)
948
949                CASE DEFAULT
950                   WRITE( message_string, * ) 'unknown field named "', &
951                                              TRIM( field_chr ), '" found in', &
952                                              '&data from prior run on PE ',myid
953                    CALL message( 'read_3d_binary', 'PA0295', 1, 2, 0, 6, 0 ) 
954                   
955             END SELECT
956
957          ENDDO  ! overlap loop
958
959!
960!--       Deallocate arrays needed for specific variables only
961          IF ( ALLOCATED( tmp_3dwul ) )  DEALLOCATE( tmp_3dwul )
962          IF ( ALLOCATED( tmp_3dwun ) )  DEALLOCATE( tmp_3dwun )
963          IF ( ALLOCATED( tmp_3dwur ) )  DEALLOCATE( tmp_3dwur )
964          IF ( ALLOCATED( tmp_3dwus ) )  DEALLOCATE( tmp_3dwus )
965          IF ( ALLOCATED( tmp_3dwvl ) )  DEALLOCATE( tmp_3dwvl )
966          IF ( ALLOCATED( tmp_3dwvn ) )  DEALLOCATE( tmp_3dwvn )
967          IF ( ALLOCATED( tmp_3dwvr ) )  DEALLOCATE( tmp_3dwvr )
968          IF ( ALLOCATED( tmp_3dwvs ) )  DEALLOCATE( tmp_3dwvs )
969          IF ( ALLOCATED( tmp_3dwwl ) )  DEALLOCATE( tmp_3dwwl )
970          IF ( ALLOCATED( tmp_3dwwn ) )  DEALLOCATE( tmp_3dwwn )
971          IF ( ALLOCATED( tmp_3dwwr ) )  DEALLOCATE( tmp_3dwwr )
972          IF ( ALLOCATED( tmp_3dwws ) )  DEALLOCATE( tmp_3dwws )
973          IF ( ALLOCATED( tmp_4d ) )  DEALLOCATE( tmp_4d )
974
975!
976!--       Read next character string
977          READ ( 13 )  field_chr
978
979       ENDDO  ! loop over variables
980
981!
982!--    Read user-defined restart data
983       CALL user_read_restart_data( i, nxlfa, nxl_on_file, nxrfa, nxr_on_file, &
984                                    nynfa, nyn_on_file, nysfa, nys_on_file,    &
985                                    offset_xa, offset_ya, overlap_count(i),    &
986                                    tmp_2d, tmp_3d )
987
988!
989!--    Close the restart file
990       CALL close_file( 13 )
991
992       DEALLOCATE( tmp_2d, tmp_3d )
993
994    ENDDO  ! loop over restart files
995
996
997!
998!-- Restore the original filename for the restart file to be written
999    myid_char = myid_char_save
1000
1001
1002!
1003!-- End of time measuring for reading binary data
1004    CALL cpu_log( log_point_s(14), 'read_3d_binary', 'stop' )
1005
1006 END SUBROUTINE read_3d_binary
Note: See TracBrowser for help on using the repository browser.