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/SOURCE/init_pegrid.f90

    r2300 r2365  
    2525! -----------------
    2626! $Id$
     27! Vertical nesting implemented (SadiqHuq)
     28!
     29! 2300 2017-06-29 13:31:14Z raasch
    2730! host-specific settings removed
    2831!
     
    228231        ONLY:  nxl_y, nxl_yd, nxl_z, nxr_y, nxr_yd, nxr_z, nyn_x, nyn_z, nys_x,&
    229232               nys_z, nzb_x, nzb_y, nzb_yd, nzt_x, nzt_yd, nzt_y
     233
     234    USE vertical_nesting_mod,                                                  &
     235        ONLY:  vnested, vnest_init_pegrid_domain, vnest_init_pegrid_rank
    230236
    231237    IMPLICIT NONE
     
    335341
    336342!
     343!-- Vertical nesting: store four lists that identify partner ranks to exchange
     344!-- data
     345    IF ( vnested )  CALL vnest_init_pegrid_rank
     346
     347!
    337348!-- Determine sub-topologies for transpositions
    338349!-- Transposition from z to x:
     
    642653    CALL MPI_TYPE_COMMIT( type_xy, ierr )
    643654
    644     IF ( TRIM( coupling_mode ) /= 'uncoupled' )  THEN
     655    IF ( TRIM( coupling_mode ) /= 'uncoupled' .AND. .NOT. vnested )  THEN
    645656   
    646657!
     
    743754    ENDIF
    744755
     756!
     757!-- Store partner grid point co-ordinates as lists.
     758!-- Create custom MPI vector datatypes for contiguous data transfer
     759    IF ( vnested )  CALL vnest_init_pegrid_domain
    745760
    746761#endif
Note: See TracChangeset for help on using the changeset viewer.