Ignore:
Timestamp:
Aug 25, 2017 12:37:32 PM (7 years ago)
Author:
sward
Message:

y_shift for periodic boundary conditions

File:
1 edited

Legend:

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

    r2365 r2372  
    2525! -----------------
    2626! $Id$
     27! Shifted cyclic boundary conditions implemented
     28!
     29! 2365 2017-08-21 14:59:59Z kanani
    2730! Vertical nesting implemented (SadiqHuq)
    2831!
     
    206209               psolver, outflow_l, outflow_n, outflow_r, outflow_s,            &
    207210               outflow_source_plane, recycling_width, scalar_advec,            &
    208                subdomain_size, turbulent_outflow
     211               subdomain_size, turbulent_outflow, y_shift
    209212
    210213    USE grid_variables,                                                        &
     
    271274    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nysf    !<
    272275
    273     INTEGER(iwp), DIMENSION(2) :: pdims_remote          !<
     276    INTEGER(iwp), DIMENSION(2) ::  pdims_remote         !<
     277    INTEGER(iwp)               ::  lcoord(2)            !< PE coordinates of left neighbor along x and y
     278    INTEGER(iwp)               ::  rcoord(2)            !< PE coordinates of right neighbor along x and y
    274279
    275280!
     
    339344    CALL MPI_CART_SHIFT( comm2d, 0, 1, pleft, pright, ierr )
    340345    CALL MPI_CART_SHIFT( comm2d, 1, 1, psouth, pnorth, ierr )
     346
     347!
     348!-- In case of cyclic boundary conditions, a y-shift at the boundaries in
     349!-- x-direction can be introduced via parameter y_shift. The shift is done
     350!-- by modifying the processor grid in such a way that processors located
     351!-- at the x-boundary communicate across it to processors with y-coordinate
     352!-- shifted by y_shift relative to their own. This feature can not be used
     353!-- in combination with an fft pressure solver. It has been implemented to
     354!-- counter the effect of streak structures in case of cyclic boundary
     355!-- conditions. For a description of these see Munters
     356!-- (2016; dx.doi.org/10.1063/1.4941912)
     357!--
     358!-- Get coordinates of left and right neighbor on PE grid
     359    IF ( y_shift /= 0 ) THEN
     360
     361       IF ( bc_lr /= 'cyclic'  .OR.  bc_ns /= 'cyclic' )  THEN
     362          message_string = 'y_shift /= 0 is only allowed for cyclic ' //       &
     363                           'boundary conditions in both directions '
     364          CALL message( 'check_parameters', 'PA0467', 1, 2, 0, 6, 0 )
     365       ENDIF
     366       IF ( TRIM( psolver ) /= 'multigrid' .AND.                               &
     367            TRIM( psolver ) /= 'multigrid_noopt')                              &
     368       THEN
     369          message_string = 'y_shift /= 0 requires a multigrid pressure solver '
     370          CALL message( 'check_parameters', 'PA0468', 1, 2, 0, 6, 0 )
     371       ENDIF
     372
     373       CALL MPI_CART_COORDS( comm2d, pright, ndim, rcoord, ierr )
     374       CALL MPI_CART_COORDS( comm2d, pleft, ndim, lcoord, ierr )
     375
     376!
     377!--    If the x(y)-coordinate of the right (left) neighbor is smaller (greater)
     378!--    than that of the calling process, then the calling process is located on
     379!--    the right (left) boundary of the processor grid. In that case,
     380!--    the y-coordinate of that neighbor is increased (decreased) by y_shift.
     381!--    The rank of the process with that coordinate is then inquired and the
     382!--    neighbor rank for MPI_SENDRECV, pright (pleft) is set to it.
     383!--    In this way, the calling process receives a new right (left) neighbor
     384!--    for all future MPI_SENDRECV calls. That neighbor has a y-coordinate
     385!--    of y+(-)y_shift, where y is the original right (left) neighbor's
     386!--    y-coordinate. The modulo-operation ensures that if the neighbor's
     387!--    y-coordinate exceeds the grid-boundary, it will be relocated to
     388!--    the opposite part of the grid cyclicly.
     389       IF ( rcoord(1) < pcoord(1) ) THEN
     390          rcoord(2) = MODULO( rcoord(2) + y_shift, pdims(2) )
     391          CALL MPI_CART_RANK( comm2d, rcoord, pright, ierr )
     392       ENDIF
     393
     394       IF ( lcoord(1) > pcoord(1) ) THEN
     395          lcoord(2) = MODULO( lcoord(2) - y_shift, pdims(2) )
     396          CALL MPI_CART_RANK( comm2d, lcoord, pleft, ierr )
     397       ENDIF
     398    ENDIF
    341399
    342400!
Note: See TracChangeset for help on using the changeset viewer.