Back to home page

MITgcm

 
 

    


Warning, /pkg/exch2/exch2_send_rx1.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_SEND_RX1
                0006 
                0007 C !INTERFACE:
046fd16d1c Andr*0008       SUBROUTINE EXCH2_SEND_RX1 (
                0009      I       thisTile, nN,
ed81d0a43c Jean*0010      I       e2BufrRecSize,
                0011      I       iBufr,
                0012      I       e2Bufr1_RX,
046fd16d1c Andr*0013      O       e2_msgHandle,
                0014      I       commSetting, myThid )
                0015 
ed81d0a43c Jean*0016 C !DESCRIPTION:
                0017 C     Scalar field (1 component) Exchange:
                0018 C     Send buffer to the target Process.
                0019 C     buffer has been previously filled with interior data point
                0020 C     corresponding to the target-neighbour-edge overlap region.
                0021 
                0022 C !USES:
046fd16d1c Andr*0023       IMPLICIT NONE
                0024 
7dde890654 Jean*0025 #include "SIZE.h"
                0026 #include "EEPARAMS.h"
                0027 #include "EESUPPORT.h"
90219e5912 Jean*0028 #include "W2_EXCH2_SIZE.h"
046fd16d1c Andr*0029 #include "W2_EXCH2_TOPOLOGY.h"
                0030 
ed81d0a43c Jean*0031 C !INPUT/OUTPUT PARAMETERS:
046fd16d1c Andr*0032 C     === Routine arguments ===
ed81d0a43c Jean*0033 C     thisTile      :: sending tile Id. number
                0034 C     nN            :: Neighbour entry that we are processing
                0035 C     e2BufrRecSize :: Number of elements in each entry of e2Bufr1_RX
d6ea3164dc Jean*0036 C     iBufr         :: number of buffer elements to transfer
ed81d0a43c Jean*0037 C     e2Bufr1_RX    :: Data transport buffer array. This array is used in one of
                0038 C                   :: two ways. For PUT communication the entry in the buffer
                0039 C                   :: associated with the source for this receive (determined
                0040 C                   :: from the opposing_send index) is read.
                0041 C                   :: For MSG communication the entry in the buffer associated
                0042 C                   :: with this neighbor of this tile is used as a receive
                0043 C                   :: location for loading a linear stream of bytes.
                0044 C     e2_msgHandles :: Synchronization and coordination data structure used to
                0045 C                   :: coordinate access to e2Bufr1_RX or to regulate message
                0046 C                   :: buffering. In PUT communication sender will increment
                0047 C                   :: handle entry once data is ready in buffer. Receiver will
                0048 C                   :: decrement handle once data is consumed from buffer.
d6ea3164dc Jean*0049 C                   :: For MPI MSG communication MPI_Wait uses handle to check
ed81d0a43c Jean*0050 C                   :: Isend has cleared. This is done in routine after receives.
                0051 C     commSetting   :: Mode of communication used to exchange with this neighbor
                0052 C     myThid        :: my Thread Id. number
                0053 
046fd16d1c Andr*0054       INTEGER thisTile, nN
92307680ae Jean*0055       INTEGER e2BufrRecSize
ed81d0a43c Jean*0056       INTEGER iBufr
046fd16d1c Andr*0057       _RX     e2Bufr1_RX( e2BufrRecSize )
                0058       INTEGER e2_msgHandle(1)
                0059       CHARACTER commSetting
ed81d0a43c Jean*0060       INTEGER myThid
                0061 CEOP
046fd16d1c Andr*0062 
ed81d0a43c Jean*0063 #ifdef ALLOW_USE_MPI
                0064 C !LOCAL VARIABLES:
046fd16d1c Andr*0065 C     == Local variables ==
ed81d0a43c Jean*0066 C     tgT         :: Target tile
                0067       INTEGER  tgT
046fd16d1c Andr*0068 
                0069 C     MPI setup
                0070       INTEGER theTag, theType, theHandle
                0071       INTEGER sProc, tProc, mpiRc
026642cc3c Jean*0072 #ifdef W2_E2_DEBUG_ON
ed81d0a43c Jean*0073       CHARACTER*(MAX_LEN_MBUF) msgBuf
026642cc3c Jean*0074 #endif
046fd16d1c Andr*0075 
ed81d0a43c Jean*0076       tgT = exch2_neighbourId(nN, thisTile )
046fd16d1c Andr*0077 
ed81d0a43c Jean*0078 C     Do data transport depending on communication mechanism between
                0079 C     source and target tile
                0080       IF ( commSetting .EQ. 'M' ) THEN
046fd16d1c Andr*0081 C      Setup MPI stuff here
90219e5912 Jean*0082        theTag =  (thisTile-1)*W2_maxNeighbours + nN
0b153c4cea Jean*0083        tProc = W2_tileProc(tgT)-1
                0084        sProc = W2_tileProc(thisTile)-1
92307680ae Jean*0085        theType = _MPI_TYPE_RX
046fd16d1c Andr*0086 #ifdef W2_E2_DEBUG_ON
b9dadda204 Mart*0087        WRITE(msgBuf,'(A,I8,A,I8,A)')
ed81d0a43c Jean*0088      &  ' SEND FROM TILE=', thisTile, ' (proc =',sProc,')'
                0089        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
                0090      I                     SQUEEZE_RIGHT, myThid)
b9dadda204 Mart*0091        WRITE(msgBuf,'(A,I8,A,I8,A)')
                0092      &  '        TO TILE=', tgT, ' (proc =',tProc,')'
ed81d0a43c Jean*0093        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
                0094      I                     SQUEEZE_RIGHT, myThid)
                0095        WRITE(msgBuf,'(A,I10)') '            TAG=', theTag
                0096        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
                0097      I                     SQUEEZE_RIGHT, myThid)
b9dadda204 Mart*0098        WRITE(msgBuf,'(A,I8)')  '            NEL=', iBufr
ed81d0a43c Jean*0099        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
                0100      I                     SQUEEZE_RIGHT, myThid)
046fd16d1c Andr*0101 #endif /* W2_E2_DEBUG_ON */
                0102        CALL MPI_Isend( e2Bufr1_RX, iBufr, theType,
92307680ae Jean*0103      I                 tProc, theTag, MPI_COMM_MODEL,
046fd16d1c Andr*0104      O                 theHandle, mpiRc )
                0105 C      Store MPI_Wait token in messageHandle.
                0106        e2_msgHandle(1) = theHandle
                0107       ENDIF
ed81d0a43c Jean*0108 #endif /* ALLOW_USE_MPI */
92307680ae Jean*0109 
046fd16d1c Andr*0110       RETURN
                0111       END
2ad152b417 Ed H*0112 
                0113 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
                0114 
                0115 CEH3 ;;; Local Variables: ***
                0116 CEH3 ;;; mode:fortran ***
                0117 CEH3 ;;; End: ***