Ignore:
Timestamp:
Aug 21, 2017 2:59:59 PM (7 years ago)
Author:
kanani
Message:

Vertical nesting implemented (SadiqHuq?)

File:
1 edited

Legend:

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

    r1809 r2365  
    2121! -----------------
    2222!
    23 !
     23! 
    2424! Former revisions:
    2525! -----------------
    2626! $Id$
     27! Vertical grid nesting implemented (SadiqHuq)
     28!
     29! 1809 2016-04-05 20:13:28Z raasch
    2730!
    2831! 1808 2016-04-05 19:44:00Z raasch
     
    120123    LOGICAL  ::  avs_output, compressed, found, iso2d_output, netcdf_output,   &
    121124                 netcdf_parallel, netcdf_0, netcdf_1
     125    LOGICAL  ::  vnest
    122126
    123127    REAL(wp) ::  cpu_start_time, cpu_end_time, dx, simulated_time
     
    126130    REAL(spk), DIMENSION(:,:,:), ALLOCATABLE ::  pf3d, pf3d_tmp
    127131
     132
     133
    128134    PRINT*, ''
    129135    PRINT*, ''
     
    133139!-- Find out if a coupled run has been carried out
    134140    INQUIRE( FILE='COUPLING_PORT_OPENED', EXIST=found )
     141    INQUIRE( FILE='VNESTING_PORT_OPENED', EXIST=vnest )
    135142    IF ( found )  THEN
    136143       models = 2
    137144       PRINT*, '    coupled run'
     145    ELSEIF ( vnest )  THEN
     146       models = 2
     147       PRINT*, '    Vertically nested grid coupling'
    138148    ELSE
    139149       models = 1
     
    160170          PRINT*, '*** combine_plot_fields ***'
    161171          IF ( model == 2 )  THEN
    162              model_string = '_O'
    163              PRINT*, '    now combining ocean data'
    164              PRINT*, '    ========================'
     172             IF ( vnest )  THEN
     173                model_string = '_N'
     174                PRINT*, '    now combining FINE data'
     175                PRINT*, '    ========================'
     176             ELSE
     177                model_string = '_O'
     178                PRINT*, '    now combining ocean data'
     179                PRINT*, '    ========================'
     180             ENDIF
    165181          ELSE
    166              PRINT*, '    now combining atmosphere data'
    167              PRINT*, '    ============================='
     182             IF ( vnest )  THEN
     183                PRINT*, '    now combining COARSE data'
     184                PRINT*, '    ============================='
     185             ELSE
     186                PRINT*, '    now combining atmosphere data'
     187                PRINT*, '    ============================='
     188             ENDIF
    168189          ENDIF
    169190       ENDIF
Note: See TracChangeset for help on using the changeset viewer.