source: palm/trunk/UTIL/combine_plot_fields.f90 @ 483

Last change on this file since 483 was 226, checked in by raasch, 15 years ago

preparations for the next release

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