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

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

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


Revision 1.1 - (show annotations) (download)
Fri Jan 9 20:46:09 2004 UTC (20 years, 5 months ago) by afe
Branch: MAIN
CVS Tags: checkpoint52l_pre, hrcube4, checkpoint52j_post, checkpoint52l_post, checkpoint52k_post, checkpoint52f_post, hrcube5, checkpoint52i_post, checkpoint52j_pre, checkpoint52i_pre, checkpoint52h_pre, hrcube_2, hrcube_3
Added exch2 routines and pointed hs94.cs-32x32x5 at them

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

  ViewVC Help
Powered by ViewVC 1.1.22