Ignore:
Timestamp:
Feb 28, 2016 12:45:19 PM (8 years ago)
Author:
raasch
Message:

update of the nested domain system + some bugfixes

File:
1 edited

Legend:

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

    r1763 r1764  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! cpp-statements for nesting removed
    2222!
    2323! Former revisions:
     
    151151    USE pegrid
    152152 
    153 #if defined( PMC_ACTIVE )
    154153    USE pmc_interface,                                                         &
    155         ONLY:  cpl_npex,cpl_npey
    156 #endif
     154        ONLY:  cpl_npex, cpl_npey, nested_run
    157155
    158156    USE transpose_indices,                                                     &
     
    215213    CALL location_message( 'creating virtual PE grids + MPI derived data types', &
    216214                           .FALSE. )
    217 #if defined( PMC_ACTIVE )
    218 !
    219 !-- In case of nested-domain runs, the processor grid is explicitly given
    220 !-- by the user in the nestpar-NAMELIST
    221     pdims(1) = cpl_npex
    222     pdims(2) = cpl_npey
    223 #else
    224 !
    225 !-- Determine the processor topology or check it, if prescribed by the user
    226     IF ( npex == -1  .AND.  npey == -1 )  THEN
    227 
    228 !
    229 !--    Automatic determination of the topology
    230        numproc_sqr = SQRT( REAL( numprocs, KIND=wp ) )
    231        pdims(1)    = MAX( numproc_sqr , 1 )
    232        DO  WHILE ( MOD( numprocs , pdims(1) ) /= 0 )
    233           pdims(1) = pdims(1) - 1
    234        ENDDO
    235        pdims(2) = numprocs / pdims(1)
    236 
    237     ELSEIF ( npex /= -1  .AND.  npey /= -1 )  THEN
    238 
    239 !
    240 !--    Prescribed by user. Number of processors on the prescribed topology
    241 !--    must be equal to the number of PEs available to the job
    242        IF ( ( npex * npey ) /= numprocs )  THEN
    243           WRITE( message_string, * ) 'number of PEs of the prescribed ',      &
     215
     216    IF ( nested_run )  THEN
     217!
     218!--    In case of nested-domain runs, the processor grid is explicitly given
     219!--    by the user in the nestpar-NAMELIST
     220       pdims(1) = cpl_npex
     221       pdims(2) = cpl_npey
     222
     223    ELSE
     224!
     225!--    Determine the processor topology or check it, if prescribed by the user
     226       IF ( npex == -1  .AND.  npey == -1 )  THEN
     227
     228!
     229!--       Automatic determination of the topology
     230          numproc_sqr = SQRT( REAL( numprocs, KIND=wp ) )
     231          pdims(1)    = MAX( numproc_sqr , 1 )
     232          DO  WHILE ( MOD( numprocs , pdims(1) ) /= 0 )
     233             pdims(1) = pdims(1) - 1
     234          ENDDO
     235          pdims(2) = numprocs / pdims(1)
     236
     237       ELSEIF ( npex /= -1  .AND.  npey /= -1 )  THEN
     238
     239!
     240!--       Prescribed by user. Number of processors on the prescribed topology
     241!--       must be equal to the number of PEs available to the job
     242          IF ( ( npex * npey ) /= numprocs )  THEN
     243             WRITE( message_string, * ) 'number of PEs of the prescribed ',   &
    244244                 'topology (', npex*npey,') does not match & the number of ', &
    245245                 'PEs available to the job (', numprocs, ')'
    246           CALL message( 'init_pegrid', 'PA0221', 1, 2, 0, 6, 0 )
    247        ENDIF
    248        pdims(1) = npex
    249        pdims(2) = npey
    250 
    251     ELSE
    252 !
    253 !--    If the processor topology is prescribed by the user, the number of
    254 !--    PEs must be given in both directions
    255        message_string = 'if the processor topology is prescribed by the, ' //  &
    256                    ' user& both values of "npex" and "npey" must be given ' // &
    257                    'in the &NAMELIST-parameter file'
    258        CALL message( 'init_pegrid', 'PA0222', 1, 2, 0, 6, 0 )
    259 
    260     ENDIF
    261 #endif
     246             CALL message( 'init_pegrid', 'PA0221', 1, 2, 0, 6, 0 )
     247          ENDIF
     248          pdims(1) = npex
     249          pdims(2) = npey
     250
     251       ELSE
     252!
     253!--       If the processor topology is prescribed by the user, the number of
     254!--       PEs must be given in both directions
     255          message_string = 'if the processor topology is prescribed by th' //  &
     256                   'e user& both values of "npex" and "npey" must be given' // &
     257                   ' in the &NAMELIST-parameter file'
     258          CALL message( 'init_pegrid', 'PA0222', 1, 2, 0, 6, 0 )
     259
     260       ENDIF
     261
     262    ENDIF
     263
    262264
    263265!
     
    10821084       ELSEIF ( bc_lr == 'radiation/dirichlet' )  THEN
    10831085          outflow_l = .TRUE.
    1084 #if defined( PMC_ACTIVE )
    10851086       ELSEIF ( bc_lr == 'nested' )  THEN
    10861087          nest_bound_l = .TRUE.
    1087 #endif
    10881088       ENDIF
    10891089    ENDIF
     
    10941094       ELSEIF ( bc_lr == 'radiation/dirichlet' )  THEN
    10951095          inflow_r  = .TRUE.
    1096 #if defined( PMC_ACTIVE )
    10971096       ELSEIF ( bc_lr == 'nested' )  THEN
    10981097          nest_bound_r = .TRUE.
    1099 #endif
    11001098       ENDIF
    11011099    ENDIF
     
    11061104       ELSEIF ( bc_ns == 'radiation/dirichlet' )  THEN
    11071105          inflow_s  = .TRUE.
    1108 #if defined( PMC_ACTIVE )
    11091106       ELSEIF ( bc_ns == 'nested' )  THEN
    11101107          nest_bound_s = .TRUE.
    1111 #endif
    11121108       ENDIF
    11131109    ENDIF
     
    11181114       ELSEIF ( bc_ns == 'radiation/dirichlet' )  THEN
    11191115          outflow_n = .TRUE.
    1120 #if defined( PMC_ACTIVE )
    11211116       ELSEIF ( bc_ns == 'nested' )  THEN
    11221117          nest_bound_n = .TRUE.
    1123 #endif
    11241118       ENDIF
    11251119    ENDIF
Note: See TracChangeset for help on using the changeset viewer.