/[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.16 - (show annotations) (download)
Mon Sep 3 19:37:54 2012 UTC (11 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint64, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint63s, checkpoint65o, checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, HEAD
Changes since 1.15: +8 -7 lines
avoid unused variable (+ start to remove ALWAYS_USE_MPI)

1 C $Header: /u/gcmpack/MITgcm/eesupp/src/exch_rx_recv_get_x.template,v 1.15 2010/05/19 08:14:16 mlosch Exp $
2 C $Name: $
3 #include "CPP_EEOPTIONS.h"
4 #undef EXCH_USE_SPINNING
5
6 CBOP
7 C !ROUTINE: EXCH_RX_RECV_GET_X
8
9 C !INTERFACE:
10 SUBROUTINE EXCH_RX_RECV_GET_X( array,
11 I myOLw, myOLe, myOLs, myOLn, myNz,
12 I exchWidthX, exchWidthY,
13 I theSimulationMode, theCornerMode, myThid )
14 IMPLICIT NONE
15
16 C !DESCRIPTION:
17 C *==========================================================*
18 C | SUBROUTINE RECV_RX_GET_X
19 C | o "Send" or "put" X edges for RX array.
20 C *==========================================================*
21 C | Routine that invokes actual message passing send or
22 C | direct "put" of data to update X faces of an XY[R] array.
23 C *==========================================================*
24
25 C !USES:
26 C == Global variables ==
27 #include "SIZE.h"
28 #include "EEPARAMS.h"
29 #include "EESUPPORT.h"
30 #include "EXCH.h"
31
32 C !INPUT/OUTPUT PARAMETERS:
33 C == Routine arguments ==
34 C array :: Array with edges to exchange.
35 C myOLw :: West, East, North and South overlap region sizes.
36 C myOLe
37 C myOLn
38 C myOLs
39 C exchWidthX :: Width of data region exchanged.
40 C exchWidthY
41 C theSimulationMode :: Forward or reverse mode exchange ( provides
42 C support for adjoint integration of code. )
43 C theCornerMode :: Flag indicating whether corner updates are
44 C needed.
45 C myThid :: Thread number of this instance of S/R EXCH...
46 C eBl :: Edge buffer level
47 INTEGER myOLw
48 INTEGER myOLe
49 INTEGER myOLs
50 INTEGER myOLn
51 INTEGER myNz
52 _RX array(1-myOLw:sNx+myOLe,
53 & 1-myOLs:sNy+myOLn,
54 & myNZ, nSx, nSy)
55 INTEGER exchWidthX
56 INTEGER exchWidthY
57 INTEGER theSimulationMode
58 INTEGER theCornerMode
59 INTEGER myThid
60
61 C !LOCAL VARIABLES:
62 C == Local variables ==
63 C i, j, k, iMin, iMax, iB :: Loop counters and extents
64 C bi, bj
65 C biW, bjW :: West tile indices
66 C biE, bjE :: East tile indices
67 C eBl :: Current exchange buffer level
68 C theProc, theTag, theType, :: Variables used in message building
69 C theSize
70 C westCommMode :: Working variables holding type
71 C eastCommMode of communication a particular
72 C tile face uses.
73 INTEGER i, j, k, iMin, iMax, iB, iB0
74 INTEGER bi, bj, biW, bjW, biE, bjE
75 INTEGER eBl
76 INTEGER westCommMode
77 INTEGER eastCommMode
78 #ifdef EXCH_USE_SPINNING
79 INTEGER spinCount
80 #endif
81 #ifdef ALLOW_USE_MPI
82 INTEGER theProc, theTag, theType, theSize
83 INTEGER mpiStatus(MPI_STATUS_SIZE,4), mpiRc
84 # ifdef ALLOW_AUTODIFF_OPENAD_AMPI
85 INTEGER pReqI
86 # endif
87 #endif /* ALLOW_USE_MPI */
88 CEOP
89
90 C-- Under a "put" scenario we
91 C-- i. set completetion signal for buffer we put into.
92 C-- ii. wait for completetion signal indicating data has been put in
93 C-- our buffer.
94 C-- Under a messaging mode we "receive" the message.
95 C-- Under a "get" scenario we
96 C-- i. Check that the data is ready.
97 C-- ii. Read the data.
98 C-- iii. Set data read flag + memory sync.
99
100 #ifdef ALLOW_USE_MPI
101 IF ( usingMPI ) THEN
102
103 C-- Receive buffer data: Only Master Thread do proc communication
104 _BEGIN_MASTER(myThid)
105
106 DO bj=1,nSy
107 DO bi=1,nSx
108 eBl = exchangeBufLevel(1,bi,bj)
109 westCommMode = _tileCommModeW(bi,bj)
110 eastCommMode = _tileCommModeE(bi,bj)
111 biE = _tileBiE(bi,bj)
112 bjE = _tileBjE(bi,bj)
113 biW = _tileBiW(bi,bj)
114 bjW = _tileBjW(bi,bj)
115 theType = _MPI_TYPE_RX
116 theSize = sNy*exchWidthX*myNz
117
118 IF ( westCommMode .EQ. COMM_MSG ) THEN
119 theProc = tilePidW(bi,bj)
120 theTag = _tileTagRecvW(bi,bj)
121 # ifndef ALLOW_AUTODIFF_OPENAD_AMPI
122 CALL MPI_Recv( westRecvBuf_RX(1,eBl,bi,bj), theSize,
123 & theType, theProc, theTag, MPI_COMM_MODEL,
124 & mpiStatus, mpiRc )
125 # else
126 pReqI=exchNReqsX(1,bi,bj)+1
127 CALL ampi_recv_RX(
128 & westRecvBuf_RX(1,eBl,bi,bj) ,
129 & theSize ,
130 & theType ,
131 & theProc ,
132 & theTag ,
133 & MPI_COMM_MODEL ,
134 & exchReqIdX(pReqI,1,bi,bj),
135 & exchNReqsX(1,bi,bj),
136 & mpiStatus ,
137 & mpiRc )
138 # endif /* ALLOW_AUTODIFF_OPENAD_AMPI */
139 westRecvAck(eBl,bi,bj) = 1
140 ENDIF
141
142 IF ( eastCommMode .EQ. COMM_MSG ) THEN
143 theProc = tilePidE(bi,bj)
144 theTag = _tileTagRecvE(bi,bj)
145 # ifndef ALLOW_AUTODIFF_OPENAD_AMPI
146 CALL MPI_Recv( eastRecvBuf_RX(1,eBl,bi,bj), theSize,
147 & theType, theProc, theTag, MPI_COMM_MODEL,
148 & mpiStatus, mpiRc )
149 # else
150 pReqI=exchNReqsX(1,bi,bj)+1
151 CALL ampi_recv_RX(
152 & eastRecvBuf_RX(1,eBl,bi,bj) ,
153 & theSize ,
154 & theType ,
155 & theProc ,
156 & theTag ,
157 & MPI_COMM_MODEL ,
158 & exchReqIdX(pReqI,1,bi,bj),
159 & exchNReqsX(1,bi,bj),
160 & mpiStatus ,
161 & mpiRc )
162 # endif /* ALLOW_AUTODIFF_OPENAD_AMPI */
163 eastRecvAck(eBl,bi,bj) = 1
164 ENDIF
165 ENDDO
166 ENDDO
167
168 C-- Processes wait for buffers I am going to read to be ready.
169 IF ( .NOT.exchUsesBarrier ) THEN
170 DO bj=1,nSy
171 DO bi=1,nSx
172 IF ( exchNReqsX(1,bi,bj) .GT. 0 ) THEN
173 # ifndef ALLOW_AUTODIFF_OPENAD_AMPI
174 CALL MPI_Waitall( exchNReqsX(1,bi,bj), exchReqIdX(1,1,bi,bj),
175 & mpiStatus, mpiRC )
176 # else
177 CALL ampi_waitall(
178 & exchNReqsX(1,bi,bj),
179 & exchReqIdX(1,1,bi,bj),
180 & mpiStatus,
181 & mpiRC )
182 # endif /* ALLOW_AUTODIFF_OPENAD_AMPI */
183 ENDIF
184 C Clear outstanding requests counter
185 exchNReqsX(1,bi,bj) = 0
186 ENDDO
187 ENDDO
188 ENDIF
189
190 _END_MASTER(myThid)
191 C-- need to sync threads after master has received data ;
192 C (done after mpi waitall in case waitall is really needed)
193 _BARRIER
194
195 ENDIF
196 #endif /* ALLOW_USE_MPI */
197
198 C-- Threads wait for buffers I am going to read to be ready.
199 C note: added BARRIER in exch_send_put S/R and here above (message mode)
200 C so that we no longer needs this (undef EXCH_USE_SPINNING)
201 #ifdef EXCH_USE_SPINNING
202 IF ( exchUsesBarrier ) THEN
203 C o On some machines ( T90 ) use system barrier rather than spinning.
204 CALL BARRIER( myThid )
205 ELSE
206 C o Spin waiting for completetion flag. This avoids a global-lock
207 C i.e. we only lock waiting for data that we need.
208 DO bj=myByLo(myThid),myByHi(myThid)
209 DO bi=myBxLo(myThid),myBxHi(myThid)
210
211 spinCount = 0
212 eBl = exchangeBufLevel(1,bi,bj)
213 westCommMode = _tileCommModeW(bi,bj)
214 eastCommMode = _tileCommModeE(bi,bj)
215 # ifndef ALLOW_AUTODIFF_OPENAD_AMPI
216 10 CONTINUE
217 CALL FOOL_THE_COMPILER( spinCount )
218 spinCount = spinCount+1
219 C IF ( myThid .EQ. 1 .AND. spinCount .GT. _EXCH_SPIN_LIMIT ) THEN
220 C WRITE(*,*) ' eBl = ', ebl
221 C STOP ' S/R EXCH_RECV_GET_X: spinCount .GT. _EXCH_SPIN_LIMIT'
222 C ENDIF
223 IF ( westRecvAck(eBl,bi,bj) .EQ. 0 ) GOTO 10
224 IF ( eastRecvAck(eBl,bi,bj) .EQ. 0 ) GOTO 10
225 # else
226 DO WHILE ((westRecvAck(eBl,bi,bj) .EQ. 0
227 & .OR.
228 & eastRecvAck(eBl,bi,bj) .EQ. 0 ))
229 CALL FOOL_THE_COMPILER( spinCount )
230 spinCount = spinCount+1
231 ENDDO
232 # endif /* ALLOW_AUTODIFF_OPENAD_AMPI */
233 C Clear outstanding requests
234 westRecvAck(eBl,bi,bj) = 0
235 eastRecvAck(eBl,bi,bj) = 0
236 C Update statistics
237 IF ( exchCollectStatistics ) THEN
238 exchRecvXExchCount(1,bi,bj) = exchRecvXExchCount(1,bi,bj)+1
239 exchRecvXSpinCount(1,bi,bj) =
240 & exchRecvXSpinCount(1,bi,bj)+spinCount
241 exchRecvXSpinMax(1,bi,bj) =
242 & MAX(exchRecvXSpinMax(1,bi,bj),spinCount)
243 exchRecvXSpinMin(1,bi,bj) =
244 & MIN(exchRecvXSpinMin(1,bi,bj),spinCount)
245 ENDIF
246
247 ENDDO
248 ENDDO
249 ENDIF
250 #endif /* EXCH_USE_SPINNING */
251
252 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
253
254 C-- Read from the buffers
255 DO bj=myByLo(myThid),myByHi(myThid)
256 DO bi=myBxLo(myThid),myBxHi(myThid)
257
258 eBl = exchangeBufLevel(1,bi,bj)
259 biE = _tileBiE(bi,bj)
260 bjE = _tileBjE(bi,bj)
261 biW = _tileBiW(bi,bj)
262 bjW = _tileBjW(bi,bj)
263 westCommMode = _tileCommModeW(bi,bj)
264 eastCommMode = _tileCommModeE(bi,bj)
265
266 IF ( _theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
267 iMin = sNx+1
268 iMax = sNx+exchWidthX
269 iB0 = 0
270 IF ( eastCommMode .EQ. COMM_PUT
271 & .OR. eastCommMode .EQ. COMM_MSG ) THEN
272 iB = 0
273 DO k=1,myNz
274 DO j=1,sNy
275 DO i=iMin,iMax
276 iB = iB + 1
277 array(i,j,k,bi,bj) = eastRecvBuf_RX(iB,eBl,bi,bj)
278 ENDDO
279 ENDDO
280 ENDDO
281 ELSEIF ( eastCommMode .EQ. COMM_GET ) THEN
282 DO k=1,myNz
283 DO j=1,sNy
284 iB = iB0
285 DO i=iMin,iMax
286 iB = iB+1
287 array(i,j,k,bi,bj) = array(iB,j,k,biE,bjE)
288 ENDDO
289 ENDDO
290 ENDDO
291 ENDIF
292 ELSEIF ( _theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
293 iMin = sNx-exchWidthX+1
294 iMax = sNx
295 iB0 = 1-exchWidthX-1
296 IF ( eastCommMode .EQ. COMM_PUT
297 & .OR. eastCommMode .EQ. COMM_MSG ) THEN
298 iB = 0
299 DO k=1,myNz
300 DO j=1,sNy
301 DO i=iMin,iMax
302 iB = iB + 1
303 array(i,j,k,bi,bj) =
304 & array(i,j,k,bi,bj) + eastRecvBuf_RX(iB,eBl,bi,bj)
305 ENDDO
306 ENDDO
307 ENDDO
308 ELSEIF ( eastCommMode .EQ. COMM_GET ) THEN
309 DO k=1,myNz
310 DO j=1,sNy
311 iB = iB0
312 DO i=iMin,iMax
313 iB = iB+1
314 array(i,j,k,bi,bj) =
315 & array(i,j,k,bi,bj) + array(iB,j,k,biE,bjE)
316 array(iB,j,k,biE,bjE) = 0.0
317 ENDDO
318 ENDDO
319 ENDDO
320 ENDIF
321 ENDIF
322
323 IF ( _theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
324 iMin = 1-exchWidthX
325 iMax = 0
326 iB0 = sNx-exchWidthX
327 IF ( westCommMode .EQ. COMM_PUT
328 & .OR. westCommMode .EQ. COMM_MSG ) THEN
329 iB = 0
330 DO k=1,myNz
331 DO j=1,sNy
332 DO i=iMin,iMax
333 iB = iB + 1
334 array(i,j,k,bi,bj) = westRecvBuf_RX(iB,eBl,bi,bj)
335 ENDDO
336 ENDDO
337 ENDDO
338 ELSEIF ( westCommMode .EQ. COMM_GET ) THEN
339 DO k=1,myNz
340 DO j=1,sNy
341 iB = iB0
342 DO i=iMin,iMax
343 iB = iB+1
344 array(i,j,k,bi,bj) = array(iB,j,k,biW,bjW)
345 ENDDO
346 ENDDO
347 ENDDO
348 ENDIF
349 ELSEIF ( _theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
350 iMin = 1
351 iMax = 1+exchWidthX-1
352 iB0 = sNx
353 IF ( westCommMode .EQ. COMM_PUT
354 & .OR. westCommMode .EQ. COMM_MSG ) THEN
355 iB = 0
356 DO k=1,myNz
357 DO j=1,sNy
358 DO i=iMin,iMax
359 iB = iB + 1
360 array(i,j,k,bi,bj) =
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) =
372 & array(i,j,k,bi,bj) + array(iB,j,k,biW,bjW)
373 array(iB,j,k,biW,bjW) = 0.0
374 ENDDO
375 ENDDO
376 ENDDO
377 ENDIF
378 ENDIF
379
380 ENDDO
381 ENDDO
382
383 RETURN
384 END

  ViewVC Help
Powered by ViewVC 1.1.22