source: palm/tags/release-3.2/UTIL/combine_plot_fields.f90 @ 2977

Last change on this file since 2977 was 1, checked in by raasch, 17 years ago

Initial repository layout and content

File size: 22.7 KB
Line 
1 PROGRAM combine_plot_fields
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! 18/01/06  Output of time-averaged data
11!
12! 25/05/05  Errors removed
13!
14! 26/04/05  Output in NetCDF format, iso2d and avs output only if parameter
15!           file exists
16!
17! 31/10/01  All comments and messages translated into English
18!
19! 23/02/99  Keine Bearbeitung komprimierter 3D-Daten
20! Ursprungsversion vom 28/07/97
21!
22!
23! Description:
24! ------------
25! This routine combines data of the PALM-subdomains into one file. In PALM
26! every processor element opens its own file and writes 2D- or 3D-binary-data
27! into it (different files are opened for xy-, xz-, yz-cross-sections and
28! 3D-data). For plotting or analyzing these PE-data have to be collected and
29! to be put into single files, which is done by this routine.
30! Output format is NetCDF. Additionally, a data are output in a binary format
31! readable by ISO2D-software (cross-sections) and by AVS (3D-data).
32!
33! This routine must be compiled with:
34! decalpha:
35!    f95 -cpp -D__netcdf -fast -r8 -I/usr/local/netcdf-3.5.1/include
36!    -L/usr/local/netcdf-3.5.1/lib -lnetcdf
37! IBM-Regatta:
38!    xlf95 -qsuffix=cpp=f90 -WF,-D__netcdf -qrealsize=8 -q64 -qmaxmem=-1 -Q
39!    -I /aws/dataformats/netcdf-3.6.0-p1/64-32/include-64
40!    -L/aws/dataformats/netcdf-3.6.0-p1/64-32/lib -lnetcdf -O3
41! IBM-Regatta KISTI:
42!    xlf95 -qsuffix=cpp=f90 -WF,-D__netcdf -qrealsize=8 -q64 -qmaxmem=-1 -Q
43!    -I /applic/netcdf64/src/f90
44!    -L/applic/lib/NETCDF64 -lnetcdf -O3
45! IBM-Regatta Yonsei (gfdl5):
46!    xlf95 -qsuffix=cpp=f90 -WF,-D__netcdf -qrealsize=8 -q64 -qmaxmem=-1 -Q
47!    -I /usr1/users/raasch/pub/netcdf-3.6.0-p1/include
48!    -L/usr1/users/raasch/pub/netcdf-3.6.0-p1/lib -lnetcdf -O3
49! IMUK:
50!    ifort combine...f90 -o combine...x
51!    -cpp -D__netcdf -I /muksoft/packages/netcdf/linux/include -axW -r8 -nbs
52!    -Vaxlib -L /muksoft/packages/netcdf/linux/lib -lnetcdf
53! NEC-SX6:
54!    sxf90 combine...f90 -o combine...x
55!    -I /pool/SX-6/netcdf/netcdf-3.6.0-p1/include  -C hopt -Wf '-A idbl4'
56!    -D__netcdf -L/pool/SX-6/netcdf/netcdf-3.6.0-p1/lib -lnetcdf
57! Sun Fire X4600
58!    pgf95 combine...f90 -o combine...x
59!    -Mpreprocess -D__netcdf -I /home/usr5/mkanda/netcdf-3.6.1/src/f90 -r8
60!    -fast -L/home/usr5/mkanda/netcdf-3.6.1/src/libsrc -lnetcdf
61!------------------------------------------------------------------------------!
62
63#if defined( __netcdf )
64    USE netcdf
65#endif
66
67    IMPLICIT NONE
68
69!
70!-- Local variables
71    CHARACTER (LEN=2)    ::  modus
72    CHARACTER (LEN=7)    ::  id_char
73    CHARACTER (LEN=10)   ::  dimname, var_name
74    CHARACTER (LEN=40)   ::  filename
75
76    CHARACTER (LEN=2000), DIMENSION(0:1) ::  var_list
77
78    INTEGER, PARAMETER ::  spk = SELECTED_REAL_KIND( 6 )
79
80    INTEGER ::  av, danz, i, id,             &
81                j, nc_stat, nxa, nxag, nxe, nxeg, nya,   &
82                nyag, nye, nyeg, nza, nzag, nze, nzeg, pos, time_step, xa, xe, &
83                ya, ye, za, ze
84
85    INTEGER, DIMENSION(0:1) ::  current_level, current_var, fanz, id_set, id_var_time, num_var
86
87    INTEGER, DIMENSION(4) ::  id_dims_loc
88
89    INTEGER, DIMENSION(0:1,4) ::  id_dims
90
91    INTEGER, DIMENSION(0:1,1000) ::  id_var, levels
92
93    LOGICAL ::  avs_output, compressed, found, iso2d_output, netcdf_output, &
94                netcdf_0, netcdf_1
95
96    REAL ::  dx, simulated_time
97    REAL, DIMENSION(:),   ALLOCATABLE   ::  eta, ho, hu
98    REAL, DIMENSION(:,:), ALLOCATABLE   ::  pf
99    REAL(spk), DIMENSION(:,:,:), ALLOCATABLE ::  pf3d
100
101
102!
103!-- 2D-arrays for ISO2D
104!-- Main loop for the three different cross-sections, starting with xy-section
105    modus = 'XY'
106    PRINT*, ''
107    DO  WHILE ( modus == 'XY'  .OR.  modus == 'XZ'  .OR.  modus == 'YZ' )
108!
109!--    Check, if file from PE0 exists. If it does not exist, PALM did not
110!--    create any output for this cross-section.
111       danz = 0
112       WRITE (id_char,'(A2,''_'',I4.4)')  modus, danz
113       INQUIRE ( FILE='PLOT2D_'//id_char, EXIST=found )
114!
115!--    Find out the number of files (equal to the number of PEs which
116!--    have been used in PALM) and open them
117       DO  WHILE ( found )
118
119          OPEN ( danz+110, FILE='PLOT2D_'//id_char, FORM='UNFORMATTED' )
120          danz = danz + 1
121          WRITE (id_char,'(A2,''_'',I4.4)')  modus, danz
122          INQUIRE ( FILE='PLOT2D_'//id_char, EXIST=found )
123
124       ENDDO
125
126!
127!--    Inquire whether an iso2d parameter file exists
128       INQUIRE( FILE='PLOT2D_' // modus // '_GLOBAL', EXIST=iso2d_output )
129
130!
131!--    Inquire whether a NetCDF file exists
132       INQUIRE( FILE='DATA_2D_' // modus // '_NETCDF', EXIST=netcdf_0 )
133
134!
135!--    Inquire whether a NetCDF file for time-averaged data exists
136       INQUIRE( FILE='DATA_2D_' // modus // '_AV_NETCDF', EXIST=netcdf_1 )
137
138       IF ( netcdf_0  .OR.  netcdf_1 )  THEN
139          netcdf_output = .TRUE.
140       ELSE
141          netcdf_output = .FALSE.
142       ENDIF
143
144!
145!--    Info-output
146       PRINT*, ''
147       PRINT*, '*** combine_plot_fields ***'
148#if defined( __netcdf )
149       IF ( netcdf_output )  PRINT*, '    NetCDF output enabled'
150#else
151       IF ( netcdf_output )  THEN
152          PRINT*, '--- Sorry, no NetCDF support on this host'
153          netcdf_output = .FALSE.
154       ENDIF
155#endif
156       IF ( danz /= 0 )  THEN
157          PRINT*, '    ',modus,'-section:  ', danz, ' file(s) found'
158       ELSE
159          PRINT*, '    no ', modus, '-section data available'
160       ENDIF
161
162       IF ( netcdf_output  .AND.  danz /= 0 )  THEN
163#if defined( __netcdf )
164          DO  av = 0, 1
165
166             IF ( av == 0  .AND.  .NOT.  netcdf_0 )  CYCLE
167             IF ( av == 1  .AND.  .NOT.  netcdf_1 )  CYCLE
168
169!
170!--          Open NetCDF dataset
171             IF ( av == 0 )  THEN
172                filename = 'DATA_2D_' // modus // '_NETCDF'
173             ELSE
174                filename = 'DATA_2D_' // modus // '_AV_NETCDF'
175             ENDIF
176             nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set(av) )
177             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 1 )
178
179!
180!--          Get the list of variables (order of variables corresponds with the
181!--          order of data on the binary file)
182             var_list(av) = ' '    ! GET_ATT does not assign trailing blanks
183             nc_stat = NF90_GET_ATT( id_set(av), NF90_GLOBAL, 'VAR_LIST', &
184                                     var_list(av) )
185             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 2 )
186
187!
188!--          Inquire id of the time coordinate variable
189             nc_stat = NF90_INQ_VARID( id_set(av), 'time', id_var_time(av) )
190             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 3 )
191
192!
193!--          Count number of variables; there is one more semicolon in the
194!--          string than variable names
195             num_var(av) = -1
196             DO  i = 1, LEN( var_list(av) )
197                IF ( var_list(av)(i:i) == ';' )  num_var(av) = num_var(av) + 1
198             ENDDO
199
200!
201!--          Extract the variable names from the list and inquire their
202!--          NetCDF IDs
203             pos = INDEX( var_list(av), ';' )
204!
205!--          Loop over all variables
206             DO  i = 1, num_var(av)
207
208!
209!--             Extract variable name from list
210                var_list(av) = var_list(av)(pos+1:)
211                pos = INDEX( var_list(av), ';' )
212                var_name = var_list(av)(1:pos-1)
213
214!
215!--             Get variable ID from name
216                nc_stat = NF90_INQ_VARID( id_set(av), TRIM( var_name ), &
217                                          id_var(av,i) )
218                IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 4 )
219
220!
221!--             Get number of x/y/z levels for that variable
222                nc_stat = NF90_INQUIRE_VARIABLE( id_set(av), id_var(av,i), &
223                                                 dimids = id_dims_loc )
224                IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 5 )
225                id_dims(av,:) = id_dims_loc
226
227!
228!--             Inquire dimension ID
229                DO  j = 1, 4
230                   nc_stat = NF90_INQUIRE_DIMENSION( id_set(av), id_dims(av,j),&
231                                                     dimname, levels(av,i) )
232                   IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 6 )
233
234                   IF ( modus == 'XY' .AND. INDEX(dimname, 'z') /= 0 )  EXIT
235                   IF ( modus == 'XZ' .AND. INDEX(dimname, 'y') /= 0 )  EXIT
236                   IF ( modus == 'YZ' .AND. INDEX(dimname, 'x') /= 0 )  EXIT
237                ENDDO
238
239             ENDDO
240
241          ENDDO   ! av = 0, 1
242
243       ENDIF
244#endif
245
246!
247!--    Read the arrays, as long as the end of the file is reached
248       fanz          =         0
249       current_level =         1
250       current_var   = 999999999
251
252       DO  WHILE ( danz /= 0 )
253
254!
255!--       Loop over all files (reading data of the subdomains)
256          DO  id = 0, danz-1
257!
258!--          File from PE0 contains special information at the beginning,
259!--          concerning the lower and upper indices of the total-domain used
260!--          in PALM (nxag, nxeg, nyag, nyeg) and the lower and upper
261!--          indices of the array to be writte by this routine (nxa, nxe, nya,
262!--          nye). Usually in the horizontal directions nxag=-1 and nxa=0
263!--          while all other variables have the same value (i.e. nxeg=nxe).
264!--          Allocate necessary arrays, open the output file and write
265!--          the coordinate informations needed by ISO2D.
266             IF ( id == 0  .AND.  fanz(0) == 0  .AND.  fanz(1) == 0 )  THEN
267                READ ( id+110 )  nxag, nxeg, nyag, nyeg
268                READ ( id+110 )  nxa, nxe, nya, nye
269                ALLOCATE ( eta(nya:nye), ho(nxa:nxe), hu(nxa:nxe), &
270                           pf(nxag:nxeg,nyag:nyeg) )
271                READ ( id+110 )  dx, eta, hu, ho
272
273                IF ( iso2d_output )  THEN
274                   OPEN ( 2, FILE='PLOT2D_'//modus, FORM='UNFORMATTED' )
275                   WRITE ( 2 )  dx, eta, hu, ho
276                ENDIF
277             ENDIF
278!
279!--          Read output time
280             IF ( netcdf_output  .AND.  id == 0 )  THEN
281                IF ( netcdf_1 )  THEN
282                   READ ( id+110, END=998 )  simulated_time, time_step, av
283                ELSE
284!
285!--                For compatibility with earlier PALM versions
286                   READ ( id+110, END=998 )  simulated_time, time_step
287                   av = 0
288                ENDIF
289             ENDIF
290!
291!--          Read subdomain indices
292             READ ( id+110, END=998 )  xa, xe, ya, ye
293!
294!--          IF the PE made no output (in case that no part of the
295!--          cross-section is situated on this PE), indices have the
296!--          value -1
297             IF ( .NOT. ( xa == -1  .AND.  xe == -1  .AND. &
298                          ya == -1  .AND.  ye == -1 ) )  THEN
299!
300!--              Read the subdomain grid-point values
301                 READ ( id+110 )  pf(xa:xe,ya:ye)
302             ENDIF
303             IF ( id == 0 )  fanz(av) = fanz(av) + 1
304
305          ENDDO
306!
307!--       Write the data of the total domain cross-section
308          IF ( iso2d_output )  WRITE ( 2 )  pf(nxa:nxe,nya:nye)
309       
310!
311!--       Write same data in NetCDF format
312          IF ( netcdf_output )  THEN
313#if defined( __netcdf )
314!
315!--          Check if a new time step has begun; if yes write data to time axis
316             IF ( current_var(av) > num_var(av) )  THEN
317                current_var(av) = 1
318                nc_stat = NF90_PUT_VAR( id_set(av), id_var_time(av), &
319                                        (/ simulated_time /),        &
320                                        start = (/ time_step /),     &
321                                        count = (/ 1 /) )
322                IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 7 )
323             ENDIF
324
325!
326!--          Now write the data; this is mode dependent
327             SELECT CASE ( modus )
328
329                CASE ( 'XY' )
330                   nc_stat = NF90_PUT_VAR( id_set(av),                         &
331                                           id_var(av,current_var(av)),         &
332                                           pf(nxa:nxe,nya:nye),                &
333                             start = (/ 1, 1, current_level(av), time_step /), &
334                                      count = (/ nxe-nxa+1, nye-nya+1, 1, 1 /) )
335                   IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 8 )
336                 
337                CASE ( 'XZ' )
338                   nc_stat = NF90_PUT_VAR( id_set(av),                         &
339                                           id_var(av,current_var(av)),         &
340                                           pf(nxa:nxe,nya:nye),                &
341                             start = (/ 1, current_level(av), 1, time_step /), &
342                                      count = (/ nxe-nxa+1, 1, nye-nya+1, 1 /) )
343                   IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 9 )
344
345                CASE ( 'YZ' )
346                   nc_stat = NF90_PUT_VAR( id_set(av),                         &
347                                           id_var(av,current_var(av)),         &
348                                           pf(nxa:nxe,nya:nye),                &
349                             start = (/ current_level(av), 1, 1, time_step /), &
350                                      count = (/ 1, nxe-nxa+1, nye-nya+1, 1 /) )
351                   IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 10 )
352
353             END SELECT
354
355!
356!--          Data is written, check if max level is reached
357             current_level(av) = current_level(av) + 1
358             IF ( current_level(av) > levels(av,current_var(av)) )  THEN
359                current_level(av) = 1
360                current_var(av)   = current_var(av) + 1
361             ENDIF
362
363          ENDIF
364#endif
365
366       ENDDO
367
368998    IF ( danz /= 0 )  THEN
369!
370!--       Print the number of the arrays processed
371          WRITE (*,'(16X,I4,A)')  fanz(0)+fanz(1), ' array(s) processed'
372          IF ( fanz(1) /= 0 )  THEN
373             WRITE (*,'(16X,I4,A)')  fanz(1), ' array(s) are time-averaged'
374          ENDIF
375
376!
377!--       Close all files and deallocate arrays
378          DO  id = 0, danz-1
379             CLOSE ( id+110 )
380          ENDDO
381          CLOSE ( 2 )
382          DEALLOCATE ( eta, ho, hu, pf )
383       ENDIF
384
385!
386!--    Close the NetCDF file
387       IF ( netcdf_output  .AND.  danz /= 0 )  THEN
388#if defined( __netcdf )
389          IF ( netcdf_0 )  THEN
390             nc_stat = NF90_CLOSE( id_set(0) )
391             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 11 )
392          ENDIF
393          IF ( netcdf_1 )  THEN
394             nc_stat = NF90_CLOSE( id_set(1) )
395             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 12 )
396          ENDIF
397#endif
398       ENDIF
399
400!
401!--    Choose the next cross-section
402       SELECT CASE ( modus )
403          CASE ( 'XY' )
404             modus = 'XZ'
405          CASE ( 'XZ' )
406             modus = 'YZ'
407          CASE ( 'YZ' )
408             modus = 'no'
409       END SELECT
410
411    ENDDO
412
413
414!
415!-- Combine the 3D-arrays
416
417!
418!-- Inquire whether an avs fld file exists
419    INQUIRE( FILE='PLOT3D_FLD', EXIST=avs_output )
420
421!
422!-- Inquire whether a NetCDF file exists
423    INQUIRE( FILE='DATA_3D_NETCDF', EXIST=netcdf_0 )
424
425!
426!-- Inquire whether a NetCDF file for time-averaged data exists
427    INQUIRE( FILE='DATA_3D_AV_NETCDF', EXIST=netcdf_1 )
428
429    IF ( netcdf_0  .OR.  netcdf_1 )  THEN
430       netcdf_output = .TRUE.
431    ELSE
432       netcdf_output = .FALSE.
433    ENDIF
434
435!
436!-- Check, if file from PE0 exists
437    danz = 0
438    WRITE (id_char,'(I4.4)')  danz
439    INQUIRE ( FILE='PLOT3D_DATA_'//TRIM( id_char ), EXIST=found )
440
441!
442!-- Combination only works, if data are not compressed. In that case,
443!-- PALM created a flag file (PLOT3D_COMPRESSED)
444    INQUIRE ( FILE='PLOT3D_COMPRESSED', EXIST=compressed )
445
446!
447!-- Find out the number of files and open them
448    DO  WHILE ( found  .AND.  .NOT. compressed )
449
450       OPEN ( danz+110, FILE='PLOT3D_DATA_'//TRIM( id_char ), &
451              FORM='UNFORMATTED')
452       danz = danz + 1
453       WRITE (id_char,'(I4.4)')  danz
454       INQUIRE ( FILE='PLOT3D_DATA_'//TRIM( id_char ), EXIST=found )
455
456    ENDDO
457
458!
459!-- Info-output
460    PRINT*, ' '
461    PRINT*, '*** combine_plot_fields ***'
462#if defined( __netcdf )
463       IF ( netcdf_output )  PRINT*, '    NetCDF output enabled'
464#else
465       IF ( netcdf_output )  THEN
466          PRINT*, '--- Sorry, no NetCDF support on this host'
467          netcdf_output = .FALSE.
468       ENDIF
469#endif
470    IF ( danz /= 0 )  THEN
471       PRINT*, '    3D-data:     ', danz, ' file(s) found'
472    ELSE
473       IF ( found .AND. compressed )  THEN
474          PRINT*, '+++ no 3D-data processing, since data are compressed'
475       ELSE
476          PRINT*, '    no 3D-data file available'
477       ENDIF
478    ENDIF
479
480    IF ( netcdf_output  .AND.  danz /= 0 )  THEN
481#if defined( __netcdf )
482       DO  av = 0, 1
483
484          IF ( av == 0  .AND.  .NOT.  netcdf_0 )  CYCLE
485          IF ( av == 1  .AND.  .NOT.  netcdf_1 )  CYCLE
486
487!
488!--       Open NetCDF dataset
489          IF ( av == 0 )  THEN
490             filename = 'DATA_3D_NETCDF'
491          ELSE
492             filename = 'DATA_3D_AV_NETCDF'
493          ENDIF
494          nc_stat = NF90_OPEN( filename, NF90_WRITE, id_set(av) )
495          IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 13 )
496
497
498!
499!--       Get the list of variables (order of variables corresponds with the
500!--       order of data on the binary file)
501          var_list(av) = ' '    ! GET_ATT does not assign trailing blanks
502          nc_stat = NF90_GET_ATT( id_set(av), NF90_GLOBAL, 'VAR_LIST', &
503                                  var_list(av) )
504          IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 14 )
505
506!
507!--       Inquire id of the time coordinate variable
508          nc_stat = NF90_INQ_VARID( id_set(av), 'time', id_var_time(av) )
509          IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 15 )
510
511!
512!--       Count number of variables; there is one more semicolon in the string
513!--       than variable names
514          num_var(av) = -1
515          DO  i = 1, LEN( var_list(av) )
516             IF ( var_list(av)(i:i) == ';' )  num_var(av) = num_var(av) + 1
517          ENDDO
518
519!
520!--       Extract the variable names from the list and inquire their NetCDF IDs
521          pos = INDEX( var_list(av), ';' )
522!
523!--       Loop over all variables
524          DO  i = 1, num_var(av)
525
526!
527!--          Extract variable name from list
528             var_list(av) = var_list(av)(pos+1:)
529             pos = INDEX( var_list(av), ';' )
530             var_name = var_list(av)(1:pos-1)
531
532!
533!--          Get variable ID from name
534!             print*, '*** find id for "',TRIM( var_name ),'" begin'
535             nc_stat = NF90_INQ_VARID( id_set(av), TRIM( var_name ), &
536                                       id_var(av,i) )
537             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 16 )
538!             print*, '*** find id for "',TRIM( var_name ),'" end'
539
540          ENDDO
541
542       ENDDO    ! av=0,1
543
544    ENDIF
545#endif
546
547!
548!-- Read arrays, until the end of the file is reached
549    current_var = 999999999
550    fanz = 0
551    DO  WHILE ( danz /= 0 )
552
553!
554!--    Loop over all files
555       DO  id = 0, danz-1
556!
557!--       File from PE0 contains special information at the beginning,
558!--       concerning the lower and upper indices of the total-domain used
559!--       in PALM (nxag, nxeg, nyag, nyeg, nzag, nzeg) and the lower and upper
560!--       indices of the array to be written by this routine (nxa, nxe, nya,
561!--       nye, nza, nze). Usually nxag=-1 and nxa=0, nyag=-1 and nya=0,
562!--       nzeg=nz and nze=nz_plot3d.
563!--       Allocate necessary array and open the output file.
564          IF ( id == 0  .AND.  fanz(0) == 0  .AND.  fanz(1) == 0 )  THEN
565             READ ( id+110 )  nxag, nxeg, nyag, nyeg, nzag, nzeg
566             READ ( id+110 )  nxa, nxe, nya, nye, nza, nze
567             ALLOCATE ( pf3d(nxag:nxeg,nyag:nyeg,nzag:nzeg) )
568             IF ( avs_output )  THEN
569                OPEN ( 2, FILE='PLOT3D_DATA', FORM='UNFORMATTED' )
570             ENDIF
571          ENDIF
572
573!
574!--       Read output time
575          IF ( netcdf_output  .AND.  id == 0 )  THEN
576             IF ( netcdf_1 )  THEN
577                READ ( id+110, END=999 )  simulated_time, time_step, av
578             ELSE
579!
580!--             For compatibility with earlier PALM versions
581                READ ( id+110, END=999 )  simulated_time, time_step
582                av = 0
583             ENDIF
584          ENDIF
585
586!
587!--       Read subdomain indices and grid point values
588          READ ( id+110, END=999 )  xa, xe, ya, ye, za, ze
589          READ ( id+110 )  pf3d(xa:xe,ya:ye,za:ze)
590          IF ( id == 0 )  fanz(av) = fanz(av) + 1
591
592       ENDDO
593
594!
595!--    Write data of the total domain
596       IF ( avs_output )  WRITE ( 2 )  pf3d(nxa:nxe,nya:nye,nza:nze)
597       
598!
599!--    Write same data in NetCDF format
600       IF ( netcdf_output )  THEN
601#if defined( __netcdf )
602!
603!--       Check if a new time step has begun; if yes write data to time axis
604          IF ( current_var(av) > num_var(av) )  THEN
605             current_var(av) = 1
606             nc_stat = NF90_PUT_VAR( id_set(av), id_var_time(av), &
607                                     (/ simulated_time /),&
608                                     start = (/ time_step /), count = (/ 1 /) )
609             IF ( nc_stat /= NF90_NOERR ) CALL handle_netcdf_error( 17 )
610          ENDIF
611
612!
613!--       Now write the data
614          nc_stat = NF90_PUT_VAR( id_set(av), id_var(av,current_var(av)), &
615                                  pf3d(nxa:nxe,nya:nye,nza:nze),      &
616                                  start = (/ 1, 1, 1, time_step /),   &
617                              count = (/ nxe-nxa+1, nye-nya+1, nze-nza+1, 1 /) )
618          IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 18 )
619
620          current_var(av) = current_var(av) + 1
621
622#endif
623       ENDIF
624
625    ENDDO
626
627999 IF ( danz /= 0 )  THEN
628!
629!--    Print the number of arrays processed
630       WRITE (*,'(16X,I4,A)')  fanz(0)+fanz(1), ' array(s) processed'
631       IF ( fanz(1) /= 0 )  THEN
632          WRITE (*,'(16X,I4,A)')  fanz(1), ' array(s) are time-averaged'
633       ENDIF
634!
635!--    Close all files and deallocate array
636       DO  id = 0, danz-1
637          CLOSE ( id+110 )
638       ENDDO
639       CLOSE ( 2 )
640       DEALLOCATE ( pf3d )
641!
642!--    Close the NetCDF file
643       IF ( netcdf_output )  THEN
644#if defined( __netcdf )
645          IF ( netcdf_0 )  THEN
646             nc_stat = NF90_CLOSE( id_set(0) )
647             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 19 )
648          ENDIF
649          IF ( netcdf_1 )  THEN
650             nc_stat = NF90_CLOSE( id_set(1) )
651             IF ( nc_stat /= NF90_NOERR )  CALL handle_netcdf_error( 20 )
652          ENDIF
653#endif
654       ENDIF
655    ENDIF
656
657
658 CONTAINS
659
660
661    SUBROUTINE handle_netcdf_error( errno )
662!
663!--    Prints out a text message corresponding to the current NetCDF status
664
665       IMPLICIT NONE
666
667       INTEGER, INTENT(IN) ::  errno
668
669       IF ( nc_stat /= NF90_NOERR )  THEN
670          PRINT*, '+++ combine_plot_fields  netcdf: ', av, errno, &
671                  TRIM( nf90_strerror( nc_stat ) )
672       ENDIF
673
674    END SUBROUTINE handle_netcdf_error
675
676
677 END PROGRAM combine_plot_fields
678
679
680
Note: See TracBrowser for help on using the repository browser.