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

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

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


Revision 1.14 - (show annotations) (download)
Mon May 17 02:28:06 2010 UTC (13 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62g, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62w, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint63g, checkpoint63, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c
Changes since 1.13: +220 -278 lines
 - Separate buffer filling and MPI sending: allow EXCH-1 to work for local
   array (non-shared) when using MPI+MTH. Also reduces number of BARRIER
   (even without using MPI).
 - Message mode: move RecvAck setting (indicator of buffer being ready)
   from send_put to recv_get S/R (was useless before, but not sure if
   it's much more useful now);
 - switch the order of sync: MPI-proc 1rst and then threads;
 - take out spin-waiting code (#undef EXCH_USE_SPINNING), use BARRIER instead.

1 C $Header: /u/gcmpack/MITgcm/eesupp/src/exch_rx_send_put_y.template,v 1.13 2009/01/09 22:51:12 jmc Exp $
2 C $Name: $
3 #include "CPP_EEOPTIONS.h"
4
5 CBOP
6 C !ROUTINE: EXCH_RX_SEND_PUT_Y
7
8 C !INTERFACE:
9 SUBROUTINE EXCH_RX_SEND_PUT_Y( array,
10 I myOLw, myOLe, myOLs, myOLn, myNz,
11 I exchWidthX, exchWidthY,
12 I thesimulationMode, thecornerMode, myThid )
13 IMPLICIT NONE
14 C !DESCRIPTION:
15 C *==========================================================*
16 C | SUBROUTINE SEND_PUT_Y
17 C | o "Send" or "put" Y edges for RX array.
18 C *==========================================================*
19 C | Routine that invokes actual message passing send or
20 C | direct "put" of data to update Y faces of an XY[R] array.
21 C *==========================================================*
22
23 C !USES:
24 C == Global variables ==
25 #include "SIZE.h"
26 #include "EEPARAMS.h"
27 #include "EESUPPORT.h"
28 #include "EXCH.h"
29
30 C !INPUT/OUTPUT PARAMETERS:
31 C == Routine arguments ==
32 C array :: Array with edges to exchange.
33 C myOLw :: West, East, North and South overlap region sizes.
34 C myOLe
35 C myOLn
36 C myOLs
37 C exchWidthX :: Width of data region exchanged.
38 C exchWidthY
39 C theSimulationMode :: Forward or reverse mode exchange ( provides
40 C support for adjoint integration of code. )
41 C Note - the reverse mode for an assignment
42 C is an accumulation. This means that
43 C put implementations that do leary things
44 C like writing to overlap regions in a
45 C remote process need to be even more
46 C careful. You need to be pretty careful
47 C in forward mode too!
48 C theCornerMode :: Flag indicating whether corner updates are
49 C needed.
50 C myThid :: Thread number of this instance of S/R EXCH...
51 C eBl :: Edge buffer level
52 INTEGER myOLw
53 INTEGER myOLe
54 INTEGER myOLs
55 INTEGER myOLn
56 INTEGER myNz
57 _RX array(1-myOLw:sNx+myOLe,
58 & 1-myOLs:sNy+myOLn,
59 & myNZ, nSx, nSy)
60 INTEGER exchWidthX
61 INTEGER exchWidthY
62 INTEGER theSimulationMode
63 INTEGER theCornerMode
64 INTEGER myThid
65
66 C !LOCAL VARIABLES:
67 C == Local variables ==
68 C i, j, k, jMin, jMax, iB - Loop counters and extents
69 C bi, bj
70 C biS, bjS - South tile indices
71 C biN, bjN - North tile indices
72 C eBl - Current exchange buffer level
73 C theProc, theTag, theType, - Variables used in message building
74 C theSize
75 C southCommMode - Working variables holding type
76 C northCommMode of communication a particular
77 C tile face uses.
78 INTEGER i, j, k, jMin, jMax, iMin, iMax, iB
79 INTEGER bi, bj, biS, bjS, biN, bjN
80 INTEGER eBl
81 INTEGER northCommMode
82 INTEGER southCommMode
83 #ifdef ALLOW_USE_MPI
84 INTEGER theProc, theTag, theType, theSize, mpiRc
85 # ifdef ALLOW_AUTODIFF_OPENAD_AMPI
86 INTEGER mpiStatus(MPI_STATUS_SIZE)
87 INTEGER pReqI
88 # endif
89 #endif
90
91 C-- Write data to exchange buffer
92 C Various actions are possible depending on the communication mode
93 C as follows:
94 C Mode Action
95 C -------- ---------------------------
96 C COMM_NONE Do nothing
97 C
98 C COMM_MSG Message passing communication ( e.g. MPI )
99 C Fill south send buffer from this tile.
100 C Send data with tag identifying tile and direction.
101 C Fill north send buffer from this tile.
102 C Send data with tag identifying tile and direction.
103 C
104 C COMM_PUT "Put" communication ( UMP_, shmemput, etc... )
105 C Fill south receive buffer of south-neighbor tile
106 C Fill north receive buffer of north-neighbor tile
107 C Sync. memory
108 C Write data-ready Ack for north edge of south-neighbor
109 C tile
110 C Write data-ready Ack for south edge of north-neighbor
111 C tile
112 C Sync. memory
113 CEOP
114
115 #ifdef ALLOW_AUTODIFF_OPENAD_AMPI
116 # ifdef ALLOW_USE_MPI
117 # ifndef ALWAYS_USE_MPI
118 IF ( usingMPI ) THEN
119 # endif
120 _BEGIN_MASTER(myThid)
121 DO bj=1,nSy
122 DO bi=1,nSx
123 CALL ampi_awaitall (
124 & exchNReqsY(1,bi,bj) ,
125 & exchReqIdY(1,1,bi,bj) ,
126 & mpiStatus ,
127 & mpiRC )
128 ENDDO
129 ENDDO
130 _END_MASTER(myThid)
131 # ifndef ALWAYS_USE_MPI
132 ENDIF
133 # endif
134 # endif
135 #endif
136
137 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
138
139 C Prevent anyone to access shared buffer while an other thread modifies it
140 _BARRIER
141
142 C Fill shared buffers from array values
143 DO bj=myByLo(myThid),myByHi(myThid)
144 DO bi=myBxLo(myThid),myBxHi(myThid)
145
146 eBl = exchangeBufLevel(1,bi,bj)
147 southCommMode = _tileCommModeS(bi,bj)
148 northCommMode = _tileCommModeN(bi,bj)
149 biS = _tileBiS(bi,bj)
150 bjS = _tileBjS(bi,bj)
151 biN = _tileBiN(bi,bj)
152 bjN = _tileBjN(bi,bj)
153 iMin = 1
154 iMax = sNx
155 IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS ) THEN
156 iMin = 1-exchWidthX
157 iMax = sNx+exchWidthX
158 ENDIF
159
160 C >>>>>>>>>>>>>>>>>>> FORWARD RUN <<<<<<<<<<<<<<<<<<<
161
162 IF ( _theSimulationMode .EQ. FORWARD_SIMULATION ) THEN
163
164 C o Send or Put south edge
165 jMin = 1
166 jMax = 1+exchWidthY-1
167 IF ( southCommMode .EQ. COMM_MSG ) THEN
168 iB = 0
169 DO k=1,myNz
170 DO j=jMin,jMax
171 DO i=iMin,iMax
172 iB = iB + 1
173 southSendBuf_RX(iB,eBl,bi,bj) = array(i,j,k,bi,bj)
174 ENDDO
175 ENDDO
176 ENDDO
177 ELSEIF ( southCommMode .EQ. COMM_PUT ) THEN
178 iB = 0
179 DO k=1,myNz
180 DO j=jMin,jMax
181 DO i=iMin,iMax
182 iB = iB + 1
183 northRecvBuf_RX(iB,eBl,biS,bjS) = array(i,j,k,bi,bj)
184 ENDDO
185 ENDDO
186 ENDDO
187 ELSEIF ( southCommMode .NE. COMM_NONE
188 & .AND. southCommMode .NE. COMM_GET ) THEN
189 STOP ' S/R EXCH: Invalid commS mode.'
190 ENDIF
191
192 C o Send or Put north edge
193 jMin = sNy-exchWidthY+1
194 jMax = sNy
195 IF ( northCommMode .EQ. COMM_MSG ) THEN
196 iB = 0
197 DO k=1,myNz
198 DO j=jMin,jMax
199 DO i=iMin,iMax
200 iB = iB + 1
201 northSendBuf_RX(iB,eBl,bi,bj) = array(i,j,k,bi,bj)
202 ENDDO
203 ENDDO
204 ENDDO
205 ELSEIF ( northCommMode .EQ. COMM_PUT ) THEN
206 iB = 0
207 DO k=1,myNz
208 DO j=jMin,jMax
209 DO i=iMin,iMax
210 iB = iB + 1
211 southRecvBuf_RX(iB,eBl,biN,bjN) = array(i,j,k,bi,bj)
212 ENDDO
213 ENDDO
214 ENDDO
215 ELSEIF ( northCommMode .NE. COMM_NONE
216 & .AND. northCommMode .NE. COMM_GET ) THEN
217 STOP ' S/R EXCH: Invalid commN mode.'
218 ENDIF
219
220 C >>>>>>>>>>>>>>>>>>> ADJOINT RUN <<<<<<<<<<<<<<<<<<<
221
222 ELSEIF ( _theSimulationMode .EQ. REVERSE_SIMULATION ) THEN
223
224 C o Send or Put south edge
225 jMin = 1-exchWidthY
226 jMax = 0
227 IF ( southCommMode .EQ. COMM_MSG ) THEN
228 iB = 0
229 DO k=1,myNz
230 DO j=jMin,jMax
231 DO i=iMin,iMax
232 iB = iB + 1
233 southSendBuf_RX(iB,eBl,bi,bj) = array(i,j,k,bi,bj)
234 array(i,j,k,bi,bj) = 0.0
235 ENDDO
236 ENDDO
237 ENDDO
238 ELSEIF ( southCommMode .EQ. COMM_PUT ) THEN
239 iB = 0
240 DO k=1,myNz
241 DO j=jMin,jMax
242 DO i=iMin,iMax
243 iB = iB + 1
244 northRecvBuf_RX(iB,eBl,biS,bjS) = array(i,j,k,bi,bj)
245 array(i,j,k,bi,bj) = 0.0
246 ENDDO
247 ENDDO
248 ENDDO
249 ELSEIF ( southCommMode .NE. COMM_NONE
250 & .AND. southCommMode .NE. COMM_GET ) THEN
251 STOP ' S/R EXCH: Invalid commS mode.'
252 ENDIF
253
254 C o Send or Put north edge
255 jMin = sNy+1
256 jMax = sNy+exchWidthY
257 IF ( northCommMode .EQ. COMM_MSG ) THEN
258 iB = 0
259 DO k=1,myNz
260 DO j=jMin,jMax
261 DO i=iMin,iMax
262 iB = iB + 1
263 northSendBuf_RX(iB,eBl,bi,bj) = array(i,j,k,bi,bj)
264 array(i,j,k,bi,bj) = 0.0
265 ENDDO
266 ENDDO
267 ENDDO
268 ELSEIF ( northCommMode .EQ. COMM_PUT ) THEN
269 iB = 0
270 DO k=1,myNz
271 DO j=jMin,jMax
272 DO i=iMin,iMax
273 iB = iB + 1
274 southRecvBuf_RX(iB,eBl,biN,bjN) = array(i,j,k,bi,bj)
275 array(i,j,k,bi,bj) = 0.0
276 ENDDO
277 ENDDO
278 ENDDO
279 ELSEIF ( northCommMode .NE. COMM_NONE
280 & .AND. northCommMode .NE. COMM_GET ) THEN
281 STOP ' S/R EXCH: Invalid commN mode.'
282 ENDIF
283
284 ENDIF
285
286 ENDDO
287 ENDDO
288
289 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
290 C-- Signal completetion ( making sure system-wide memory state is
291 C-- consistent ).
292
293 C ** NOTE ** We are relying on being able to produce strong-ordered
294 C memory semantics here. In other words we assume that there is a
295 C mechanism which can ensure that by the time the Ack is seen the
296 C overlap region data that will be exchanged is up to date.
297 IF ( exchNeedsMemSync ) CALL MEMSYNC
298
299 DO bj=myByLo(myThid),myByHi(myThid)
300 DO bi=myBxLo(myThid),myBxHi(myThid)
301 eBl = exchangeBufLevel(1,bi,bj)
302 biS = _tileBiS(bi,bj)
303 bjS = _tileBjS(bi,bj)
304 biN = _tileBiN(bi,bj)
305 bjN = _tileBjN(bi,bj)
306 southCommMode = _tileCommModeS(bi,bj)
307 northCommMode = _tileCommModeN(bi,bj)
308 IF ( southCommMode.EQ.COMM_PUT ) northRecvAck(eBl,biS,bjS) = 1
309 IF ( northCommMode.EQ.COMM_PUT ) southRecvAck(eBl,biN,bjN) = 1
310 IF ( southCommMode.EQ.COMM_GET ) northRecvAck(eBl,biS,bjS) = 1
311 IF ( northCommMode.EQ.COMM_GET ) southRecvAck(eBl,biN,bjN) = 1
312 ENDDO
313 ENDDO
314
315 C-- Make sure "ack" setting is seen system-wide.
316 C Here strong-ordering is not an issue but we want to make
317 C sure that processes that might spin on the above Ack settings
318 C will see the setting.
319 C ** NOTE ** On some machines we wont spin on the Ack setting
320 C ( particularly the T90 ), instead we will use s system barrier.
321 C On the T90 the system barrier is very fast and switches out the
322 C thread while it waits. On most machines the system barrier
323 C is much too slow and if we own the machine and have one thread
324 C per process preemption is not a problem.
325 IF ( exchNeedsMemSync ) CALL MEMSYNC
326
327 C Wait until all threads finish filling buffer
328 _BARRIER
329
330 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
331
332 #ifdef ALLOW_USE_MPI
333 #ifndef ALWAYS_USE_MPI
334 IF ( usingMPI ) THEN
335 #endif
336 C-- Send buffer data: Only Master Thread do proc communication
337 _BEGIN_MASTER(myThid)
338
339 DO bj=1,nSy
340 DO bi=1,nSx
341
342 eBl = exchangeBufLevel(1,bi,bj)
343 southCommMode = _tileCommModeS(bi,bj)
344 northCommMode = _tileCommModeN(bi,bj)
345 biS = _tileBiS(bi,bj)
346 bjS = _tileBjS(bi,bj)
347 biN = _tileBiN(bi,bj)
348 bjN = _tileBjN(bi,bj)
349 theType = _MPI_TYPE_RX
350 theSize = sNx*exchWidthY*myNz
351 IF ( theCornerMode .EQ. EXCH_UPDATE_CORNERS ) THEN
352 theSize = (sNx+2*exchWidthX)*exchWidthY*myNz
353 ENDIF
354
355 IF ( southCommMode .EQ. COMM_MSG ) THEN
356 C Send buffer data (copied from south edge)
357 theProc = tilePidS(bi,bj)
358 theTag = _tileTagSendS(bi,bj)
359 # ifndef ALLOW_AUTODIFF_OPENAD_AMPI
360 exchNreqsY(1,bi,bj) = exchNreqsY(1,bi,bj)+1
361 CALL MPI_Isend( southSendBuf_RX(1,eBl,bi,bj), theSize,
362 & theType, theProc, theTag, MPI_COMM_MODEL,
363 & exchReqIdY(exchNreqsY(1,bi,bj),1,bi,bj),
364 & mpiRc )
365 # else
366 pReqI=exchNReqsY(1,bi,bj)+1
367 CALL ampi_isend_RX(
368 & southSendBuf_RX(1,eBl,bi,bj),
369 & theSize,
370 & theType,
371 & theProc,
372 & theTag,
373 & MPI_COMM_MODEL,
374 & exchReqIdY(pReqI,1,bi,bj),
375 & exchNReqsY(1,bi,bj),
376 & mpiStatus,
377 & mpiRc )
378 # endif /* ALLOW_AUTODIFF_OPENAD_AMPI */
379 c northRecvAck(eBl,biS,bjS) = 1
380 ENDIF
381
382 IF ( northCommMode .EQ. COMM_MSG ) THEN
383 C Send buffer data (copied from north edge)
384 theProc = tilePidN(bi,bj)
385 theTag = _tileTagSendN(bi,bj)
386 #ifndef ALLOW_AUTODIFF_OPENAD_AMPI
387 exchNreqsY(1,bi,bj) = exchNreqsY(1,bi,bj)+1
388 CALL MPI_Isend( northSendBuf_RX(1,eBl,bi,bj), theSize,
389 & theType, theProc, theTag, MPI_COMM_MODEL,
390 & exchReqIdY(exchNreqsY(1,bi,bj),1,bi,bj),
391 & mpiRc )
392 # else
393 pReqI=exchNReqsY(1,bi,bj)+1
394 CALL ampi_isend_RX(
395 & northSendBuf_RX(1,eBl,bi,bj) ,
396 & theSize ,
397 & theType ,
398 & theProc ,
399 & theTag ,
400 & MPI_COMM_MODEL ,
401 & exchReqIdY(pReqI,1,bi,bj) ,
402 & exchNReqsY(1,bi,bj) ,
403 & mpiStatus ,
404 & mpiRc )
405 # endif /* ALLOW_AUTODIFF_OPENAD_AMPI */
406 c southRecvAck(eBl,biN,bjN) = 1
407 ENDIF
408
409 ENDDO
410 ENDDO
411
412 _END_MASTER(myThid)
413
414 #ifndef ALWAYS_USE_MPI
415 ENDIF
416 #endif
417 #endif /* ALLOW_USE_MPI */
418
419 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
420
421 RETURN
422 END

  ViewVC Help
Powered by ViewVC 1.1.22