source: palm/tags/release-3.5/SOURCE/read_3d_binary.f90 @ 3999

Last change on this file since 3999 was 198, checked in by raasch, 16 years ago

file headers updated for the next release 3.5

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