/[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.13 - (show annotations) (download)
Fri Jan 9 22:51:12 2009 UTC (15 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62c, checkpoint62a, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62, checkpoint62b, checkpoint61n, checkpoint61q, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.12: +4 -4 lines
remove "tabs" from src files

1 C $Header: /u/gcmpack/MITgcm/eesupp/src/exch_rx_recv_get_y.template,v 1.12 2008/07/15 04:00:33 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, pReqI
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 do not 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_AMPI
161 CALL MPI_Recv( southRecvBuf_RX(1,eBl,bi,bj), theSize, theType,
162 & theProc, theTag, MPI_COMM_MODEL,
163 & mpiStatus, mpiRc )
164 # else
165 pReqI=exchNReqsY(1,bi,bj)+1
166 CALL ampi_recv_RX(
167 & southRecvBuf_RX(1,eBl,bi,bj) ,
168 & theSize ,
169 & theType ,
170 & theProc ,
171 & theTag ,
172 & MPI_COMM_MODEL ,
173 & exchReqIdY(pReqI,1,bi,bj),
174 & exchNReqsY(1,bi,bj),
175 & mpiStatus ,
176 & mpiRc )
177 # endif /* ALLOW_AUTODIFF_OPENAD_AMPI */
178 #ifndef ALWAYS_USE_MPI
179 ENDIF
180 #endif
181 #endif /* ALLOW_USE_MPI */
182 ENDIF
183 IF ( northCommMode .EQ. COMM_MSG ) THEN
184 #ifdef ALLOW_USE_MPI
185 #ifndef ALWAYS_USE_MPI
186 IF ( usingMPI ) THEN
187 #endif
188 theProc = tilePidN(bi,bj)
189 theTag = _tileTagRecvN(bi,bj)
190 theType = _MPI_TYPE_RX
191 theSize = sNx*exchWidthY*myNz
192 IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS )
193 & theSize = (sNx+2*exchWidthX)*exchWidthY*myNz
194 # ifndef ALLOW_AUTODIFF_OPENAD_AMPI
195 CALL MPI_Recv( northRecvBuf_RX(1,eBl,bi,bj), theSize, theType,
196 & theProc, theTag, MPI_COMM_MODEL,
197 & mpiStatus, mpiRc )
198 # else
199 pReqI=exchNReqsY(1,bi,bj)+1
200 CALL ampi_recv_RX(
201 & northRecvBuf_RX(1,eBl,bi,bj) ,
202 & theSize ,
203 & theType ,
204 & theProc ,
205 & theTag ,
206 & MPI_COMM_MODEL ,
207 & exchReqIdY(pReqI,1,bi,bj),
208 & exchNReqsY(1,bi,bj),
209 & mpiStatus ,
210 & mpiRc )
211 # endif /* ALLOW_AUTODIFF_OPENAD_AMPI */
212 #ifndef ALWAYS_USE_MPI
213 ENDIF
214 #endif
215 #endif /* ALLOW_USE_MPI */
216 ENDIF
217 ENDDO
218 ENDDO
219
220 C-- Wait for buffers I am going read to be ready.
221 IF ( exchUsesBarrier ) THEN
222 C o On some machines ( T90 ) use system barrier rather than spinning.
223 CALL BARRIER( myThid )
224 ELSE
225 C o Spin waiting for completetion flag. This avoids a global-lock
226 C i.e. we only lock waiting for data that we need.
227 DO bj=myByLo(myThid),myByHi(myThid)
228 DO bi=myBxLo(myThid),myBxHi(myThid)
229 ebL = exchangeBufLevel(1,bi,bj)
230 southCommMode = _tileCommModeS(bi,bj)
231 northCommMode = _tileCommModeN(bi,bj)
232 spinCount = 0
233 # ifndef ALLOW_AUTODIFF_OPENAD_AMPI
234 10 CONTINUE
235 CALL FOOL_THE_COMPILER( spinCount )
236 spinCount = spinCount+1
237 C IF ( myThid .EQ. 1 .AND. spinCount .GT. _EXCH_SPIN_LIMIT ) THEN
238 C STOP ' S/R EXCH_RECV_GET_Y: spinCount .GT. _EXCH_SPIN_LIMIT'
239 C ENDIF
240 IF ( southRecvAck(eBl,bi,bj) .EQ. 0 ) GOTO 10
241 IF ( northRecvAck(eBl,bi,bj) .EQ. 0 ) GOTO 10
242 # else
243 do while ((southRecvAck(eBl,bi,bj) .EQ. 0.
244 & .or.
245 & northRecvAck(eBl,bi,bj) .EQ. 0. ))
246 CALL FOOL_THE_COMPILER( spinCount )
247 spinCount = spinCount+1
248 end do
249 # endif /* ALLOW_AUTODIFF_OPENAD_AMPI */
250 C Clear requests
251 southRecvAck(eBl,bi,bj) = 0
252 northRecvAck(eBl,bi,bj) = 0
253 C Update statistics
254 IF ( exchCollectStatistics ) THEN
255 exchRecvYExchCount(1,bi,bj) = exchRecvYExchCount(1,bi,bj)+1
256 exchRecvYSpinCount(1,bi,bj) =
257 & exchRecvYSpinCount(1,bi,bj)+spinCount
258 exchRecvYSpinMax(1,bi,bj) =
259 & MAX(exchRecvYSpinMax(1,bi,bj),spinCount)
260 exchRecvYSpinMin(1,bi,bj) =
261 & MIN(exchRecvYSpinMin(1,bi,bj),spinCount)
262 ENDIF
263
264
265 IF ( exchNReqsY(1,bi,bj) .GT. 0 ) THEN
266 #ifdef ALLOW_USE_MPI
267 #ifndef ALWAYS_USE_MPI
268 IF ( usingMPI ) THEN
269 #endif
270 # ifndef ALLOW_AUTODIFF_OPENAD_AMPI
271 CALL MPI_Waitall( exchNReqsY(1,bi,bj), exchReqIdY(1,1,bi,bj),
272 & mpiStatus, mpiRC )
273 # else
274 CALL ampi_waitall(
275 & exchNReqsY(1,bi,bj),
276 & exchReqIdY(1,1,bi,bj),
277 & mpiStatus,
278 & mpiRC )
279 # endif /* ALLOW_AUTODIFF_OPENAD_AMPI */
280 #ifndef ALWAYS_USE_MPI
281 ENDIF
282 #endif
283 #endif /* ALLOW_USE_MPI */
284 ENDIF
285 C Clear outstanding requests counter
286 exchNReqsY(1,bi,bj) = 0
287 ENDDO
288 ENDDO
289 ENDIF
290
291 C-- Read from the buffers
292 DO bj=myByLo(myThid),myByHi(myThid)
293 DO bi=myBxLo(myThid),myBxHi(myThid)
294
295 ebL = exchangeBufLevel(1,bi,bj)
296 biN = _tileBiN(bi,bj)
297 bjN = _tileBjN(bi,bj)
298 biS = _tileBiS(bi,bj)
299 bjS = _tileBjS(bi,bj)
300 southCommMode = _tileCommModeS(bi,bj)
301 northCommMode = _tileCommModeN(bi,bj)
302 IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS ) THEN
303 iMin = 1-exchWidthX
304 iMax = sNx+exchWidthX
305 ELSE
306 iMin = 1
307 iMax = sNx
308 ENDIF
309 IF ( _theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
310 jMin = sNy+1
311 jMax = sNy+exchWidthY
312 iB0 = 0
313 IF ( northCommMode .EQ. COMM_PUT
314 & .OR. northCommMode .EQ. COMM_MSG ) THEN
315 iB = 0
316 DO K=1,myNz
317 DO J=jMin,jMax
318 DO I=iMin,iMax
319 iB = iB + 1
320 array(I,J,K,bi,bj) = northRecvBuf_RX(iB,eBl,bi,bj)
321 ENDDO
322 ENDDO
323 ENDDO
324 ELSEIF ( northCommMode .EQ. COMM_GET ) THEN
325 DO K=1,myNz
326 iB = iB0
327 DO J=jMin,jMax
328 iB = iB+1
329 DO I=iMin,iMax
330 array(I,J,K,bi,bj) = array(I,iB,K,biN,bjN)
331 ENDDO
332 ENDDO
333 ENDDO
334 ENDIF
335 ELSEIF ( _theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
336 jMin = sNy-exchWidthY+1
337 jMax = sNy
338 iB0 = 1-exchWidthY-1
339 IF ( northCommMode .EQ. COMM_PUT
340 & .OR. northCommMode .EQ. COMM_MSG ) THEN
341 iB = 0
342 DO K=1,myNz
343 DO J=jMin,jMax
344 DO I=iMin,iMax
345 iB = iB + 1
346 array(I,J,K,bi,bj) =
347 & array(I,J,K,bi,bj)+northRecvBuf_RX(iB,eBl,bi,bj)
348 ENDDO
349 ENDDO
350 ENDDO
351 ELSEIF ( northCommMode .EQ. COMM_GET ) THEN
352 DO K=1,myNz
353 iB = iB0
354 DO J=jMin,jMax
355 iB = iB+1
356 DO I=iMin,iMax
357 array(I,J,K,bi,bj) =
358 & array(I,J,K,bi,bj)+array(I,iB,K,biN,bjN)
359 ENDDO
360 ENDDO
361 ENDDO
362 ENDIF
363 ENDIF
364
365 IF ( _theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
366 jMin = 1-exchWidthY
367 jMax = 0
368 iB0 = sNy-exchWidthY
369 IF ( southCommMode .EQ. COMM_PUT
370 & .OR. southCommMode .EQ. COMM_MSG ) THEN
371 iB = 0
372 DO K=1,myNz
373 DO J=jMin,jMax
374 DO I=iMin,iMax
375 iB = iB + 1
376 array(I,J,K,bi,bj) = southRecvBuf_RX(iB,eBl,bi,bj)
377 ENDDO
378 ENDDO
379 ENDDO
380 ELSEIF ( southCommMode .EQ. COMM_GET ) THEN
381 DO K=1,myNz
382 iB = iB0
383 DO J=jMin,jMax
384 iB = iB+1
385 DO I=iMin,iMax
386 array(I,J,K,bi,bj) = array(I,iB,K,biS,bjS)
387 ENDDO
388 ENDDO
389 ENDDO
390 ENDIF
391 ELSEIF ( _theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
392 jMin = 1
393 jMax = 1+exchWidthY-1
394 iB0 = sNy
395 IF ( southCommMode .EQ. COMM_PUT
396 & .OR. southCommMode .EQ. COMM_MSG ) THEN
397 iB = 0
398 DO K=1,myNz
399 DO J=jMin,jMax
400 DO I=iMin,iMax
401 iB = iB + 1
402 array(I,J,K,bi,bj) =
403 & array(I,J,K,bi,bj)+southRecvBuf_RX(iB,eBl,bi,bj)
404 ENDDO
405 ENDDO
406 ENDDO
407 ELSEIF ( southCommMode .EQ. COMM_GET ) THEN
408 DO K=1,myNz
409 iB = iB0
410 DO J=jMin,jMax
411 iB = iB+1
412 DO I=iMin,iMax
413 array(I,J,K,bi,bj) =
414 & array(I,J,K,bi,bj)+array(I,iB,K,biS,bjS)
415 ENDDO
416 ENDDO
417 ENDDO
418 ENDIF
419 ENDIF
420 ENDDO
421 ENDDO
422
423 _BARRIER
424 IF ( doingSingleThreadedComms ) THEN
425 C Restore saved settings that were stored to allow
426 C single thred comms.
427 _BEGIN_MASTER(myThid)
428 DO I=1,nThreads
429 myBxLo(I) = myBxLoSave(I)
430 myBxHi(I) = myBxHiSave(I)
431 myByLo(I) = myByLoSave(I)
432 myByHi(I) = myByHiSave(I)
433 ENDDO
434 _END_MASTER(myThid)
435 ENDIF
436 _BARRIER
437
438 RETURN
439 END

  ViewVC Help
Powered by ViewVC 1.1.22