/[MITgcm]/MITgcm/pkg/exch2/exch2_recv_rx2.template
ViewVC logotype

Diff of /MITgcm/pkg/exch2/exch2_recv_rx2.template

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.9 by jmc, Wed May 20 21:01:45 2009 UTC revision 1.10 by jmc, Sat May 30 21:18:59 2009 UTC
# Line 4  C $Name$ Line 4  C $Name$
4  #include "CPP_EEOPTIONS.h"  #include "CPP_EEOPTIONS.h"
5  #include "W2_OPTIONS.h"  #include "W2_OPTIONS.h"
6    
7    CBOP 0
8    C !ROUTINE: EXCH2_RECV_RX2
9    
10    C !INTERFACE:
11        SUBROUTINE EXCH2_RECV_RX2(        SUBROUTINE EXCH2_RECV_RX2(
12       I       tIlo1, tIhi1, tIlo2, tIhi2, tiStride,       I       thisTile, nN,
13       I       tJlo1, tJhi1, tJlo2, tJhi2, tjStride,       I       e2BufrRecSize,
14       I       tKlo, tKhi, tkStride,       I       iBufr1, iBufr2,
15       I       thisTile, thisI, nN,       I       e2Bufr1_RX, e2Bufr2_RX,
16       I       e2Bufr1_RX, e2Bufr2_RX, e2BufrRecSize,       I       commSetting, myThid )
17       I       mnb, nt,  
18       U       array1,  C !DESCRIPTION:
19       I       i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,  C     Two components vector field Exchange:
20       U       array2,  C     Receive into buffer exchanged data from the source Process.
21       I       i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,  C     buffer data will be used to fill in the tile-edge overlap region.
      U       e2_msgHandles, myTiles,  
      I       commSetting,  
      I       myThid )  
22    
23    C !USES:
24        IMPLICIT NONE        IMPLICIT NONE
25    
26  #include "SIZE.h"  #include "SIZE.h"
# Line 27  C $Name$ Line 29  C $Name$
29  #include "W2_EXCH2_SIZE.h"  #include "W2_EXCH2_SIZE.h"
30  #include "W2_EXCH2_TOPOLOGY.h"  #include "W2_EXCH2_TOPOLOGY.h"
31    
32    C !INPUT/OUTPUT PARAMETERS:
33  C     === Routine arguments ===  C     === Routine arguments ===
34  C     tIlo1,tIhi1,tIstride :: index range in I that will be filled in target "array1"  C     thisTile      :: receiveing tile Id. number
35  C     tIlo2,tIhi2,tIstride :: index range in I that will be filled in target "array2"  C     nN            :: Neighbour entry that we are processing
36  C     tJlo1,tJhi1,tJstride :: index range in J that will be filled in target "array1"  C     e2BufrRecSize :: Number of elements in each entry of e2Bufr1_RX
37  C     tJlo2,tJhi2,tJstride :: index range in J that will be filled in target "array2"  C     iBufr1        :: number of buffer-1 elements to transfert
38  C     tKlo, tKhi, tKstride :: index range in K that will be filled in target arrays  C     iBufr2        :: number of buffer-2 elements to transfert
39  C     thisTile             :: Rank of the receiveing tile  C     e2Bufr1_RX    :: Data transport buffer array. This array is used in one of
40  C     thisI                :: Index of the receiving tile within this process (used  C     e2Bufr2_RX    :: two ways. For PUT communication the entry in the buffer
41  C                          :: to select buffer slots that are allowed).  C                   :: associated with the source for this receive (determined
42  C     nN                   :: Neighbour entry that we are processing  C                   :: from the opposing_send index) is read.
43  C     e2Bufr1_RX           :: Data transport buffer array. This array is used in one of  C                   :: For MSG communication the entry in the buffer associated
44  C                          :: two ways. For PUT communication the entry in the buffer  C                   :: with this neighbor of this tile is used as a receive
45  C                          :: associated with the source for this receive (determined  C                   :: location for loading a linear stream of bytes.
46  C                          :: from the opposing_send index) is read. For MSG communication  C     commSetting   :: Mode of communication used to exchange with this neighbor
47  C                          :: the entry in the buffer associated with this neighbor of this  C     myThid        :: my Thread Id. number
48  C                          :: tile is used as a receive location for loading a linear  
49  C                          :: stream of bytes.        INTEGER thisTile, nN
 C     e2BufrRecSize        :: Number of elements in each entry of e2Bufr1_RX  
 C     mnb                  :: Second dimension of e2Bufr1_RX  
 C     nt                   :: Third dimension of e2Bufr1_RX  
 C     array                :: Target array that this receive writes to.  
 C     i1Lo, i1Hi           :: I coordinate bounds of target array  
 C     j1Lo, j1Hi           :: J coordinate bounds of target array  
 C     k1Lo, k1Hi           :: K coordinate bounds of target array  
 C     e2_msgHandles        :: Synchronization and coordination data structure used to coordinate access  
 C                          :: to e2Bufr1_RX or to regulate message buffering. In PUT communication  
 C                          :: sender will increment handle entry once data is ready in buffer.  
 C                          :: Receiver will decrement handle once data is consumed from buffer. For  
 C                          :: MPI MSG communication MPI_Wait uses hanlde to check Isend has cleared.  
 C                          :: This is done in routine after receives.  
 C     myTiles              :: List of nt tiles that this process owns.  
 C     commSetting          :: Mode of communication used to exchnage with this neighbor  
 C     myThid               :: Thread number of this instance of EXCH2_RECV_RX2  
   
       INTEGER tIlo1, tIhi1, tIlo2, tIhi2, tiStride  
       INTEGER tJlo1, tJhi1, tJlo2, tJhi2, tjStride  
       INTEGER tKlo, tKhi, tkStride  
       INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi  
       INTEGER i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi  
       INTEGER thisTile, nN, thisI  
50        INTEGER e2BufrRecSize        INTEGER e2BufrRecSize
51        INTEGER mnb, nt        INTEGER iBufr1, iBufr2
52        _RX     e2Bufr1_RX( e2BufrRecSize, mnb, nt, 2 )        _RX     e2Bufr1_RX( e2BufrRecSize )
53        _RX     e2Bufr2_RX( e2BufrRecSize, mnb, nt, 2 )        _RX     e2Bufr2_RX( e2BufrRecSize )
       _RX     array1(i1Lo:i1Hi,j1Lo:j1Hi,k1Lo:k1Hi)  
       _RX     array2(i2Lo:i2Hi,j2Lo:j2Hi,k2Lo:k2Hi)  
       INTEGER e2_msgHandles(2, mnb, nt)  
       INTEGER myThid  
       INTEGER myTiles(nt)  
54        CHARACTER commSetting        CHARACTER commSetting
55          INTEGER myThid
56    CEOP
57    
58    #ifdef ALLOW_USE_MPI
59    C !LOCAL VARIABLES:
60  C     == Local variables ==  C     == Local variables ==
61  C     itl, jtl, ktl  :: Loop counters  C     soT     :: Source tile Id. number
62  C                    :: itl etc... target local  C     oNb     :: Opposing send record number
63        INTEGER itl, jtl, ktl        INTEGER soT
64  C     tt         :: Target tile        INTEGER oNb
 C     iBufr1     :: Buffer counter  
 C     iBufr2     ::  
       INTEGER tt  
       INTEGER iBufr1, iBufr2  
 C     mb, nb :: Selects e2Bufr, msgHandle record to use  
 C     ir     ::  
       INTEGER mb, nb, ir  
 C     oN     :: Opposing send record number  
       INTEGER oN  
 C     Loop counters  
       INTEGER I  
65    
66  C     MPI setup  C     MPI setup
 #ifdef ALLOW_USE_MPI  
       INTEGER nri1, nrj1, nrk1  
       INTEGER nri2, nrj2, nrk2  
67        INTEGER theTag1, theTag2, theType        INTEGER theTag1, theTag2, theType
68        INTEGER sProc, tProc        INTEGER sProc, tProc
69        INTEGER mpiStatus(MPI_STATUS_SIZE), mpiRc        INTEGER mpiStatus(MPI_STATUS_SIZE), mpiRc
70  #ifdef W2_E2_DEBUG_ON  #ifdef W2_E2_DEBUG_ON
71        CHARACTER*(MAX_LEN_MBUF) messageBuffer        CHARACTER*(MAX_LEN_MBUF) msgBuf
 #endif  
72  #endif  #endif
73    
74        tt=exch2_neighbourId(nN, thisTile )        soT = exch2_neighbourId(nN, thisTile )
75        oN=exch2_opposingSend(nN, thisTile )        oNb = exch2_opposingSend(nN, thisTile )
76    
77  C     Handle receive end data transport according to communication mechanism between  C     Handle receive end data transport according to communication mechanism
78  C     source and target tile  C     between source and target tile
79        IF     ( commSetting .EQ. 'P' ) THEN        IF ( commSetting .EQ. 'M' ) THEN
 C      1 Need to check and spin on data ready assertion for multithreaded mode, for now do nothing i.e.  
 C        assume only one thread per process.  
   
 C      2 Need to set e2Bufr to use put buffer from opposing send.  
        oN = exch2_opposingSend(nN, thisTile )  
        mb = oN  
        ir = 1  
        DO I=1,nt  
         IF ( myTiles(I) .EQ. tt ) THEN  
          nb = I  
         ENDIF  
        ENDDO  
 C      Get data from e2Bufr(1,mb,nb)  
       ELSEIF ( commSetting .EQ. 'M' ) THEN  
 #ifdef ALLOW_USE_MPI  
80  C      Setup MPI stuff here  C      Setup MPI stuff here
81         nb = thisI         theTag1 = (soT-1)*W2_maxNeighbours*2 + oNb-1
82         mb = nN         theTag2 = (soT-1)*W2_maxNeighbours*2 + W2_maxNeighbours + oNb-1
        ir = 2  
        theTag1 =  (tt-1)*W2_maxNeighbours*2 + oN-1  
        theTag2 =  (tt-1)*W2_maxNeighbours*2 + W2_maxNeighbours + oN-1  
83         tProc = exch2_tProc(thisTile)-1         tProc = exch2_tProc(thisTile)-1
84         sProc = exch2_tProc(tt)-1         sProc = exch2_tProc(soT)-1
85         theType = _MPI_TYPE_RX         theType = _MPI_TYPE_RX
86         nri1 = (tIhi1-tIlo1+1)/tiStride         CALL MPI_Recv( e2Bufr1_RX, iBufr1, theType, sProc,
87         nrj1 = (tJhi1-tJlo1+1)/tjStride       &                theTag1, MPI_COMM_MODEL, mpiStatus, mpiRc )
88         nrk1 = (tKhi-tKlo+1)/tkStride         CALL MPI_Recv( e2Bufr2_RX, iBufr2, theType, sProc,
89         iBufr1 = nri1*nrj1*nrk1       &                theTag2, MPI_COMM_MODEL, mpiStatus, mpiRc )
        nri2 = (tIhi2-tIlo2+1)/tiStride  
        nrj2 = (tJhi2-tJlo2+1)/tjStride  
        nrk2 = (tKhi-tKlo+1)/tkStride  
        iBufr2 = nri2*nrj2*nrk2  
        CALL MPI_Recv( e2Bufr1_RX(1,mb,nb,ir), iBufr1, theType, sProc,  
      &               theTag1, MPI_COMM_MODEL, mpiStatus, mpiRc )  
        CALL MPI_Recv( e2Bufr2_RX(1,mb,nb,ir), iBufr2, theType, sProc,  
      &               theTag2, MPI_COMM_MODEL, mpiStatus, mpiRc )  
90  #ifdef W2_E2_DEBUG_ON  #ifdef W2_E2_DEBUG_ON
91         WRITE(messageBuffer,'(A,I4,A,I4,A)') ' RECV FROM TILE=', tt,         WRITE(msgBuf,'(A,I4,A,I4,A)')
92       &                                   ' (proc = ',sProc,')'       &   ' RECV FROM TILE=', soT, ' (proc = ',sProc,')'
93         CALL PRINT_MESSAGE(messageBuffer,         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
94       I      standardMessageUnit,SQUEEZE_RIGHT,       I                     SQUEEZE_RIGHT, myThid )
95       I      myThid)         WRITE(msgBuf,'(A,I4,A,I4,A)')
96         WRITE(messageBuffer,'(A,I4,A,I4,A)') '      INTO TILE=',thisTile,       &   '  INTO TILE=', thisTile, ' (proc = ',tProc,')'
97       &                                   ' (proc = ',tProc,')'         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
98         CALL PRINT_MESSAGE(messageBuffer,       I                     SQUEEZE_RIGHT, myThid )
99       I      standardMessageUnit,SQUEEZE_RIGHT,         WRITE(msgBuf,'(A,I10)') '            TAG1=', theTag1
100       I      myThid)         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
101         WRITE(messageBuffer,'(A,I10)') '            TAG1=', theTag1       I                     SQUEEZE_RIGHT, myThid )
102         CALL PRINT_MESSAGE(messageBuffer,         WRITE(msgBuf,'(A,I4)')  '            NEL1=', iBufr1
103       I      standardMessageUnit,SQUEEZE_RIGHT,         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
104       I      myThid)       I                     SQUEEZE_RIGHT, myThid )
105         WRITE(messageBuffer,'(A,I4)') '            NEL1=', iBufr1         WRITE(msgBuf,'(A,I10)') '            TAG2=', theTag2
106         CALL PRINT_MESSAGE(messageBuffer,         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
107       I      standardMessageUnit,SQUEEZE_RIGHT,       I                     SQUEEZE_RIGHT, myThid )
108       I      myThid)         WRITE(msgBuf,'(A,I4)')  '            NEL2=', iBufr2
109         WRITE(messageBuffer,'(A,I10)') '            TAG2=', theTag2         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
110         CALL PRINT_MESSAGE(messageBuffer,       I                     SQUEEZE_RIGHT, myThid )
      I      standardMessageUnit,SQUEEZE_RIGHT,  
      I      myThid)  
        WRITE(messageBuffer,'(A,I4)') '            NEL2=', iBufr2  
        CALL PRINT_MESSAGE(messageBuffer,  
      I      standardMessageUnit,SQUEEZE_RIGHT,  
      I      myThid)  
111  #endif /* W2_E2_DEBUG_ON */  #endif /* W2_E2_DEBUG_ON */
 C      Set mb to neighbour entry  
 C      Set nt to this tiles rank  
        mb = nN  
 #endif  
       ELSE  
        STOP 'EXCH2_RECV_RX2:: commSetting VALUE IS INVALID'  
112        ENDIF        ENDIF
113    #endif /* ALLOW_USE_MPI */
       iBufr1=0  
       DO ktl=tKlo,tKhi,tkStride  
        DO jtl=tJLo1, tJHi1, tjStride  
         DO itl=tILo1, tIHi1, tiStride  
 C        Read from e2Bufr1_RX(iBufr,mb,nb)  
          iBufr1=iBufr1+1  
          array1(itl,jtl,ktl)=e2Bufr1_RX(iBufr1,mb,nb,ir)  
         ENDDO  
        ENDDO  
       ENDDO  
   
       iBufr2=0  
       DO ktl=tKlo,tKhi,tkStride  
        DO jtl=tJLo2, tJHi2, tjStride  
         DO itl=tILo2, tIHi2, tiStride  
 C        Read from e2Bufr1_RX(iBufr,mb,nb)  
          iBufr2=iBufr2+1  
          array2(itl,jtl,ktl)=e2Bufr2_RX(iBufr2,mb,nb,ir)  
         ENDDO  
        ENDDO  
       ENDDO  
114    
115        RETURN        RETURN
116        END        END

Legend:
Removed from v.1.9  
changed lines
  Added in v.1.10

  ViewVC Help
Powered by ViewVC 1.1.22