/[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.10 - (show annotations) (download)
Fri Mar 28 18:39:54 2008 UTC (16 years, 2 months ago) by utke
Branch: MAIN
Changes since 1.9: +5 -1 lines
handle request book keeping within the wrapper

1 C $Header: /u/gcmpack/MITgcm/eesupp/src/exch_rx_recv_get_y.template,v 1.9 2008/03/18 21:34:01 utke Exp $
2 C $Name: $
3 #include "CPP_EEOPTIONS.h"
4
5 CBOP
6 C !ROUTINE: EXCH_RX_RECV_GET_Y
7
8 C !INTERFACE:
9 SUBROUTINE EXCH_RX_RECV_GET_Y( array,
10 I myOLw, myOLe, myOLs, myOLn, myNz,
11 I exchWidthX, exchWidthY,
12 I theSimulationMode, theCornerMode, myThid )
13 IMPLICIT NONE
14
15 C !DESCRIPTION:
16 C *==========================================================*
17 C | SUBROUTINE RECV_GET_Y
18 C | o "Send" or "put" Y edges for RX array.
19 C *==========================================================*
20 C | Routine that invokes actual message passing send or
21 C | direct "put" of data to update X faces of an XY[R] array.
22 C *==========================================================*
23
24 C !USES:
25 C == Global variables ==
26 #include "SIZE.h"
27 #include "EEPARAMS.h"
28 #include "EESUPPORT.h"
29 #include "EXCH.h"
30
31 C !INPUT/OUTPUT PARAMETERS:
32 C == Routine arguments ==
33 C array :: Array with edges to exchange.
34 C myOLw :: West, East, North and South overlap region sizes.
35 C myOLe
36 C myOLn
37 C myOLs
38 C exchWidthX :: Width of data region exchanged.
39 C exchWidthY
40 C theSimulationMode :: Forward or reverse mode exchange ( provides
41 C support for adjoint integration of code. )
42 C theCornerMode :: Flag indicating whether corner updates are
43 C needed.
44 C myThid :: Thread number of this instance of S/R EXCH...
45 C eBl :: Edge buffer level
46 INTEGER myOLw
47 INTEGER myOLe
48 INTEGER myOLs
49 INTEGER myOLn
50 INTEGER myNz
51 _RX array(1-myOLw:sNx+myOLe,
52 & 1-myOLs:sNy+myOLn,
53 & myNZ, nSx, nSy)
54 INTEGER exchWidthX
55 INTEGER exchWidthY
56 INTEGER theSimulationMode
57 INTEGER theCornerMode
58 INTEGER myThid
59
60 C !LOCAL VARIABLES:
61 C == Local variables ==
62 C I, J, K, iMin, iMax, iB :: Loop counters and extents
63 C bi, bj
64 C biS, bjS :: South tile indices
65 C biN, bjN :: North tile indices
66 C eBl :: Current exchange buffer level
67 C theProc, theTag, theType, :: Variables used in message building
68 C theSize
69 C southCommMode :: Working variables holding type
70 C northCommMode of communication a particular
71 C tile face uses.
72 C spinCount :: Exchange statistics counter
73 C mpiStatus :: MPI error code
74 INTEGER I, J, K, iMin, iMax, jMin, jMax, iB, iB0
75 INTEGER bi, bj, biS, bjS, biN, bjN
76 INTEGER eBl
77 INTEGER southCommMode
78 INTEGER northCommMode
79 INTEGER spinCount
80 #ifdef ALLOW_USE_MPI
81 INTEGER theProc, theTag, theType, theSize
82 INTEGER mpiStatus(MPI_STATUS_SIZE,4), mpiRc
83 #endif
84 CEOP
85
86 INTEGER myBxLoSave(MAX_NO_THREADS)
87 INTEGER myBxHiSave(MAX_NO_THREADS)
88 INTEGER myByLoSave(MAX_NO_THREADS)
89 INTEGER myByHiSave(MAX_NO_THREADS)
90 LOGICAL doingSingleThreadedComms
91
92 doingSingleThreadedComms = .FALSE.
93 #ifdef ALLOW_USE_MPI
94 #ifndef ALWAYS_USE_MPI
95 IF ( usingMPI ) THEN
96 #endif
97 C Set default behavior to have MPI comms done by a single thread.
98 C Most MPI implementations don't support concurrent comms from
99 C several threads.
100 IF ( nThreads .GT. 1 ) THEN
101 _BARRIER
102 _BEGIN_MASTER( myThid )
103 DO I=1,nThreads
104 myBxLoSave(I) = myBxLo(I)
105 myBxHiSave(I) = myBxHi(I)
106 myByLoSave(I) = myByLo(I)
107 myByHiSave(I) = myByHi(I)
108 ENDDO
109 C Comment out loop below and myB[xy][Lo|Hi](1) settings below
110 C if you want to get multi-threaded MPI comms.
111 DO I=1,nThreads
112 myBxLo(I) = 0
113 myBxHi(I) = -1
114 myByLo(I) = 0
115 myByHi(I) = -1
116 ENDDO
117 myBxLo(1) = 1
118 myBxHi(1) = nSx
119 myByLo(1) = 1
120 myByHi(1) = nSy
121 doingSingleThreadedComms = .TRUE.
122 _END_MASTER( myThid )
123 _BARRIER
124 ENDIF
125 #ifndef ALWAYS_USE_MPI
126 ENDIF
127 #endif
128 #endif
129 C-- Under a "put" scenario we
130 C-- i. set completetion signal for buffer we put into.
131 C-- ii. wait for completetion signal indicating data has been put in
132 C-- our buffer.
133 C-- Under a messaging mode we "receive" the message.
134 C-- Under a "get" scenario we
135 C-- i. Check that the data is ready.
136 C-- ii. Read the data.
137 C-- iii. Set data read flag + memory sync.
138
139
140 DO bj=myByLo(myThid),myByHi(myThid)
141 DO bi=myBxLo(myThid),myBxHi(myThid)
142 ebL = exchangeBufLevel(1,bi,bj)
143 southCommMode = _tileCommModeS(bi,bj)
144 northCommMode = _tileCommModeN(bi,bj)
145 biN = _tileBiN(bi,bj)
146 bjN = _tileBjN(bi,bj)
147 biS = _tileBiS(bi,bj)
148 bjS = _tileBjS(bi,bj)
149 IF ( southCommMode .EQ. COMM_MSG ) THEN
150 #ifdef ALLOW_USE_MPI
151 #ifndef ALWAYS_USE_MPI
152 IF ( usingMPI ) THEN
153 #endif
154 theProc = tilePidS(bi,bj)
155 theTag = _tileTagRecvS(bi,bj)
156 theType = _MPI_TYPE_RX
157 theSize = sNx*exchWidthY*myNz
158 IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS )
159 & theSize = (sNx+2*exchWidthX)*exchWidthY*myNz
160 # ifndef ALLOW_AUTODIFF_OPENAD
161 CALL MPI_Recv( southRecvBuf_RX(1,eBl,bi,bj), theSize, theType,
162 & theProc, theTag, MPI_COMM_MODEL,
163 & mpiStatus, mpiRc )
164 # else
165 CALL ampi_recv_RX(
166 & southRecvBuf_RX(1,eBl,bi,bj) ,
167 & theSize ,
168 & theType ,
169 & theProc ,
170 & theTag ,
171 & MPI_COMM_MODEL ,
172 & exchReqIdY(exchNReqsY(1,bi,bj)+1,1,bi,bj),
173 & exchNReqsY(1,bi,bj),
174 & mpiStatus ,
175 & mpiRc )
176 # endif /* ALLOW_AUTODIFF_OPENAD */
177 #ifndef ALWAYS_USE_MPI
178 ENDIF
179 #endif
180 #endif /* ALLOW_USE_MPI */
181 ENDIF
182 IF ( northCommMode .EQ. COMM_MSG ) THEN
183 #ifdef ALLOW_USE_MPI
184 #ifndef ALWAYS_USE_MPI
185 IF ( usingMPI ) THEN
186 #endif
187 theProc = tilePidN(bi,bj)
188 theTag = _tileTagRecvN(bi,bj)
189 theType = _MPI_TYPE_RX
190 theSize = sNx*exchWidthY*myNz
191 IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS )
192 & theSize = (sNx+2*exchWidthX)*exchWidthY*myNz
193 # ifndef ALLOW_AUTODIFF_OPENAD
194 CALL MPI_Recv( northRecvBuf_RX(1,eBl,bi,bj), theSize, theType,
195 & theProc, theTag, MPI_COMM_MODEL,
196 & mpiStatus, mpiRc )
197 # else
198 CALL ampi_recv_RX(
199 & northRecvBuf_RX(1,eBl,bi,bj) ,
200 & theSize ,
201 & theType ,
202 & theProc ,
203 & theTag ,
204 & MPI_COMM_MODEL ,
205 & exchReqIdY(exchNReqsY(1,bi,bj)+1,1,bi,bj),
206 & exchNReqsY(1,bi,bj),
207 & mpiStatus ,
208 & mpiRc )
209 # endif /* ALLOW_AUTODIFF_OPENAD */
210 #ifndef ALWAYS_USE_MPI
211 ENDIF
212 #endif
213 #endif /* ALLOW_USE_MPI */
214 ENDIF
215 ENDDO
216 ENDDO
217
218 C-- Wait for buffers I am going read to be ready.
219 IF ( exchUsesBarrier ) THEN
220 C o On some machines ( T90 ) use system barrier rather than spinning.
221 CALL BARRIER( myThid )
222 ELSE
223 C o Spin waiting for completetion flag. This avoids a global-lock
224 C i.e. we only lock waiting for data that we need.
225 DO bj=myByLo(myThid),myByHi(myThid)
226 DO bi=myBxLo(myThid),myBxHi(myThid)
227 ebL = exchangeBufLevel(1,bi,bj)
228 southCommMode = _tileCommModeS(bi,bj)
229 northCommMode = _tileCommModeN(bi,bj)
230 spinCount = 0
231 # ifndef ALLOW_AUTODIFF_OPENAD
232 10 CONTINUE
233 CALL FOOL_THE_COMPILER( spinCount )
234 spinCount = spinCount+1
235 C IF ( myThid .EQ. 1 .AND. spinCount .GT. _EXCH_SPIN_LIMIT ) THEN
236 C STOP ' S/R EXCH_RECV_GET_Y: spinCount .GT. _EXCH_SPIN_LIMIT'
237 C ENDIF
238 IF ( southRecvAck(eBl,bi,bj) .EQ. 0 ) GOTO 10
239 IF ( northRecvAck(eBl,bi,bj) .EQ. 0 ) GOTO 10
240 # else
241 do while ((southRecvAck(eBl,bi,bj) .EQ. 0.
242 & .or.
243 & northRecvAck(eBl,bi,bj) .EQ. 0. ))
244 CALL FOOL_THE_COMPILER( spinCount )
245 spinCount = spinCount+1
246 end do
247 # endif /* ALLOW_AUTODIFF_OPENAD */
248 C Clear requests
249 southRecvAck(eBl,bi,bj) = 0
250 northRecvAck(eBl,bi,bj) = 0
251 C Update statistics
252 IF ( exchCollectStatistics ) THEN
253 exchRecvYExchCount(1,bi,bj) = exchRecvYExchCount(1,bi,bj)+1
254 exchRecvYSpinCount(1,bi,bj) =
255 & exchRecvYSpinCount(1,bi,bj)+spinCount
256 exchRecvYSpinMax(1,bi,bj) =
257 & MAX(exchRecvYSpinMax(1,bi,bj),spinCount)
258 exchRecvYSpinMin(1,bi,bj) =
259 & MIN(exchRecvYSpinMin(1,bi,bj),spinCount)
260 ENDIF
261
262
263 IF ( exchNReqsY(1,bi,bj) .GT. 0 ) THEN
264 #ifdef ALLOW_USE_MPI
265 #ifndef ALWAYS_USE_MPI
266 IF ( usingMPI ) THEN
267 #endif
268 CALL MPI_Waitall( exchNReqsY(1,bi,bj), exchReqIdY(1,1,bi,bj),
269 & mpiStatus, mpiRC )
270 #ifndef ALWAYS_USE_MPI
271 ENDIF
272 #endif
273 #endif /* ALLOW_USE_MPI */
274 ENDIF
275 C Clear outstanding requests counter
276 exchNReqsY(1,bi,bj) = 0
277 ENDDO
278 ENDDO
279 ENDIF
280
281 C-- Read from the buffers
282 DO bj=myByLo(myThid),myByHi(myThid)
283 DO bi=myBxLo(myThid),myBxHi(myThid)
284
285 ebL = exchangeBufLevel(1,bi,bj)
286 biN = _tileBiN(bi,bj)
287 bjN = _tileBjN(bi,bj)
288 biS = _tileBiS(bi,bj)
289 bjS = _tileBjS(bi,bj)
290 southCommMode = _tileCommModeS(bi,bj)
291 northCommMode = _tileCommModeN(bi,bj)
292 IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS ) THEN
293 iMin = 1-exchWidthX
294 iMax = sNx+exchWidthX
295 ELSE
296 iMin = 1
297 iMax = sNx
298 ENDIF
299 IF ( _theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
300 jMin = sNy+1
301 jMax = sNy+exchWidthY
302 iB0 = 0
303 IF ( northCommMode .EQ. COMM_PUT
304 & .OR. northCommMode .EQ. COMM_MSG ) THEN
305 iB = 0
306 DO K=1,myNz
307 DO J=jMin,jMax
308 DO I=iMin,iMax
309 iB = iB + 1
310 array(I,J,K,bi,bj) = northRecvBuf_RX(iB,eBl,bi,bj)
311 ENDDO
312 ENDDO
313 ENDDO
314 ELSEIF ( northCommMode .EQ. COMM_GET ) THEN
315 DO K=1,myNz
316 iB = iB0
317 DO J=jMin,jMax
318 iB = iB+1
319 DO I=iMin,iMax
320 array(I,J,K,bi,bj) = array(I,iB,K,biN,bjN)
321 ENDDO
322 ENDDO
323 ENDDO
324 ENDIF
325 ELSEIF ( _theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
326 jMin = sNy-exchWidthY+1
327 jMax = sNy
328 iB0 = 1-exchWidthY-1
329 IF ( northCommMode .EQ. COMM_PUT
330 & .OR. northCommMode .EQ. COMM_MSG ) THEN
331 iB = 0
332 DO K=1,myNz
333 DO J=jMin,jMax
334 DO I=iMin,iMax
335 iB = iB + 1
336 array(I,J,K,bi,bj) =
337 & array(I,J,K,bi,bj)+northRecvBuf_RX(iB,eBl,bi,bj)
338 ENDDO
339 ENDDO
340 ENDDO
341 ELSEIF ( northCommMode .EQ. COMM_GET ) THEN
342 DO K=1,myNz
343 iB = iB0
344 DO J=jMin,jMax
345 iB = iB+1
346 DO I=iMin,iMax
347 array(I,J,K,bi,bj) =
348 & array(I,J,K,bi,bj)+array(I,iB,K,biN,bjN)
349 ENDDO
350 ENDDO
351 ENDDO
352 ENDIF
353 ENDIF
354
355 IF ( _theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
356 jMin = 1-exchWidthY
357 jMax = 0
358 iB0 = sNy-exchWidthY
359 IF ( southCommMode .EQ. COMM_PUT
360 & .OR. southCommMode .EQ. COMM_MSG ) THEN
361 iB = 0
362 DO K=1,myNz
363 DO J=jMin,jMax
364 DO I=iMin,iMax
365 iB = iB + 1
366 array(I,J,K,bi,bj) = southRecvBuf_RX(iB,eBl,bi,bj)
367 ENDDO
368 ENDDO
369 ENDDO
370 ELSEIF ( southCommMode .EQ. COMM_GET ) THEN
371 DO K=1,myNz
372 iB = iB0
373 DO J=jMin,jMax
374 iB = iB+1
375 DO I=iMin,iMax
376 array(I,J,K,bi,bj) = array(I,iB,K,biS,bjS)
377 ENDDO
378 ENDDO
379 ENDDO
380 ENDIF
381 ELSEIF ( _theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
382 jMin = 1
383 jMax = 1+exchWidthY-1
384 iB0 = sNy
385 IF ( southCommMode .EQ. COMM_PUT
386 & .OR. southCommMode .EQ. COMM_MSG ) THEN
387 iB = 0
388 DO K=1,myNz
389 DO J=jMin,jMax
390 DO I=iMin,iMax
391 iB = iB + 1
392 array(I,J,K,bi,bj) =
393 & array(I,J,K,bi,bj)+southRecvBuf_RX(iB,eBl,bi,bj)
394 ENDDO
395 ENDDO
396 ENDDO
397 ELSEIF ( southCommMode .EQ. COMM_GET ) THEN
398 DO K=1,myNz
399 iB = iB0
400 DO J=jMin,jMax
401 iB = iB+1
402 DO I=iMin,iMax
403 array(I,J,K,bi,bj) =
404 & array(I,J,K,bi,bj)+array(I,iB,K,biS,bjS)
405 ENDDO
406 ENDDO
407 ENDDO
408 ENDIF
409 ENDIF
410 ENDDO
411 ENDDO
412
413 _BARRIER
414 IF ( doingSingleThreadedComms ) THEN
415 C Restore saved settings that were stored to allow
416 C single thred comms.
417 _BEGIN_MASTER(myThid)
418 DO I=1,nThreads
419 myBxLo(I) = myBxLoSave(I)
420 myBxHi(I) = myBxHiSave(I)
421 myByLo(I) = myByLoSave(I)
422 myByHi(I) = myByHiSave(I)
423 ENDDO
424 _END_MASTER(myThid)
425 ENDIF
426 _BARRIER
427
428 RETURN
429 END

  ViewVC Help
Powered by ViewVC 1.1.22