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

Contents of /MITgcm/eesupp/src/exch_rx_recv_get_x.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_x.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_X
7
8 C !INTERFACE:
9 SUBROUTINE EXCH_RX_RECV_GET_X( 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_RX_GET_X
18 C | o "Send" or "put" X 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 biW, bjW :: West tile indices
65 C biE, bjE :: East tile indices
66 C eBl :: Current exchange buffer level
67 C theProc, theTag, theType, :: Variables used in message building
68 C theSize
69 C westCommMode :: Working variables holding type
70 C eastCommMode of communication a particular
71 C tile face uses.
72 INTEGER I, J, K, iMin, iMax, iB, iB0
73 INTEGER bi, bj, biW, bjW, biE, bjE
74 INTEGER eBl
75 INTEGER westCommMode
76 INTEGER eastCommMode
77 INTEGER spinCount
78 #ifdef ALLOW_USE_MPI
79 INTEGER theProc, theTag, theType, theSize
80 INTEGER mpiStatus(MPI_STATUS_SIZE,4), mpiRc
81 #endif
82 CEOP
83
84 INTEGER myBxLoSave(MAX_NO_THREADS)
85 INTEGER myBxHiSave(MAX_NO_THREADS)
86 INTEGER myByLoSave(MAX_NO_THREADS)
87 INTEGER myByHiSave(MAX_NO_THREADS)
88 LOGICAL doingSingleThreadedComms
89
90 doingSingleThreadedComms = .FALSE.
91 #ifdef ALLOW_USE_MPI
92 #ifndef ALWAYS_USE_MPI
93 IF ( usingMPI ) THEN
94 #endif
95 C Set default behavior to have MPI comms done by a single thread.
96 C Most MPI implementations don't support concurrent comms from
97 C several threads.
98 IF ( nThreads .GT. 1 ) THEN
99 _BARRIER
100 _BEGIN_MASTER( myThid )
101 DO I=1,nThreads
102 myBxLoSave(I) = myBxLo(I)
103 myBxHiSave(I) = myBxHi(I)
104 myByLoSave(I) = myByLo(I)
105 myByHiSave(I) = myByHi(I)
106 ENDDO
107 C Comment out loop below and myB[xy][Lo|Hi](1) settings below
108 C if you want to get multi-threaded MPI comms.
109 DO I=1,nThreads
110 myBxLo(I) = 0
111 myBxHi(I) = -1
112 myByLo(I) = 0
113 myByHi(I) = -1
114 ENDDO
115 myBxLo(1) = 1
116 myBxHi(1) = nSx
117 myByLo(1) = 1
118 myByHi(1) = nSy
119 doingSingleThreadedComms = .TRUE.
120 _END_MASTER( myThid )
121 _BARRIER
122 ENDIF
123 #ifndef ALWAYS_USE_MPI
124 ENDIF
125 #endif
126 #endif
127
128 C-- Under a "put" scenario we
129 C-- i. set completetion signal for buffer we put into.
130 C-- ii. wait for completetion signal indicating data has been put in
131 C-- our buffer.
132 C-- Under a messaging mode we "receive" the message.
133 C-- Under a "get" scenario we
134 C-- i. Check that the data is ready.
135 C-- ii. Read the data.
136 C-- iii. Set data read flag + memory sync.
137
138
139 DO bj=myByLo(myThid),myByHi(myThid)
140 DO bi=myBxLo(myThid),myBxHi(myThid)
141 ebL = exchangeBufLevel(1,bi,bj)
142 westCommMode = _tileCommModeW(bi,bj)
143 eastCommMode = _tileCommModeE(bi,bj)
144 biE = _tileBiE(bi,bj)
145 bjE = _tileBjE(bi,bj)
146 biW = _tileBiW(bi,bj)
147 bjW = _tileBjW(bi,bj)
148 IF ( westCommMode .EQ. COMM_MSG ) THEN
149 #ifdef ALLOW_USE_MPI
150 #ifndef ALWAYS_USE_MPI
151 IF ( usingMPI ) THEN
152 #endif
153 theProc = tilePidW(bi,bj)
154 theTag = _tileTagRecvW(bi,bj)
155 theType = _MPI_TYPE_RX
156 theSize = sNy*exchWidthX*myNz
157 # ifndef ALLOW_AUTODIFF_OPENAD
158 CALL MPI_Recv( westRecvBuf_RX(1,eBl,bi,bj), theSize, theType,
159 & theProc, theTag, MPI_COMM_MODEL,
160 & mpiStatus, mpiRc )
161 # else
162 CALL ampi_recv_RX(
163 & westRecvBuf_RX(1,eBl,bi,bj) ,
164 & theSize ,
165 & theType ,
166 & theProc ,
167 & theTag ,
168 & MPI_COMM_MODEL ,
169 & exchReqIdX(exchNReqsX(1,bi,bj)+1,1,bi,bj),
170 & exchNReqsX(1,bi,bj),
171 & mpiStatus ,
172 & mpiRc )
173 # endif /* ALLOW_AUTODIFF_OPENAD */
174 #ifndef ALWAYS_USE_MPI
175 ENDIF
176 #endif
177 #endif /* ALLOW_USE_MPI */
178 ENDIF
179 IF ( eastCommMode .EQ. COMM_MSG ) THEN
180 #ifdef ALLOW_USE_MPI
181 #ifndef ALWAYS_USE_MPI
182 IF ( usingMPI ) THEN
183 #endif
184 theProc = tilePidE(bi,bj)
185 theTag = _tileTagRecvE(bi,bj)
186 theType = _MPI_TYPE_RX
187 theSize = sNy*exchWidthX*myNz
188 # ifndef ALLOW_AUTODIFF_OPENAD
189 CALL MPI_Recv( eastRecvBuf_RX(1,eBl,bi,bj), theSize, theType,
190 & theProc, theTag, MPI_COMM_MODEL,
191 & mpiStatus, mpiRc )
192 # else
193 CALL ampi_recv_RX(
194 & eastRecvBuf_RX(1,eBl,bi,bj) ,
195 & theSize ,
196 & theType ,
197 & theProc ,
198 & theTag ,
199 & MPI_COMM_MODEL ,
200 & exchReqIdX(exchNReqsX(1,bi,bj)+1,1,bi,bj),
201 & exchNReqsX(1,bi,bj),
202 & mpiStatus ,
203 & mpiRc )
204 # endif /* ALLOW_AUTODIFF_OPENAD */
205 #ifndef ALWAYS_USE_MPI
206 ENDIF
207 #endif
208 #endif /* ALLOW_USE_MPI */
209 ENDIF
210 ENDDO
211 ENDDO
212
213 C-- Wait for buffers I am going read to be ready.
214 IF ( exchUsesBarrier ) THEN
215 C o On some machines ( T90 ) use system barrier rather than spinning.
216 CALL BARRIER( myThid )
217 ELSE
218 C o Spin waiting for completetion flag. This avoids a global-lock
219 C i.e. we only lock waiting for data that we need.
220 DO bj=myByLo(myThid),myByHi(myThid)
221 DO bi=myBxLo(myThid),myBxHi(myThid)
222 spinCount = 0
223 ebL = exchangeBufLevel(1,bi,bj)
224 westCommMode = _tileCommModeW(bi,bj)
225 eastCommMode = _tileCommModeE(bi,bj)
226 # ifndef ALLOW_AUTODIFF_OPENAD
227 10 CONTINUE
228 CALL FOOL_THE_COMPILER( spinCount )
229 spinCount = spinCount+1
230 C IF ( myThid .EQ. 1 .AND. spinCount .GT. _EXCH_SPIN_LIMIT ) THEN
231 C WRITE(*,*) ' eBl = ', ebl
232 C STOP ' S/R EXCH_RECV_GET_X: spinCount .GT. _EXCH_SPIN_LIMIT'
233 C ENDIF
234 IF ( westRecvAck(eBl,bi,bj) .EQ. 0 ) GOTO 10
235 IF ( eastRecvAck(eBl,bi,bj) .EQ. 0 ) GOTO 10
236 # else
237 do while ((westRecvAck(eBl,bi,bj) .EQ. 0.
238 & .or.
239 & eastRecvAck(eBl,bi,bj) .EQ. 0. ))
240 CALL FOOL_THE_COMPILER( spinCount )
241 spinCount = spinCount+1
242 end do
243 # endif /* ALLOW_AUTODIFF_OPENAD */
244 C Clear outstanding requests
245 westRecvAck(eBl,bi,bj) = 0
246 eastRecvAck(eBl,bi,bj) = 0
247
248 IF ( exchNReqsX(1,bi,bj) .GT. 0 ) THEN
249 #ifdef ALLOW_USE_MPI
250 #ifndef ALWAYS_USE_MPI
251 IF ( usingMPI ) THEN
252 #endif
253 # ifndef ALLOW_AUTODIFF_OPENAD
254 CALL MPI_Waitall( exchNReqsX(1,bi,bj), exchReqIdX(1,1,bi,bj),
255 & mpiStatus, mpiRC )
256 # else
257 CALL ampi_waitall(
258 & exchNReqsX(1,bi,bj),
259 & exchReqIdX(1,1,bi,bj),
260 & mpiStatus,
261 & mpiRC )
262 # endif /* ALLOW_AUTODIFF_OPENAD */
263 #ifndef ALWAYS_USE_MPI
264 ENDIF
265 #endif
266 #endif /* ALLOW_USE_MPI */
267 ENDIF
268 C Clear outstanding requests counter
269 exchNReqsX(1,bi,bj) = 0
270 C Update statistics
271 IF ( exchCollectStatistics ) THEN
272 exchRecvXExchCount(1,bi,bj) = exchRecvXExchCount(1,bi,bj)+1
273 exchRecvXSpinCount(1,bi,bj) =
274 & exchRecvXSpinCount(1,bi,bj)+spinCount
275 exchRecvXSpinMax(1,bi,bj) =
276 & MAX(exchRecvXSpinMax(1,bi,bj),spinCount)
277 exchRecvXSpinMin(1,bi,bj) =
278 & MIN(exchRecvXSpinMin(1,bi,bj),spinCount)
279 ENDIF
280 ENDDO
281 ENDDO
282 ENDIF
283
284 C-- Read from the buffers
285 DO bj=myByLo(myThid),myByHi(myThid)
286 DO bi=myBxLo(myThid),myBxHi(myThid)
287
288 ebL = exchangeBufLevel(1,bi,bj)
289 biE = _tileBiE(bi,bj)
290 bjE = _tileBjE(bi,bj)
291 biW = _tileBiW(bi,bj)
292 bjW = _tileBjW(bi,bj)
293 westCommMode = _tileCommModeW(bi,bj)
294 eastCommMode = _tileCommModeE(bi,bj)
295 IF ( _theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
296 iMin = sNx+1
297 iMax = sNx+exchWidthX
298 iB0 = 0
299 IF ( eastCommMode .EQ. COMM_PUT
300 & .OR. eastCommMode .EQ. COMM_MSG ) THEN
301 iB = 0
302 DO K=1,myNz
303 DO J=1,sNy
304 DO I=iMin,iMax
305 iB = iB + 1
306 array(I,J,K,bi,bj) = eastRecvBuf_RX(iB,eBl,bi,bj)
307 ENDDO
308 ENDDO
309 ENDDO
310 ELSEIF ( eastCommMode .EQ. COMM_GET ) THEN
311 DO K=1,myNz
312 DO J=1,sNy
313 iB = iB0
314 DO I=iMin,iMax
315 iB = iB+1
316 array(I,J,K,bi,bj) = array(iB,J,K,biE,bjE)
317 ENDDO
318 ENDDO
319 ENDDO
320 ENDIF
321 ELSEIF ( _theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
322 iMin = sNx-exchWidthX+1
323 iMax = sNx
324 iB0 = 1-exchWidthX-1
325 IF ( eastCommMode .EQ. COMM_PUT
326 & .OR. eastCommMode .EQ. COMM_MSG ) THEN
327 iB = 0
328 DO K=1,myNz
329 DO J=1,sNy
330 DO I=iMin,iMax
331 iB = iB + 1
332 array(I,J,K,bi,bj) =
333 & array(I,J,K,bi,bj)+eastRecvBuf_RX(iB,eBl,bi,bj)
334 ENDDO
335 ENDDO
336 ENDDO
337 ELSEIF ( eastCommMode .EQ. COMM_GET ) THEN
338 DO K=1,myNz
339 DO J=1,sNy
340 iB = iB0
341 DO I=iMin,iMax
342 iB = iB+1
343 array(I,J,K,bi,bj) =
344 & array(I,J,K,bi,bj)+array(iB,J,K,biE,bjE)
345 ENDDO
346 ENDDO
347 ENDDO
348 ENDIF
349 ENDIF
350 IF ( _theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
351 iMin = 1-exchWidthX
352 iMax = 0
353 iB0 = sNx-exchWidthX
354 IF ( westCommMode .EQ. COMM_PUT
355 & .OR. westCommMode .EQ. COMM_MSG ) THEN
356 iB = 0
357 DO K=1,myNz
358 DO J=1,sNy
359 DO I=iMin,iMax
360 iB = iB + 1
361 array(I,J,K,bi,bj) = westRecvBuf_RX(iB,eBl,bi,bj)
362 ENDDO
363 ENDDO
364 ENDDO
365 ELSEIF ( westCommMode .EQ. COMM_GET ) THEN
366 DO K=1,myNz
367 DO J=1,sNy
368 iB = iB0
369 DO I=iMin,iMax
370 iB = iB+1
371 array(I,J,K,bi,bj) = array(iB,J,K,biW,bjW)
372 ENDDO
373 ENDDO
374 ENDDO
375 ENDIF
376 ELSEIF ( _theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
377 iMin = 1
378 iMax = 1+exchWidthX-1
379 iB0 = sNx
380 IF ( westCommMode .EQ. COMM_PUT
381 & .OR. westCommMode .EQ. COMM_MSG ) THEN
382 iB = 0
383 DO K=1,myNz
384 DO J=1,sNy
385 DO I=iMin,iMax
386 iB = iB + 1
387 array(I,J,K,bi,bj) =
388 & array(I,J,K,bi,bj)+westRecvBuf_RX(iB,eBl,bi,bj)
389 ENDDO
390 ENDDO
391 ENDDO
392 ELSEIF ( westCommMode .EQ. COMM_GET ) THEN
393 DO K=1,myNz
394 DO J=1,sNy
395 iB = iB0
396 DO I=iMin,iMax
397 iB = iB+1
398 array(I,J,K,bi,bj) =
399 & array(I,J,K,bi,bj)+array(iB,J,K,biW,bjW)
400 ENDDO
401 ENDDO
402 ENDDO
403 ENDIF
404 ENDIF
405
406 ENDDO
407 ENDDO
408
409 _BARRIER
410 IF ( doingSingleThreadedComms ) THEN
411 C Restore saved settings that were stored to allow
412 C single thred comms.
413 _BEGIN_MASTER(myThid)
414 DO I=1,nThreads
415 myBxLo(I) = myBxLoSave(I)
416 myBxHi(I) = myBxHiSave(I)
417 myByLo(I) = myByLoSave(I)
418 myByHi(I) = myByHiSave(I)
419 ENDDO
420 _END_MASTER(myThid)
421 ENDIF
422 _BARRIER
423
424 RETURN
425 END

  ViewVC Help
Powered by ViewVC 1.1.22