Ignore:
Timestamp:
Jun 12, 2020 2:03:36 PM (4 years ago)
Author:
raasch
Message:

Vertical nesting method of Huq et al. (2019) removed

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/init_coupling.f90

    r4444 r4564  
    2525! ------------------
    2626! $Id$
     27! Vertical nesting method of Huq et al. (2019) removed
     28!
     29! 4444 2020-03-05 15:59:50Z raasch
    2730! bugfix: cpp-directives for serial mode added
    2831!
     
    5053   
    5154    USE pegrid
    52 
    53     USE vertical_nesting_mod
    5455
    5556    IMPLICIT NONE
     
    8485       IF ( TRIM( coupling_mode ) == 'coupled_run' )  THEN
    8586          i = 1
    86        ELSEIF ( TRIM( coupling_mode ) == 'vnested_twi' )  THEN
    87           i = 9
    8887       ELSE
    8988          i = 0
     
    111110          CLOSE ( 90 )
    112111       ENDIF
    113     ELSEIF ( i == 9 )  THEN
    114 
    115 !
    116 !--    Set a flag to identify runs with vertical nesting
    117        vnested = .TRUE.
    118        
    119        comm_inter = MPI_COMM_WORLD
    120        
    121 !
    122 !--    Split the total available PE's into two groups
    123 !--    numprocs for coarse and fine grid are read from stdin (see above, and
    124 !--    execution command in the palmrun script, numprocs are provided via
    125 !--    palmrun option -Y)
    126        IF ( myid < bc_data(1) )  THEN
    127           inter_color     = 0
    128           numprocs        = bc_data(1)
    129           coupling_mode   = 'vnested_crse'
    130        ELSE
    131           inter_color     = 1
    132           numprocs        = bc_data(2)
    133           coupling_mode   = 'vnested_fine'
    134        ENDIF
    135        
    136        CALL MPI_COMM_SPLIT( MPI_COMM_WORLD, inter_color, 0, comm_palm, ierr )
    137        comm2d = comm_palm
    138        
    139        OPEN( 90, FILE='VNESTING_PORT_OPENED', FORM='FORMATTED' )
    140        WRITE ( 90, '(''TRUE'')' )
    141        CLOSE ( 90 )
    142      
    143112    ELSE
    144113       comm_inter = MPI_COMM_WORLD
     
    174143    ENDIF
    175144
    176     IF (  TRIM( coupling_mode ) == 'vnested_fine' )  THEN
    177 !
    178 !-- Set file extension for vertical nesting
    179        coupling_char = '_NV'
    180     ENDIF
    181 
    182145 END SUBROUTINE init_coupling
Note: See TracChangeset for help on using the changeset viewer.