Back to home page

MITgcm

 
 

    


Warning, /pkg/exch2/exch2_recv_rx2.template is written in an unsupported language. File is not indexed.

view on githubraw file Latest commit b9dadda2 on 2020-07-28 16:49:33 UTC
7dde890654 Jean*0001 #include "CPP_EEOPTIONS.h"
                0002 #include "W2_OPTIONS.h"
046fd16d1c Andr*0003 
ed81d0a43c Jean*0004 CBOP 0
                0005 C !ROUTINE: EXCH2_RECV_RX2
046fd16d1c Andr*0006 
ed81d0a43c Jean*0007 C !INTERFACE:
                0008       SUBROUTINE EXCH2_RECV_RX2(
                0009      I       thisTile, nN,
                0010      I       e2BufrRecSize,
                0011      I       iBufr1, iBufr2,
                0012      I       e2Bufr1_RX, e2Bufr2_RX,
                0013      I       commSetting, myThid )
                0014 
                0015 C !DESCRIPTION:
                0016 C     Two components vector field Exchange:
                0017 C     Receive into buffer exchanged data from the source Process.
                0018 C     buffer data will be used to fill in the tile-edge overlap region.
                0019 
                0020 C !USES:
046fd16d1c Andr*0021       IMPLICIT NONE
                0022 
7dde890654 Jean*0023 #include "SIZE.h"
                0024 #include "EEPARAMS.h"
                0025 #include "EESUPPORT.h"
90219e5912 Jean*0026 #include "W2_EXCH2_SIZE.h"
046fd16d1c Andr*0027 #include "W2_EXCH2_TOPOLOGY.h"
                0028 
ed81d0a43c Jean*0029 C !INPUT/OUTPUT PARAMETERS:
046fd16d1c Andr*0030 C     === Routine arguments ===
d6ea3164dc Jean*0031 C     thisTile      :: receiving tile Id. number
ed81d0a43c Jean*0032 C     nN            :: Neighbour entry that we are processing
                0033 C     e2BufrRecSize :: Number of elements in each entry of e2Bufr1_RX
d6ea3164dc Jean*0034 C     iBufr1        :: number of buffer-1 elements to transfer
                0035 C     iBufr2        :: number of buffer-2 elements to transfer
ed81d0a43c Jean*0036 C     e2Bufr1_RX    :: Data transport buffer array. This array is used in one of
                0037 C     e2Bufr2_RX    :: two ways. For PUT communication the entry in the buffer
                0038 C                   :: associated with the source for this receive (determined
                0039 C                   :: from the opposing_send index) is read.
                0040 C                   :: For MSG communication the entry in the buffer associated
                0041 C                   :: with this neighbor of this tile is used as a receive
                0042 C                   :: location for loading a linear stream of bytes.
                0043 C     commSetting   :: Mode of communication used to exchange with this neighbor
                0044 C     myThid        :: my Thread Id. number
                0045 
                0046       INTEGER thisTile, nN
9b79698769 Jean*0047       INTEGER e2BufrRecSize
ed81d0a43c Jean*0048       INTEGER iBufr1, iBufr2
                0049       _RX     e2Bufr1_RX( e2BufrRecSize )
                0050       _RX     e2Bufr2_RX( e2BufrRecSize )
046fd16d1c Andr*0051       CHARACTER commSetting
ed81d0a43c Jean*0052       INTEGER myThid
                0053 CEOP
046fd16d1c Andr*0054 
ed81d0a43c Jean*0055 #ifdef ALLOW_USE_MPI
                0056 C !LOCAL VARIABLES:
046fd16d1c Andr*0057 C     == Local variables ==
ed81d0a43c Jean*0058 C     soT     :: Source tile Id. number
                0059 C     oNb     :: Opposing send record number
                0060       INTEGER soT
                0061       INTEGER oNb
046fd16d1c Andr*0062 
                0063 C     MPI setup
026642cc3c Jean*0064       INTEGER theTag1, theTag2, theType
                0065       INTEGER sProc, tProc
046fd16d1c Andr*0066       INTEGER mpiStatus(MPI_STATUS_SIZE), mpiRc
026642cc3c Jean*0067 #ifdef W2_E2_DEBUG_ON
ed81d0a43c Jean*0068       CHARACTER*(MAX_LEN_MBUF) msgBuf
046fd16d1c Andr*0069 #endif
                0070 
ed81d0a43c Jean*0071       soT = exch2_neighbourId(nN, thisTile )
                0072       oNb = exch2_opposingSend(nN, thisTile )
046fd16d1c Andr*0073 
ed81d0a43c Jean*0074 C     Handle receive end data transport according to communication mechanism
                0075 C     between source and target tile
                0076       IF ( commSetting .EQ. 'M' ) THEN
046fd16d1c Andr*0077 C      Setup MPI stuff here
ed81d0a43c Jean*0078        theTag1 = (soT-1)*W2_maxNeighbours*2 + oNb-1
                0079        theTag2 = (soT-1)*W2_maxNeighbours*2 + W2_maxNeighbours + oNb-1
0b153c4cea Jean*0080        tProc = W2_tileProc(thisTile)-1
                0081        sProc = W2_tileProc(soT)-1
92307680ae Jean*0082        theType = _MPI_TYPE_RX
ed81d0a43c Jean*0083        CALL MPI_Recv( e2Bufr1_RX, iBufr1, theType, sProc,
                0084      &                theTag1, MPI_COMM_MODEL, mpiStatus, mpiRc )
                0085        CALL MPI_Recv( e2Bufr2_RX, iBufr2, theType, sProc,
                0086      &                theTag2, MPI_COMM_MODEL, mpiStatus, mpiRc )
046fd16d1c Andr*0087 #ifdef W2_E2_DEBUG_ON
b9dadda204 Mart*0088        WRITE(msgBuf,'(A,I8,A,I8,A)')
ed81d0a43c Jean*0089      &   ' RECV FROM TILE=', soT, ' (proc = ',sProc,')'
                0090        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
                0091      I                     SQUEEZE_RIGHT, myThid )
b9dadda204 Mart*0092        WRITE(msgBuf,'(A,I8,A,I8,A)')
ed81d0a43c Jean*0093      &   '  INTO TILE=', thisTile, ' (proc = ',tProc,')'
                0094        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
                0095      I                     SQUEEZE_RIGHT, myThid )
                0096        WRITE(msgBuf,'(A,I10)') '            TAG1=', theTag1
                0097        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
                0098      I                     SQUEEZE_RIGHT, myThid )
b9dadda204 Mart*0099        WRITE(msgBuf,'(A,I8)')  '            NEL1=', iBufr1
ed81d0a43c Jean*0100        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
                0101      I                     SQUEEZE_RIGHT, myThid )
                0102        WRITE(msgBuf,'(A,I10)') '            TAG2=', theTag2
                0103        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
                0104      I                     SQUEEZE_RIGHT, myThid )
b9dadda204 Mart*0105        WRITE(msgBuf,'(A,I8)')  '            NEL2=', iBufr2
ed81d0a43c Jean*0106        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
                0107      I                     SQUEEZE_RIGHT, myThid )
046fd16d1c Andr*0108 #endif /* W2_E2_DEBUG_ON */
                0109       ENDIF
ed81d0a43c Jean*0110 #endif /* ALLOW_USE_MPI */
9b79698769 Jean*0111 
046fd16d1c Andr*0112       RETURN
                0113       END
2ad152b417 Ed H*0114 
                0115 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
                0116 
                0117 CEH3 ;;; Local Variables: ***
                0118 CEH3 ;;; mode:fortran ***
                0119 CEH3 ;;; End: ***