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

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

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


Revision 1.2 - (hide annotations) (download)
Mon Apr 5 15:27:06 2004 UTC (20 years, 2 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint52n_post, checkpoint53d_post, checkpoint54a_pre, checkpoint55c_post, checkpoint54e_post, checkpoint54a_post, checkpoint53c_post, checkpoint57k_post, checkpoint55d_pre, checkpoint57d_post, checkpoint57g_post, checkpoint57b_post, checkpoint57c_pre, checkpoint55j_post, checkpoint56b_post, checkpoint57i_post, checkpoint57e_post, checkpoint55h_post, checkpoint53b_post, checkpoint57g_pre, checkpoint54b_post, checkpoint53b_pre, checkpoint55b_post, checkpoint54d_post, checkpoint56c_post, checkpoint52m_post, checkpoint55, checkpoint53a_post, checkpoint57f_pre, checkpoint57a_post, checkpoint54, checkpoint54f_post, checkpoint55g_post, checkpoint55f_post, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, checkpoint53, eckpoint57e_pre, checkpoint57h_done, checkpoint53g_post, checkpoint57f_post, checkpoint57c_post, checkpoint55e_post, checkpoint53f_post, checkpoint55a_post, checkpoint53d_pre, checkpoint54c_post, checkpoint57j_post, checkpoint57h_pre, checkpoint57l_post, checkpoint57h_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.1: +9 -0 lines
 o fix "make clean"
 o add CVS Header: and Name:

1 edhill 1.2 C $Header: $
2     C $Name: $
3    
4 afe 1.1 #include "CPP_OPTIONS.h"
5    
6     SUBROUTINE EXCH2_RECV_RX2(
7     I tIlo, tIhi, tiStride,
8     I tJlo, tJhi, tjStride,
9     I tKlo, tKhi, tkStride,
10     I thisTile, thisI, nN,
11     I e2Bufr1_RX, e2Bufr2_RX, e2BufrRecSize,
12     I mnb, nt,
13     U array1,
14     I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
15     U array2,
16     I i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,
17     U e2_msgHandles, myTiles,
18     I commSetting,
19     I myThid )
20    
21     IMPLICIT NONE
22    
23     C
24     #include "W2_OPTIONS.h"
25     #include "W2_EXCH2_TOPOLOGY.h"
26    
27     #include "EEPARAMS.h"
28     CHARACTER*(MAX_LEN_MBUF) messageBuffer
29     C
30     C === Routine arguments ===
31     C tIlo, tIhi, tIstride :: index range in I that will be filled in target "array"
32     C tJlo, tJhi, tJstride :: index range in J that will be filled in target "array"
33     C tKlo, tKhi, tKstride :: index range in K that will be filled in target "array"
34     C thisTile :: Rank of the receiveing tile
35     C thisI :: Index of the receiving tile within this process (used
36     C :: to select buffer slots that are allowed).
37     C nN :: Neighbour entry that we are processing
38     C e2Bufr1_RX :: Data transport buffer array. This array is used in one of
39     C :: two ways. For PUT communication the entry in the buffer
40     C :: associated with the source for this receive (determined
41     C :: from the opposing_send index) is read. For MSG communication
42     C :: the entry in the buffer associated with this neighbor of this
43     C :: tile is used as a receive location for loading a linear
44     C :: stream of bytes.
45     C e2BufrRecSize :: Number of elements in each entry of e2Bufr1_RX
46     C mnb :: Second dimension of e2Bufr1_RX
47     C nt :: Third dimension of e2Bufr1_RX
48     C array :: Target array that this receive writes to.
49     C i1Lo, i1Hi :: I coordinate bounds of target array
50     C j1Lo, j1Hi :: J coordinate bounds of target array
51     C k1Lo, k1Hi :: K coordinate bounds of target array
52     C e2_msgHandles :: Synchronization and coordination data structure used to coordinate access
53     C :: to e2Bufr1_RX or to regulate message buffering. In PUT communication
54     C :: sender will increment handle entry once data is ready in buffer.
55     C :: Receiver will decrement handle once data is consumed from buffer. For
56     C :: MPI MSG communication MPI_Wait uses hanlde to check Isend has cleared.
57     C :: This is done in routine after receives.
58     C myTiles :: List of nt tiles that this process owns.
59     C commSetting :: Mode of communication used to exchnage with this neighbor
60     C myThid :: Thread number of this instance of EXCH2_RECV_RX1
61     C
62     INTEGER tILo, tIHi, tiStride
63     INTEGER tJLo, tJHi, tjStride
64     INTEGER tKLo, tKHi, tkStride
65     INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
66     INTEGER i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi
67     INTEGER thisTile, nN, thisI
68     INTEGER e2BufrRecSize
69     INTEGER mnb, nt
70     _RX e2Bufr1_RX( e2BufrRecSize, mnb, nt, 2 )
71     _RX e2Bufr2_RX( e2BufrRecSize, mnb, nt, 2 )
72     _RX array1(i1Lo:i1Hi,j1Lo:j1Hi,k1Lo:k1Hi)
73     _RX array2(i2Lo:i2Hi,j2Lo:j2Hi,k2Lo:k2Hi)
74     INTEGER e2_msgHandles(2, mnb, nt)
75     INTEGER myThid
76     INTEGER myTiles(nt)
77     CHARACTER commSetting
78    
79     C == Local variables ==
80     C itl, jtl, ktl :: Loop counters
81     C :: itl etc... target local
82     C :: itc etc... target canonical
83     C :: isl etc... source local
84     C :: isc etc... source canonical
85     INTEGER itl, jtl, ktl
86     INTEGER itc, jtc, ktc
87     INTEGER isc, jsc, ksc
88     INTEGER isl, jsl, ksl
89     C tt :: Target tile
90     C iBufr1 :: Buffer counter
91     C iBufr2 ::
92     INTEGER tt
93     INTEGER iBufr1, iBufr2
94     C mb, nb :: Selects e2Bufr, msgHandle record to use
95     C ir ::
96     INTEGER mb, nb, ir
97     C oN :: Opposing send record number
98     INTEGER oN
99     C Loop counters
100     INTEGER I, nri1, nrj1, nrk1
101     INTEGER nri2, nrj2, nrk2
102     INTEGER itl1reduce, jtl1reduce
103     INTEGER itl2reduce, jtl2reduce
104    
105     C MPI setup
106     #include "SIZE.h"
107     #include "EESUPPORT.h"
108     INTEGER theTag1, theSize1, theType
109     INTEGER theTag2, theSize2
110     INTEGER sProc, tProc
111     #ifdef ALLOW_USE_MPI
112     INTEGER mpiStatus(MPI_STATUS_SIZE), mpiRc
113     #endif
114    
115     tt=exch2_neighbourId(nN, thisTile )
116     oN=exch2_opposingSend_record(nN, thisTile )
117     itl1reduce=0
118     jtl1reduce=0
119     itl2reduce=0
120     jtl2reduce=0
121     IF ( exch2_pi(1,oN,tt) .EQ. -1 ) itl1reduce=1
122     IF ( exch2_pj(1,oN,tt) .EQ. -1 ) itl1reduce=1
123     IF ( exch2_pi(2,oN,tt) .EQ. -1 ) jtl2reduce=1
124     IF ( exch2_pj(2,oN,tt) .EQ. -1 ) jtl2reduce=1
125    
126     C Handle receive end data transport according to communication mechanism between
127     C source and target tile
128     IF ( commSetting .EQ. 'P' ) THEN
129     C 1 Need to check and spin on data ready assertion for multithreaded mode, for now do nothing i.e.
130     C assume only one thread per process.
131    
132     C 2 Need to set e2Bufr to use put buffer from opposing send.
133     oN = exch2_opposingSend_record(nN, thisTile )
134     mb = oN
135     ir = 1
136     DO I=1,nt
137     IF ( myTiles(I) .EQ. tt ) THEN
138     nb = I
139     ENDIF
140     ENDDO
141     C Get data from e2Bufr(1,mb,nb)
142     ELSEIF ( commSetting .EQ. 'M' ) THEN
143     #ifdef ALLOW_USE_MPI
144     C Setup MPI stuff here
145     nb = thisI
146     mb = nN
147     ir = 2
148     theTag1 = (tt-1)*MAX_NEIGHBOURS*2 + oN-1
149     & + 10000*(
150     & (thisTile-1)*MAX_NEIGHBOURS*2 + oN-1
151     & )
152     theTag2 = (tt-1)*MAX_NEIGHBOURS*2 + MAX_NEIGHBOURS + oN-1
153     & + 10000*(
154     & (thisTile-1)*MAX_NEIGHBOURS*2 + MAX_NEIGHBOURS + oN-1
155     & )
156     tProc = exch2_tProc(thisTile)-1
157     sProc = exch2_tProc(tt)-1
158     theType = MPI_REAL8
159     nri1 = (tIhi-tIlo+1-itl1reduce)/tiStride
160     nrj1 = (tJhi-tJlo+1-jtl1reduce)/tjStride
161     nrk1 = (tKhi-tKlo+1)/tkStride
162     iBufr1 = nri1*nrj1*nrk1
163     nri2 = (tIhi-tIlo+1-itl2reduce)/tiStride
164     nrj2 = (tJhi-tJlo+1-jtl2reduce)/tjStride
165     nrk2 = (tKhi-tKlo+1)/tkStride
166     iBufr2 = nri2*nrj2*nrk2
167     CALL MPI_Recv( e2Bufr1_RX(1,mb,nb,ir), iBufr1, theType, sProc,
168     & theTag1, MPI_COMM_MODEL, mpiStatus, mpiRc )
169     CALL MPI_Recv( e2Bufr2_RX(1,mb,nb,ir), iBufr2, theType, sProc,
170     & theTag2, MPI_COMM_MODEL, mpiStatus, mpiRc )
171     #ifdef W2_E2_DEBUG_ON
172     WRITE(messageBuffer,'(A,I4,A,I4,A)') ' RECV FROM TILE=', tt,
173     & ' (proc = ',sProc,')'
174     CALL PRINT_MESSAGE(messageBuffer,
175     I standardMessageUnit,SQUEEZE_RIGHT,
176     I myThid)
177     WRITE(messageBuffer,'(A,I4,A,I4,A)') ' INTO TILE=', thisTile,
178     & ' (proc = ',tProc,')'
179     CALL PRINT_MESSAGE(messageBuffer,
180     I standardMessageUnit,SQUEEZE_RIGHT,
181     I myThid)
182     WRITE(messageBuffer,'(A,I10)') ' TAG1=', theTag1
183     CALL PRINT_MESSAGE(messageBuffer,
184     I standardMessageUnit,SQUEEZE_RIGHT,
185     I myThid)
186     WRITE(messageBuffer,'(A,I4)') ' NEL1=', iBufr1
187     CALL PRINT_MESSAGE(messageBuffer,
188     I standardMessageUnit,SQUEEZE_RIGHT,
189     I myThid)
190     WRITE(messageBuffer,'(A,I10)') ' TAG2=', theTag2
191     CALL PRINT_MESSAGE(messageBuffer,
192     I standardMessageUnit,SQUEEZE_RIGHT,
193     I myThid)
194     WRITE(messageBuffer,'(A,I4)') ' NEL2=', iBufr2
195     CALL PRINT_MESSAGE(messageBuffer,
196     I standardMessageUnit,SQUEEZE_RIGHT,
197     I myThid)
198     #endif /* W2_E2_DEBUG_ON */
199     C Set mb to neighbour entry
200     C Set nt to this tiles rank
201     mb = nN
202     #endif
203     ELSE
204     STOP 'EXCH2_RECV_RX2:: commSetting VALUE IS INVALID'
205     ENDIF
206    
207     iBufr1=0
208     DO ktl=tKlo,tKhi,tKStride
209     DO jtl=tJLo+jtl1reduce, tJHi, tjStride
210     DO itl=tILo+itl1reduce, tIHi, tiStride
211     C Read from e2Bufr1_RX(iBufr,mb,nb)
212     iBufr1=iBufr1+1
213     array1(itl,jtl,ktl)=e2Bufr1_RX(iBufr1,mb,nb,ir)
214     ENDDO
215     ENDDO
216     ENDDO
217    
218     iBufr2=0
219     DO ktl=tKlo,tKhi,tKStride
220     DO jtl=tJLo+jtl2reduce, tJHi, tjStride
221     DO itl=tILo+itl2reduce, tIHi, tiStride
222     C Read from e2Bufr1_RX(iBufr,mb,nb)
223     iBufr2=iBufr2+1
224     array2(itl,jtl,ktl)=e2Bufr2_RX(iBufr2,mb,nb,ir)
225     ENDDO
226     ENDDO
227     ENDDO
228    
229     RETURN
230     END
231 edhill 1.2
232     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
233    
234     CEH3 ;;; Local Variables: ***
235     CEH3 ;;; mode:fortran ***
236     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22