Changeset 2512 for palm/trunk/UTIL


Ignore:
Timestamp:
Oct 4, 2017 8:26:59 AM (7 years ago)
Author:
raasch
Message:

upper bounds of cross section and 3d output changed from nx+1,ny+1 to nx,ny; no output if redundant ghost layer data to NetCDF files

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/UTIL/combine_plot_fields.f90

    r2365 r2512  
    2525! -----------------
    2626! $Id$
     27! PALM output does not contain ghost layer data any more
     28! avs- and iso2d-related parts removed, handling of compressed data removed
     29!
     30! 2365 2017-08-21 14:59:59Z kanani
    2731! Vertical grid nesting implemented (SadiqHuq)
    2832!
     
    121125    INTEGER(iwp), DIMENSION(0:1,1000) ::  id_var, levels
    122126
    123     LOGICAL  ::  avs_output, compressed, found, iso2d_output, netcdf_output,   &
    124                  netcdf_parallel, netcdf_0, netcdf_1
     127    LOGICAL  ::  found, netcdf_output, netcdf_parallel, netcdf_0, netcdf_1
    125128    LOGICAL  ::  vnest
    126129
    127130    REAL(wp) ::  cpu_start_time, cpu_end_time, dx, simulated_time
    128     REAL(wp),  DIMENSION(:),   ALLOCATABLE   ::  eta, ho, hu
    129131    REAL(wp),  DIMENSION(:,:), ALLOCATABLE   ::  pf, pf_tmp
    130132    REAL(spk), DIMENSION(:,:,:), ALLOCATABLE ::  pf3d, pf3d_tmp
     
    227229
    228230!
    229 !--       Inquire whether an iso2d parameter file exists
    230           INQUIRE( FILE='PLOT2D_'//modus//'_GLOBAL'//TRIM( model_string ), &
    231                EXIST=iso2d_output )
    232 
    233 !
    234231!--       Inquire whether a NetCDF file exists
    235232          INQUIRE( FILE='DATA_2D_'//modus//'_NETCDF'//TRIM( model_string ), &
     
    387384!--                File from PE0 contains special information at the beginning,
    388385!--                concerning the lower and upper indices of the total-domain
    389 !--                used in PALM (nxag, nxeg, nyag, nyeg) and the lower and
    390 !--                upper indices of the array to be written by this routine
    391 !--                (nxa, nxe, nya, nye). Usually in the horizontal directions
    392 !--                nxag=-1 and nxa=0 while all other variables have the same
    393 !--                value (i.e. nxeg=nxe).
     386!--                used in PALM (nxa, nxe, nya, nye).
    394387!--                Allocate necessary arrays, open the output file and write
    395388!--                the coordinate informations needed by ISO2D.
    396389                   IF ( id == 0  .AND.  fanz(0) == 0  .AND.  fanz(1) == 0 ) THEN
    397                       READ ( id+110 )  nxag, nxeg, nyag, nyeg
     390
    398391                      READ ( id+110 )  nxa, nxe, nya, nye
    399                       ALLOCATE ( eta(nya:nye), ho(nxa:nxe), hu(nxa:nxe), &
    400                                  pf(nxag:nxeg,nyag:nyeg) )
    401                       READ ( id+110 )  dx, eta, hu, ho
    402 
    403 
     392                      ALLOCATE ( pf(nxa:nxe,nya:nye) )
    404393!
    405394!--                   Set actual domain bounds to total domain
     
    407396                      ye_do = nye
    408397
    409                       IF ( iso2d_output )  THEN
    410                          OPEN ( 2, FILE='PLOT2D_'//modus//TRIM( model_string ),&
    411                                    FORM='UNFORMATTED' )
    412                          WRITE ( 2 )  dx, eta, hu, ho
    413                       ENDIF
    414398                   ENDIF
    415399!
    416400!--                Read output time
    417401                   IF ( netcdf_output  .AND.  id == 0 )  THEN
    418                       IF ( netcdf_1 )  THEN
    419                          READ ( id+110, END=998 )  simulated_time, time_step, av
    420                       ELSE
    421 !
    422 !--                      For compatibility with earlier PALM versions
    423                          READ ( id+110, END=998 )  simulated_time, time_step
    424                          av = 0
    425                       ENDIF
     402                      READ ( id+110, END=998 )  simulated_time, time_step, av
    426403                   ENDIF
    427404!
     
    460437                ENDDO
    461438!
    462 !--             Write the data of the total domain cross-section
    463                 IF ( iso2d_output )  WRITE ( 2 )  pf(nxa:nxe,nya:nye)
    464        
    465 !
    466 !--             Write same data in NetCDF format
     439!--             Write data in NetCDF format
    467440                IF ( netcdf_output )  THEN
    468441#if defined( __netcdf )
     
    544517             ENDDO
    545518             CLOSE ( 2 )
    546              DEALLOCATE ( eta, ho, hu, pf )
     519             DEALLOCATE ( pf )
    547520
    548521!
     
    598571       CALL SYSTEM_CLOCK( count, count_rate )
    599572       cpu_start_time = REAL( count ) / REAL( count_rate )
    600 
    601 !
    602 !--    Inquire whether an avs fld file exists
    603        INQUIRE( FILE='PLOT3D_FLD'//TRIM( model_string ), EXIST=avs_output )
    604573
    605574!
     
    639608
    640609!
    641 !--    Combination only works, if data are not compressed. In that case,
    642 !--    PALM created a flag file (PLOT3D_COMPRESSED)
    643        INQUIRE ( FILE='PLOT3D_COMPRESSED'//TRIM( model_string ), &
    644             EXIST=compressed )
    645 
    646 !
    647610!--    Find out the number of files and open them
    648        DO  WHILE ( found  .AND.  .NOT. compressed )
     611       DO  WHILE ( found )
    649612
    650613          OPEN ( danz+110, &
     
    678641             PRINT*, '    3D-data:     ', danz, ' file(s) found'
    679642          ELSE
    680              IF ( found .AND. compressed )  THEN
    681                 PRINT*, '+++ no 3D-data processing, since data are compressed'
    682              ELSE
    683                 PRINT*, '    no 3D-data file available'
    684              ENDIF
     643             PRINT*, '    no 3D-data file available'
    685644          ENDIF
    686645       ENDIF
     
    764723             DO  id = 0, danz-1
    765724!
    766 !--             File from PE0 contains special information at the beginning,
    767 !--             concerning the lower and upper indices of the total-domain used
    768 !--             in PALM (nxag, nxeg, nyag, nyeg) and the lower and
    769 !--             upper indices of the array to be written by this routine (nxa,
    770 !--             nxe, nya, nye, nza, nze). Usually nxag=-1 and nxa=0, nyag=-1
    771 !--             and nya=0, nzeg=nz and nze=nz_do3d.
    772 !--             Allocate necessary array and open the output file.
     725!--             File from PE0 contains at the beginning the index bounds
     726!--             of PALM's total domain.
     727!--             Allocate the array for storing the total domain data
    773728                IF ( id == 0  .AND.  fanz(0) == 0  .AND.  fanz(1) == 0 )  THEN
    774                    READ ( id+110 )  nxag, nxeg, nyag, nyeg
     729!                   READ ( id+110 )  nxag, nxeg, nyag, nyeg
    775730                   READ ( id+110 )  nxa, nxe, nya, nye, nza, nze
    776731                   ALLOCATE ( pf3d(nxa:nxe,nya:nye,nza:nze) )
    777                    IF ( avs_output )  THEN
    778                       OPEN ( 2, FILE='PLOT3D_DATA'//TRIM( model_string ), &
    779                              FORM='UNFORMATTED' )
    780                    ENDIF
    781732                ENDIF
    782733
     
    818769
    819770!
    820 !--          Write data of the total domain
    821              IF ( avs_output )  WRITE ( 2 )  pf3d(nxa:nxe,nya:nye,nza:nze)
    822        
    823 !
    824 !--          Write same data in NetCDF format
     771!--          Write data of the total domain in NetCDF format
    825772             IF ( netcdf_output )  THEN
    826773#if defined( __netcdf )
Note: See TracChangeset for help on using the changeset viewer.