/[MITgcm]/MITgcm/eesupp/src/exch_rx_recv_get_y.template
ViewVC logotype

Contents of /MITgcm/eesupp/src/exch_rx_recv_get_y.template

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


Revision 1.1 - (show annotations) (download)
Tue May 29 14:06:38 2001 UTC (23 years ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint40pre3, checkpoint40pre1, checkpoint40pre7, checkpoint40pre6, checkpoint40pre9, checkpoint40pre8, checkpoint40pre2, checkpoint40pre4, checkpoint40pre5, checkpoint40
Merge from branch pre38 :
 o Templating of exch* routines.

1 C $Header: $
2 C $Name: $
3 #include "CPP_EEOPTIONS.h"
4
5 SUBROUTINE EXCH_RX_RECV_GET_Y( array,
6 I myOLw, myOLe, myOLs, myOLn, myNz,
7 I exchWidthX, exchWidthY,
8 I theSimulationMode, theCornerMode, myThid )
9 C /==========================================================\
10 C | SUBROUTINE RECV_GET_Y |
11 C | o "Send" or "put" Y edges for RX array. |
12 C |==========================================================|
13 C | Routine that invokes actual message passing send or |
14 C | direct "put" of data to update X faces of an XY[R] array.|
15 C \==========================================================/
16 IMPLICIT NONE
17
18 C == Global variables ==
19 #include "SIZE.h"
20 #include "EEPARAMS.h"
21 #include "EESUPPORT.h"
22 #include "EXCH.h"
23
24 C == Routine arguments ==
25 C array - Array with edges to exchange.
26 C myOLw - West, East, North and South overlap region sizes.
27 C myOLe
28 C myOLn
29 C myOLs
30 C exchWidthX - Width of data region exchanged.
31 C exchWidthY
32 C theSimulationMode - Forward or reverse mode exchange ( provides
33 C support for adjoint integration of code. )
34 C theCornerMode - Flag indicating whether corner updates are
35 C needed.
36 C myThid - Thread number of this instance of S/R EXCH...
37 C eBl - Edge buffer level
38 INTEGER myOLw
39 INTEGER myOLe
40 INTEGER myOLs
41 INTEGER myOLn
42 INTEGER myNz
43 _RX array(1-myOLw:sNx+myOLe,
44 & 1-myOLs:sNy+myOLn,
45 & myNZ, nSx, nSy)
46 INTEGER exchWidthX
47 INTEGER exchWidthY
48 INTEGER theSimulationMode
49 INTEGER theCornerMode
50 INTEGER myThid
51 CEndOfInterface
52
53 C == Local variables ==
54 C I, J, K, iMin, iMax, iB - Loop counters and extents
55 C bi, bj
56 C biS, bjS - South tile indices
57 C biN, bjN - North tile indices
58 C eBl - Current exchange buffer level
59 C theProc, theTag, theType, - Variables used in message building
60 C theSize
61 C southCommMode - Working variables holding type
62 C northCommMode of communication a particular
63 C tile face uses.
64 C spinCount - Exchange statistics counter
65 INTEGER I, J, K, iMin, iMax, jMin, jMax, iB, iB0
66 INTEGER bi, bj, biS, bjS, biN, bjN
67 INTEGER eBl
68 INTEGER southCommMode
69 INTEGER northCommMode
70 INTEGER spinCount
71 #ifdef ALLOW_USE_MPI
72 INTEGER theProc, theTag, theType, theSize
73 INTEGER mpiStatus(MPI_STATUS_SIZE,4), mpiRc
74 #endif
75
76
77 C-- Under a "put" scenario we
78 C-- i. set completetion signal for buffer we put into.
79 C-- ii. wait for completetion signal indicating data has been put in
80 C-- our buffer.
81 C-- Under a messaging mode we "receive" the message.
82 C-- Under a "get" scenario we
83 C-- i. Check that the data is ready.
84 C-- ii. Read the data.
85 C-- iii. Set data read flag + memory sync.
86
87
88 DO bj=myByLo(myThid),myByHi(myThid)
89 DO bi=myBxLo(myThid),myBxHi(myThid)
90 ebL = exchangeBufLevel(1,bi,bj)
91 southCommMode = _tileCommModeS(bi,bj)
92 northCommMode = _tileCommModeN(bi,bj)
93 biN = _tileBiN(bi,bj)
94 bjN = _tileBjN(bi,bj)
95 biS = _tileBiS(bi,bj)
96 bjS = _tileBjS(bi,bj)
97 IF ( southCommMode .EQ. COMM_MSG ) THEN
98 #ifdef ALLOW_USE_MPI
99 #ifndef ALWAYS_USE_MPI
100 IF ( usingMPI ) THEN
101 #endif
102 theProc = tilePidS(bi,bj)
103 theTag = _tileTagRecvS(bi,bj)
104 theType = MPI_DOUBLE_PRECISION
105 theSize = sNx*exchWidthY*myNz
106 IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS )
107 & theSize = (sNx+2*exchWidthX)*exchWidthY*myNz
108 CALL MPI_Recv( southRecvBuf_RX(1,eBl,bi,bj), theSize, theType,
109 & theProc, theTag, MPI_COMM_MODEL,
110 & mpiStatus, mpiRc )
111 #ifndef ALWAYS_USE_MPI
112 ENDIF
113 #endif
114 #endif /* ALLOW_USE_MPI */
115 ENDIF
116 IF ( northCommMode .EQ. COMM_MSG ) THEN
117 #ifdef ALLOW_USE_MPI
118 #ifndef ALWAYS_USE_MPI
119 IF ( usingMPI ) THEN
120 #endif
121 theProc = tilePidN(bi,bj)
122 theTag = _tileTagRecvN(bi,bj)
123 theType = MPI_DOUBLE_PRECISION
124 theSize = sNx*exchWidthY*myNz
125 IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS )
126 & theSize = (sNx+2*exchWidthX)*exchWidthY*myNz
127 CALL MPI_Recv( northRecvBuf_RX(1,eBl,bi,bj), theSize, theType,
128 & theProc, theTag, MPI_COMM_MODEL,
129 & mpiStatus, mpiRc )
130 #ifndef ALWAYS_USE_MPI
131 ENDIF
132 #endif
133 #endif /* ALLOW_USE_MPI */
134 ENDIF
135 ENDDO
136 ENDDO
137
138 C-- Wait for buffers I am going read to be ready.
139 IF ( exchUsesBarrier ) THEN
140 C o On some machines ( T90 ) use system barrier rather than spinning.
141 CALL BARRIER( myThid )
142 ELSE
143 C o Spin waiting for completetion flag. This avoids a global-lock
144 C i.e. we only lock waiting for data that we need.
145 DO bj=myByLo(myThid),myByHi(myThid)
146 DO bi=myBxLo(myThid),myBxHi(myThid)
147 ebL = exchangeBufLevel(1,bi,bj)
148 southCommMode = _tileCommModeS(bi,bj)
149 northCommMode = _tileCommModeN(bi,bj)
150 spinCount = 0
151 10 CONTINUE
152 CALL FOOL_THE_COMPILER
153 spinCount = spinCount+1
154 C IF ( myThid .EQ. 1 .AND. spinCount .GT. _EXCH_SPIN_LIMIT ) THEN
155 C STOP ' S/R EXCH_RECV_GET_Y: spinCount .GT. _EXCH_SPIN_LIMIT'
156 C ENDIF
157 IF ( southRecvAck(eBl,bi,bj) .EQ. 0. ) GOTO 10
158 IF ( northRecvAck(eBl,bi,bj) .EQ. 0. ) GOTO 10
159 C Clear requests
160 southRecvAck(eBl,bi,bj) = 0.
161 northRecvAck(eBl,bi,bj) = 0.
162 C Update statistics
163 IF ( exchCollectStatistics ) THEN
164 exchRecvYExchCount(1,bi,bj) = exchRecvYExchCount(1,bi,bj)+1
165 exchRecvYSpinCount(1,bi,bj) =
166 & exchRecvYSpinCount(1,bi,bj)+spinCount
167 exchRecvYSpinMax(1,bi,bj) =
168 & MAX(exchRecvYSpinMax(1,bi,bj),spinCount)
169 exchRecvYSpinMin(1,bi,bj) =
170 & MIN(exchRecvYSpinMin(1,bi,bj),spinCount)
171 ENDIF
172
173
174 IF ( exchNReqsY(1,bi,bj) .GT. 0 ) THEN
175 #ifdef ALLOW_USE_MPI
176 #ifndef ALWAYS_USE_MPI
177 IF ( usingMPI ) THEN
178 #endif
179 CALL MPI_Waitall( exchNReqsY(1,bi,bj), exchReqIdY(1,1,bi,bj),
180 & mpiStatus, mpiRC )
181 #ifndef ALWAYS_USE_MPI
182 ENDIF
183 #endif
184 #endif /* ALLOW_USE_MPI */
185 ENDIF
186 C Clear outstanding requests counter
187 exchNReqsY(1,bi,bj) = 0
188 ENDDO
189 ENDDO
190 ENDIF
191
192 C-- Read from the buffers
193 DO bj=myByLo(myThid),myByHi(myThid)
194 DO bi=myBxLo(myThid),myBxHi(myThid)
195
196 ebL = exchangeBufLevel(1,bi,bj)
197 biN = _tileBiN(bi,bj)
198 bjN = _tileBjN(bi,bj)
199 biS = _tileBiS(bi,bj)
200 bjS = _tileBjS(bi,bj)
201 southCommMode = _tileCommModeS(bi,bj)
202 northCommMode = _tileCommModeN(bi,bj)
203 IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS ) THEN
204 iMin = 1-exchWidthX
205 iMax = sNx+exchWidthX
206 ELSE
207 iMin = 1
208 iMax = sNx
209 ENDIF
210 IF ( _theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
211 jMin = sNy+1
212 jMax = sNy+exchWidthY
213 iB0 = 0
214 IF ( northCommMode .EQ. COMM_PUT
215 & .OR. northCommMode .EQ. COMM_MSG ) THEN
216 iB = 0
217 DO K=1,myNz
218 DO J=jMin,jMax
219 DO I=iMin,iMax
220 iB = iB + 1
221 array(I,J,K,bi,bj) = northRecvBuf_RX(iB,eBl,bi,bj)
222 ENDDO
223 ENDDO
224 ENDDO
225 ELSEIF ( northCommMode .EQ. COMM_GET ) THEN
226 DO K=1,myNz
227 iB = iB0
228 DO J=jMin,jMax
229 iB = iB+1
230 DO I=iMin,iMax
231 array(I,J,K,bi,bj) = array(I,iB,K,biN,bjN)
232 ENDDO
233 ENDDO
234 ENDDO
235 ENDIF
236 ELSEIF ( _theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
237 jMin = sNy-exchWidthY+1
238 jMax = sNy
239 iB0 = 1-exchWidthY-1
240 IF ( northCommMode .EQ. COMM_PUT
241 & .OR. northCommMode .EQ. COMM_MSG ) THEN
242 iB = 0
243 DO K=1,myNz
244 DO J=jMin,jMax
245 DO I=iMin,iMax
246 iB = iB + 1
247 array(I,J,K,bi,bj) =
248 & array(I,J,K,bi,bj)+northRecvBuf_RX(iB,eBl,bi,bj)
249 ENDDO
250 ENDDO
251 ENDDO
252 ELSEIF ( northCommMode .EQ. COMM_GET ) THEN
253 DO K=1,myNz
254 iB = iB0
255 DO J=jMin,jMax
256 iB = iB+1
257 DO I=iMin,iMax
258 array(I,J,K,bi,bj) =
259 & array(I,J,K,bi,bj)+array(I,iB,K,biN,bjN)
260 ENDDO
261 ENDDO
262 ENDDO
263 ENDIF
264 ENDIF
265
266 IF ( _theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
267 jMin = 1-exchWidthY
268 jMax = 0
269 iB0 = sNy-exchWidthY
270 IF ( southCommMode .EQ. COMM_PUT
271 & .OR. southCommMode .EQ. COMM_MSG ) THEN
272 iB = 0
273 DO K=1,myNz
274 DO J=jMin,jMax
275 DO I=iMin,iMax
276 iB = iB + 1
277 array(I,J,K,bi,bj) = southRecvBuf_RX(iB,eBl,bi,bj)
278 ENDDO
279 ENDDO
280 ENDDO
281 ELSEIF ( southCommMode .EQ. COMM_GET ) THEN
282 DO K=1,myNz
283 iB = iB0
284 DO J=jMin,jMax
285 iB = iB+1
286 DO I=iMin,iMax
287 array(I,J,K,bi,bj) = array(I,iB,K,biS,bjS)
288 ENDDO
289 ENDDO
290 ENDDO
291 ENDIF
292 ELSEIF ( _theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
293 jMin = 1
294 jMax = 1+exchWidthY-1
295 iB0 = sNy
296 IF ( southCommMode .EQ. COMM_PUT
297 & .OR. southCommMode .EQ. COMM_MSG ) THEN
298 iB = 0
299 DO K=1,myNz
300 DO J=jMin,jMax
301 DO I=iMin,iMax
302 iB = iB + 1
303 array(I,J,K,bi,bj) =
304 & array(I,J,K,bi,bj)+southRecvBuf_RX(iB,eBl,bi,bj)
305 ENDDO
306 ENDDO
307 ENDDO
308 ELSEIF ( southCommMode .EQ. COMM_GET ) THEN
309 DO K=1,myNz
310 iB = iB0
311 DO J=jMin,jMax
312 iB = iB+1
313 DO I=iMin,iMax
314 array(I,J,K,bi,bj) =
315 & array(I,J,K,bi,bj)+array(I,iB,K,biS,bjS)
316 ENDDO
317 ENDDO
318 ENDDO
319 ENDIF
320 ENDIF
321 ENDDO
322 ENDDO
323
324 RETURN
325 END

  ViewVC Help
Powered by ViewVC 1.1.22