/[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.2 by edhill, Mon Apr 5 15:27:06 2004 UTC revision 1.5 by jmc, Tue Jul 29 20:25:23 2008 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
4  #include "CPP_OPTIONS.h"  #include "CPP_EEOPTIONS.h"
5    #include "W2_OPTIONS.h"
6    
7        SUBROUTINE EXCH2_RECV_RX2(        SUBROUTINE EXCH2_RECV_RX2(
8       I       tIlo, tIhi, tiStride,       I       tIlo, tIhi, tiStride,
# Line 20  C $Name$ Line 21  C $Name$
21    
22        IMPLICIT NONE        IMPLICIT NONE
23    
24  C  #include "SIZE.h"
25  #include "W2_OPTIONS.h"  #include "EEPARAMS.h"
26    #include "EESUPPORT.h"
27  #include "W2_EXCH2_TOPOLOGY.h"  #include "W2_EXCH2_TOPOLOGY.h"
28    
 #include "EEPARAMS.h"  
       CHARACTER*(MAX_LEN_MBUF) messageBuffer  
 C  
29  C     === Routine arguments ===  C     === Routine arguments ===
30  C     tIlo, tIhi, tIstride :: index range in I that will be filled in target "array"  C     tIlo, tIhi, tIstride :: index range in I that will be filled in target "array"
31  C     tJlo, tJhi, tJstride :: index range in J that will be filled in target "array"  C     tJlo, tJhi, tJstride :: index range in J that will be filled in target "array"
# Line 58  C                          :: This is do Line 57  C                          :: This is do
57  C     myTiles              :: List of nt tiles that this process owns.  C     myTiles              :: List of nt tiles that this process owns.
58  C     commSetting          :: Mode of communication used to exchnage with this neighbor  C     commSetting          :: Mode of communication used to exchnage with this neighbor
59  C     myThid               :: Thread number of this instance of EXCH2_RECV_RX1  C     myThid               :: Thread number of this instance of EXCH2_RECV_RX1
60  C    C
61        INTEGER tILo, tIHi, tiStride        INTEGER tILo, tIHi, tiStride
62        INTEGER tJLo, tJHi, tjStride        INTEGER tJLo, tJHi, tjStride
63        INTEGER tKLo, tKHi, tkStride        INTEGER tKLo, tKHi, tkStride
64        INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi        INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
65        INTEGER i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi        INTEGER i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi
66        INTEGER thisTile, nN, thisI        INTEGER thisTile, nN, thisI
67        INTEGER e2BufrRecSize        INTEGER e2BufrRecSize
68        INTEGER mnb, nt        INTEGER mnb, nt
69        _RX     e2Bufr1_RX( e2BufrRecSize, mnb, nt, 2 )        _RX     e2Bufr1_RX( e2BufrRecSize, mnb, nt, 2 )
70        _RX     e2Bufr2_RX( e2BufrRecSize, mnb, nt, 2 )        _RX     e2Bufr2_RX( e2BufrRecSize, mnb, nt, 2 )
# Line 83  C                    :: itc etc... targe Line 82  C                    :: itc etc... targe
82  C                    :: isl etc... source local  C                    :: isl etc... source local
83  C                    :: isc etc... source canonical  C                    :: isc etc... source canonical
84        INTEGER itl, jtl, ktl        INTEGER itl, jtl, ktl
85        INTEGER itc, jtc, ktc  c     INTEGER itc, jtc, ktc
86        INTEGER isc, jsc, ksc  c     INTEGER isc, jsc, ksc
87        INTEGER isl, jsl, ksl  c     INTEGER isl, jsl, ksl
88  C     tt         :: Target tile  C     tt         :: Target tile
89  C     iBufr1     :: Buffer counter  C     iBufr1     :: Buffer counter
90  C     iBufr2     ::  C     iBufr2     ::
# Line 94  C     iBufr2     :: Line 93  C     iBufr2     ::
93  C     mb, nb :: Selects e2Bufr, msgHandle record to use  C     mb, nb :: Selects e2Bufr, msgHandle record to use
94  C     ir     ::  C     ir     ::
95        INTEGER mb, nb, ir        INTEGER mb, nb, ir
96  C     oN     :: Opposing send record number  C     oN     :: Opposing send record number
97        INTEGER oN        INTEGER oN
98  C     Loop counters  C     Loop counters
99        INTEGER I, nri1, nrj1, nrk1        INTEGER I
       INTEGER    nri2, nrj2, nrk2  
100        INTEGER itl1reduce, jtl1reduce        INTEGER itl1reduce, jtl1reduce
101        INTEGER itl2reduce, jtl2reduce        INTEGER itl2reduce, jtl2reduce
102    
103  C     MPI setup  C     MPI setup
 #include "SIZE.h"  
 #include "EESUPPORT.h"  
       INTEGER theTag1, theSize1, theType  
       INTEGER theTag2, theSize2  
       INTEGER sProc, tProc  
104  #ifdef ALLOW_USE_MPI  #ifdef ALLOW_USE_MPI
105          INTEGER    nri1, nrj1, nrk1
106          INTEGER    nri2, nrj2, nrk2
107          INTEGER theTag1, theTag2, theType
108    c     INTEGER theSize1, theSize2
109          INTEGER sProc, tProc
110        INTEGER mpiStatus(MPI_STATUS_SIZE), mpiRc        INTEGER mpiStatus(MPI_STATUS_SIZE), mpiRc
111    #ifdef W2_E2_DEBUG_ON
112          CHARACTER*(MAX_LEN_MBUF) messageBuffer
113    #endif
114  #endif  #endif
115    
116        tt=exch2_neighbourId(nN, thisTile )        tt=exch2_neighbourId(nN, thisTile )
117        oN=exch2_opposingSend_record(nN, thisTile )        oN=exch2_opposingSend(nN, thisTile )
118        itl1reduce=0        itl1reduce=0
119        jtl1reduce=0        jtl1reduce=0
120        itl2reduce=0        itl2reduce=0
121        jtl2reduce=0        jtl2reduce=0
122        IF ( exch2_pi(1,oN,tt) .EQ. -1 ) itl1reduce=1        IF ( exch2_pij(1,oN,tt) .EQ. -1 ) itl1reduce=1
123        IF ( exch2_pj(1,oN,tt) .EQ. -1 ) itl1reduce=1        IF ( exch2_pij(3,oN,tt) .EQ. -1 ) itl1reduce=1
124        IF ( exch2_pi(2,oN,tt) .EQ. -1 ) jtl2reduce=1        IF ( exch2_pij(2,oN,tt) .EQ. -1 ) jtl2reduce=1
125        IF ( exch2_pj(2,oN,tt) .EQ. -1 ) jtl2reduce=1        IF ( exch2_pij(4,oN,tt) .EQ. -1 ) jtl2reduce=1
126    
127  C     Handle receive end data transport according to communication mechanism between  C     Handle receive end data transport according to communication mechanism between
128  C     source and target tile  C     source and target tile
129        IF     ( commSetting .EQ. 'P' ) THEN        IF     ( commSetting .EQ. 'P' ) THEN
130  C      1 Need to check and spin on data ready assertion for multithreaded mode, for now do nothing i.e.  C      1 Need to check and spin on data ready assertion for multithreaded mode, for now do nothing i.e.
131  C        assume only one thread per process.  C        assume only one thread per process.
132    
133  C      2 Need to set e2Bufr to use put buffer from opposing send.  C      2 Need to set e2Bufr to use put buffer from opposing send.
134         oN = exch2_opposingSend_record(nN, thisTile )         oN = exch2_opposingSend(nN, thisTile )
135         mb = oN         mb = oN
136         ir = 1         ir = 1
137         DO I=1,nt         DO I=1,nt
# Line 225  C        Read from e2Bufr1_RX(iBufr,mb,n Line 226  C        Read from e2Bufr1_RX(iBufr,mb,n
226          ENDDO          ENDDO
227         ENDDO         ENDDO
228        ENDDO        ENDDO
229    
230        RETURN        RETURN
231        END        END
232    

Legend:
Removed from v.1.2  
changed lines
  Added in v.1.5

  ViewVC Help
Powered by ViewVC 1.1.22