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

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

further updates for turbulent inflow: PE-grid change for restart is working

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