/[MITgcm]/MITgcm/pkg/flt/exch_send_put_vec.F
ViewVC logotype

Annotation of /MITgcm/pkg/flt/exch_send_put_vec.F

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


Revision 1.8 - (hide annotations) (download)
Wed Aug 31 21:35:11 2011 UTC (12 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63g, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63c
Changes since 1.7: +36 -16 lines
make FLT EXCH working with multi-threads (and MPI + multi-threads)

1 jmc 1.8 C $Header: /u/gcmpack/MITgcm/pkg/flt/exch_send_put_vec.F,v 1.7 2009/03/26 22:21:11 cnh Exp $
2 jmc 1.2 C $Name: $
3    
4 jmc 1.6 #include "CPP_EEOPTIONS.h"
5     #undef DBUG_EXCH_VEC
6 jmc 1.4
7     C-- Contents
8     C-- o EXCH_RL_SEND_PUT_VEC_X
9     C-- o EXCH_RL_SEND_PUT_VEC_Y
10    
11     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
12 jmc 1.6 CBOP 0
13     C !ROUTINE: EXCH_RL_SEND_PUT_VEC_X
14 adcroft 1.1
15 jmc 1.6 C !INTERFACE:
16 jmc 1.5 SUBROUTINE EXCH_RL_SEND_PUT_VEC_X(
17     I arrayE, arrayW,
18     O bufRecE, bufRecW,
19     I myd1, myThid )
20 jmc 1.6 C !DESCRIPTION:
21     C *==========================================================*
22     C | SUBROUTINE EXCH_RL_SEND_PUT_VEC_X
23     C | o "Send" or "put" X edges for RL array.
24     C *==========================================================*
25     C | Routine that invokes actual message passing send or
26 jmc 1.8 C | direct "put" of data to update buffer in X direction
27     C | Note: Since only master-thread send/put, assumes input
28     C | & output arrays are shared (i.e. incommon block)
29 jmc 1.6 C *==========================================================*
30    
31     C !USES:
32 adcroft 1.1 IMPLICIT NONE
33    
34     C == Global variables ==
35     #include "SIZE.h"
36     #include "EEPARAMS.h"
37     #include "EESUPPORT.h"
38     #include "EXCH.h"
39 jmc 1.6
40     C !INPUT/OUTPUT PARAMETERS:
41     C arrayE :: Input buffer array to send to Eastern Neighbour
42     C arrayW :: Input buffer array to send to Western Neighbour
43     C bufRecE :: buffer array to collect Eastern Neighbour values
44     C bufRecW :: buffer array to collect Western Neighbour values
45     C myd1 :: size
46     C myThid :: my Thread Id. number
47 adcroft 1.1 INTEGER myd1
48 jmc 1.5 _RL arrayE(myd1,nSx,nSy), arrayW(myd1,nSx,nSy)
49     _RL bufRecE(myd1,nSx,nSy), bufRecW(myd1,nSx,nSy)
50 adcroft 1.1 INTEGER myThid
51 jmc 1.6 CEOP
52 adcroft 1.1
53 jmc 1.6 C !LOCAL VARIABLES:
54     C I :: Loop counters
55     C bi, bj :: tile indices
56     C biW, bjW :: West tile indices
57     C biE, bjE :: East tile indices
58 cnh 1.7 C theProc :: Variables used in message building
59     C theTag :: Variables used in message building
60     C theType :: Variables used in message building
61     C theSize :: Variables used in message building
62 jmc 1.6 C westCommMode :: variables holding type of communication
63     C eastCommMode :: a particular tile face uses.
64 jmc 1.4 INTEGER I
65 adcroft 1.1 INTEGER bi, bj, biW, bjW, biE, bjE
66     INTEGER westCommMode
67     INTEGER eastCommMode
68     #ifdef ALLOW_USE_MPI
69     INTEGER theProc, theTag, theType, theSize, mpiRc
70     #endif
71 jmc 1.6 #ifdef DBUG_EXCH_VEC
72     INTEGER ioUnit
73     #endif
74    
75     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
76 adcroft 1.1 C-- Write data to exchange buffer
77 jmc 1.2 C Various actions are possible depending on the communication mode
78 adcroft 1.1 C as follows:
79     C Mode Action
80     C -------- ---------------------------
81     C COMM_NONE Do nothing
82     C
83     C COMM_MSG Message passing communication ( e.g. MPI )
84     C Fill west send buffer from this tile.
85     C Send data with tag identifying tile and direction.
86     C Fill east send buffer from this tile.
87     C Send data with tag identifying tile and direction.
88     C
89     C COMM_PUT "Put" communication ( UMP_, shmemput, etc... )
90     C Fill east receive buffer of west-neighbor tile
91     C Fill west receive buffer of east-neighbor tile
92     C Sync. memory
93 jmc 1.8 C Write data-ready Ack for east edge of west-neighbor tile
94     C Write data-ready Ack for west edge of east-neighbor tile
95 adcroft 1.1 C Sync. memory
96 jmc 1.6
97 jmc 1.8 C Prevent anyone to access shared buffer while an other thread modifies it
98     _BARRIER
99    
100     _BEGIN_MASTER(myThid)
101    
102 jmc 1.6 #ifdef DBUG_EXCH_VEC
103     ioUnit = errorMessageUnit
104     WRITE(ioUnit,'(A,2L5)')
105     & 'SEND_PUT_X: exchNeedsMemsync,exchUsesBarrier=',
106     & exchNeedsMemsync,exchUsesBarrier
107     #endif
108    
109 jmc 1.8 DO bj=1,nSy
110     DO bi=1,nSx
111 adcroft 1.1
112     westCommMode = _tileCommModeW(bi,bj)
113     eastCommMode = _tileCommModeE(bi,bj)
114     biE = _tileBiE(bi,bj)
115     bjE = _tileBjE(bi,bj)
116     biW = _tileBiW(bi,bj)
117     bjW = _tileBjW(bi,bj)
118    
119     C o Send or Put west edge
120     IF ( westCommMode .EQ. COMM_MSG ) THEN
121     C Send the data
122     #ifdef ALLOW_USE_MPI
123     #ifndef ALWAYS_USE_MPI
124     IF ( usingMPI ) THEN
125     #endif
126     theProc = tilePidW(bi,bj)
127     theTag = _tileTagSendW(bi,bj)
128     theSize = myd1
129 jmc 1.6 theType = _MPI_TYPE_RL
130 adcroft 1.1 exchNReqsX(1,bi,bj) = exchNReqsX(1,bi,bj)+1
131 jmc 1.6 #ifdef DBUG_EXCH_VEC
132     write(ioUnit,'(A,7I5,I8)') 'qq1xW: ',myProcId,bi,bj,
133     & theProc,theTag, exchNReqsX(1,bi,bj),
134     & exchReqIdX(exchNReqsX(1,bi,bj),1,bi,bj), theSize
135     #endif
136 adcroft 1.1 CALL MPI_Isend(arrayW(1,bi,bj), theSize, theType,
137     & theProc, theTag, MPI_COMM_MODEL,
138     & exchReqIdX(exchNReqsX(1,bi,bj),1,bi,bj), mpiRc)
139     #ifndef ALWAYS_USE_MPI
140     ENDIF
141     #endif
142     #endif /* ALLOW_USE_MPI */
143 jmc 1.6 eastRecvAck(1,biW,bjW) = 1
144 adcroft 1.1 ELSEIF ( westCommMode .EQ. COMM_PUT ) THEN
145 jmc 1.5 c write(0,*) 'SEND_PUT_VEC_X: copy E:',biW,bjW,' <- W:',bi,bj
146 adcroft 1.1 DO I=1,myd1
147 jmc 1.5 bufRecE(I,biW,bjW) = arrayW(I,bi,bj)
148 adcroft 1.1 ENDDO
149 jmc 1.5 ELSEIF ( westCommMode .NE. COMM_NONE ) THEN
150 adcroft 1.1 STOP ' S/R EXCH: Invalid commW mode.'
151     ENDIF
152    
153     C o Send or Put east edge
154     IF ( eastCommMode .EQ. COMM_MSG ) THEN
155     C Send the data
156     #ifdef ALLOW_USE_MPI
157     #ifndef ALWAYS_USE_MPI
158     IF ( usingMPI ) THEN
159     #endif
160     theProc = tilePidE(bi,bj)
161     theTag = _tileTagSendE(bi,bj)
162     theSize = myd1
163 jmc 1.6 theType = _MPI_TYPE_RL
164 adcroft 1.1 exchNReqsX(1,bi,bj) = exchNReqsX(1,bi,bj)+1
165 jmc 1.6 #ifdef DBUG_EXCH_VEC
166 adcroft 1.1 c if (theProc .eq. 2 .or. theProc .eq. 4) then
167     c if (arrayE(1,bi,bj) .ne. 0.) then
168 jmc 1.6 write(ioUnit,'(A,7I5,I8)') 'qq1xE: ',myProcId,bi,bj,
169     & theProc,theTag, exchNReqsX(1,bi,bj),
170     & exchReqIdX(exchNReqsX(1,bi,bj),1,bi,bj), theSize
171 adcroft 1.1 c endif
172     c endif
173 jmc 1.6 #endif
174 adcroft 1.1 CALL MPI_Isend(arrayE(1,bi,bj), theSize, theType,
175     & theProc, theTag, MPI_COMM_MODEL,
176     & exchReqIdX(exchNReqsX(1,bi,bj),1,bi,bj), mpiRc)
177     #ifndef ALWAYS_USE_MPI
178     ENDIF
179     #endif
180     #endif /* ALLOW_USE_MPI */
181 jmc 1.6 westRecvAck(1,biE,bjE) = 1
182 adcroft 1.1 ELSEIF ( eastCommMode .EQ. COMM_PUT ) THEN
183 jmc 1.5 c write(0,*) 'SEND_PUT_VEC_X: copy W:',biE,bjE,' <- E:',bi,bj
184 adcroft 1.1 DO I=1,myd1
185 jmc 1.5 bufRecW(I,biE,bjE) = arrayE(I,bi,bj)
186 adcroft 1.1 ENDDO
187 jmc 1.5 ELSEIF ( eastCommMode .NE. COMM_NONE ) THEN
188 adcroft 1.1 STOP ' S/R EXCH: Invalid commE mode.'
189     ENDIF
190    
191     ENDDO
192     ENDDO
193    
194 jmc 1.8 _END_MASTER(myThid)
195    
196 adcroft 1.1 C-- Signal completetion ( making sure system-wide memory state is
197     C-- consistent ).
198    
199     C ** NOTE ** We are relying on being able to produce strong-ordered
200     C memory semantics here. In other words we assume that there is a
201     C mechanism which can ensure that by the time the Ack is seen the
202     C overlap region data that will be exchanged is up to date.
203     IF ( exchNeedsMemSync ) CALL MEMSYNC
204    
205     DO bj=myByLo(myThid),myByHi(myThid)
206     DO bi=myBxLo(myThid),myBxHi(myThid)
207     biE = _tileBiE(bi,bj)
208     bjE = _tileBjE(bi,bj)
209     biW = _tileBiW(bi,bj)
210     bjW = _tileBjW(bi,bj)
211     westCommMode = _tileCommModeW(bi,bj)
212     eastCommMode = _tileCommModeE(bi,bj)
213 jmc 1.6 IF ( westCommMode .EQ. COMM_PUT ) eastRecvAck(1,biW,bjW) = 1
214     IF ( eastCommMode .EQ. COMM_PUT ) westRecvAck(1,biE,bjE) = 1
215     IF ( westCommMode .EQ. COMM_GET ) eastRecvAck(1,biW,bjW) = 1
216     IF ( eastCommMode .EQ. COMM_GET ) westRecvAck(1,biE,bjE) = 1
217 adcroft 1.1 ENDDO
218     ENDDO
219    
220     C-- Make sure "ack" setting is seen system-wide.
221     C Here strong-ordering is not an issue but we want to make
222     C sure that processes that might spin on the above Ack settings
223     C will see the setting.
224     C ** NOTE ** On some machines we wont spin on the Ack setting
225     C ( particularly the T90 ), instead we will use s system barrier.
226 jmc 1.2 C On the T90 the system barrier is very fast and switches out the
227 adcroft 1.1 C thread while it waits. On most machines the system barrier
228     C is much too slow and if we own the machine and have one thread
229     C per process preemption is not a problem.
230     IF ( exchNeedsMemSync ) CALL MEMSYNC
231    
232 jmc 1.8 C Wait until all threads finish filling buffer <-- jmc: really needed ?
233     _BARRIER
234    
235 jmc 1.2 RETURN
236 adcroft 1.1 END
237    
238 jmc 1.4 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
239 jmc 1.6 CBOP 0
240     C !ROUTINE: EXCH_RL_SEND_PUT_VEC_Y
241 jmc 1.4
242 jmc 1.6 C !INTERFACE:
243 jmc 1.5 SUBROUTINE EXCH_RL_SEND_PUT_VEC_Y(
244     I arrayN, arrayS,
245     O bufRecN, bufRecS,
246     I myd1, myThid )
247 jmc 1.6 C !DESCRIPTION:
248     C *==========================================================*
249     C | SUBROUTINE EXCH_RL_SEND_PUT_VEC_Y
250     C | o "Send" or "put" Y edges for RL array.
251     C *==========================================================*
252     C | Routine that invokes actual message passing send or
253 jmc 1.8 C | direct "put" of data to update buffer in X direction
254     C | Note: Since only master-thread send/put, assumes input
255     C | & output arrays are shared (i.e. incommon block)
256 jmc 1.6 C *==========================================================*
257    
258     C !USES:
259 adcroft 1.1 IMPLICIT NONE
260    
261     C == Global variables ==
262     #include "SIZE.h"
263     #include "EEPARAMS.h"
264     #include "EESUPPORT.h"
265     #include "EXCH.h"
266 jmc 1.6
267     C !INPUT/OUTPUT PARAMETERS:
268     C arrayN :: buffer array to collect Northern Neighbour values
269     C arrayS :: buffer array to collect Southern Neighbour values
270     C myd1 :: size
271     C myThid :: my Thread Id. number
272     C arrayN :: Input buffer array to send to Northern Neighbour
273     C arrayS :: Input buffer array to send to Southern Neighbour
274     C bufRecN :: buffer array to collect Northern Neighbour values
275     C bufRecS :: buffer array to collect Southern Neighbour values
276     C myd1 :: size
277     C myThid :: my Thread Id. number
278 adcroft 1.1 INTEGER myd1
279 jmc 1.5 _RL arrayN(myd1,nSx,nSy), arrayS(myd1,nSx,nSy)
280     _RL bufRecN(myd1,nSx,nSy), bufRecS(myd1,nSx,nSy)
281 adcroft 1.1 INTEGER myThid
282 jmc 1.6 CEOP
283 adcroft 1.1
284 jmc 1.6 C !LOCAL VARIABLES:
285     C I :: Loop index
286     C bi, bj :: tile indices
287     C biS, bjS :: South tile indices
288     C biN, bjN :: North tile indices
289 cnh 1.7 C theProc :: Variables used in message building
290     C theTag :: Variables used in message building
291 jmc 1.8 C theType :: Variables used in message building
292 cnh 1.7 C theSize :: Variables used in message building
293 jmc 1.6 C southCommMode :: variables holding type of communication
294     C northCommMode :: a particular tile face uses.
295 jmc 1.4 INTEGER I
296 adcroft 1.1 INTEGER bi, bj, biS, bjS, biN, bjN
297     INTEGER southCommMode
298     INTEGER northCommMode
299     #ifdef ALLOW_USE_MPI
300     INTEGER theProc, theTag, theType, theSize, mpiRc
301     #endif
302 jmc 1.6 #ifdef DBUG_EXCH_VEC
303     INTEGER ioUnit
304     #endif
305    
306     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
307 adcroft 1.1 C-- Write data to exchange buffer
308 jmc 1.2 C Various actions are possible depending on the communication mode
309 adcroft 1.1 C as follows:
310     C Mode Action
311     C -------- ---------------------------
312     C COMM_NONE Do nothing
313     C
314     C COMM_MSG Message passing communication ( e.g. MPI )
315     C Fill west send buffer from this tile.
316     C Send data with tag identifying tile and direction.
317     C Fill east send buffer from this tile.
318     C Send data with tag identifying tile and direction.
319     C
320     C COMM_PUT "Put" communication ( UMP_, shmemput, etc... )
321     C Fill east receive buffer of south-neighbor tile
322     C Fill west receive buffer of north-neighbor tile
323     C Sync. memory
324 jmc 1.8 C Write data-ready Ack for east edge of south-neighbor tile
325     C Write data-ready Ack for west edge of north-neighbor tile
326 adcroft 1.1 C Sync. memory
327 jmc 1.6
328 jmc 1.8 C Prevent anyone to access shared buffer while an other thread modifies it
329     _BARRIER
330    
331     _BEGIN_MASTER(myThid)
332    
333 jmc 1.6 #ifdef DBUG_EXCH_VEC
334     ioUnit = errorMessageUnit
335     #endif
336    
337 jmc 1.8 DO bj=1,nSy
338     DO bi=1,nSx
339 adcroft 1.1
340     southCommMode = _tileCommModeS(bi,bj)
341     northCommMode = _tileCommModeN(bi,bj)
342     biN = _tileBiN(bi,bj)
343     bjN = _tileBjN(bi,bj)
344     biS = _tileBiS(bi,bj)
345     bjS = _tileBjS(bi,bj)
346    
347     C o Send or Put south edge
348     IF ( southCommMode .EQ. COMM_MSG ) THEN
349     C Send the data
350     #ifdef ALLOW_USE_MPI
351     #ifndef ALWAYS_USE_MPI
352     IF ( usingMPI ) THEN
353     #endif
354     theProc = tilePidS(bi,bj)
355     theTag = _tileTagSendS(bi,bj)
356     theSize = myd1
357 jmc 1.6 theType = _MPI_TYPE_RL
358 adcroft 1.1 exchNReqsY(1,bi,bj) = exchNReqsY(1,bi,bj)+1
359     CALL MPI_Isend(arrayS(1,bi,bj), theSize, theType,
360     & theProc, theTag, MPI_COMM_MODEL,
361     & exchReqIdY(exchNReqsY(1,bi,bj),1,bi,bj), mpiRc)
362     #ifndef ALWAYS_USE_MPI
363     ENDIF
364     #endif
365     #endif /* ALLOW_USE_MPI */
366 jmc 1.6 northRecvAck(1,biS,bjS) = 1
367 adcroft 1.1 ELSEIF ( southCommMode .EQ. COMM_PUT ) THEN
368 jmc 1.5 c write(0,*) 'SEND_PUT_VEC_Y: copy N:',biS,bjS,' <- S:',bi,bj
369 adcroft 1.1 DO I=1,myd1
370 jmc 1.5 bufRecN(I,biS,bjS) = arrayS(I,bi,bj)
371 adcroft 1.1 ENDDO
372 jmc 1.5 ELSEIF ( southCommMode .NE. COMM_NONE ) THEN
373 adcroft 1.1 STOP ' S/R EXCH: Invalid commS mode.'
374     ENDIF
375    
376     C o Send or Put north edge
377     IF ( northCommMode .EQ. COMM_MSG ) THEN
378     C Send the data
379     #ifdef ALLOW_USE_MPI
380     #ifndef ALWAYS_USE_MPI
381     IF ( usingMPI ) THEN
382     #endif
383     theProc = tilePidN(bi,bj)
384     theTag = _tileTagSendN(bi,bj)
385     theSize = myd1
386 jmc 1.6 theType = _MPI_TYPE_RL
387 adcroft 1.1 exchNReqsY(1,bi,bj) = exchNReqsY(1,bi,bj)+1
388     CALL MPI_Isend(arrayN(1,bi,bj), theSize, theType,
389     & theProc, theTag, MPI_COMM_MODEL,
390     & exchReqIdY(exchNReqsY(1,bi,bj),1,bi,bj), mpiRc)
391     #ifndef ALWAYS_USE_MPI
392     ENDIF
393     #endif
394     #endif /* ALLOW_USE_MPI */
395 jmc 1.6 southRecvAck(1,biN,bjN) = 1
396 adcroft 1.1 ELSEIF ( northCommMode .EQ. COMM_PUT ) THEN
397 jmc 1.5 c write(0,*) 'SEND_PUT_VEC_Y: copy S:',biN,bjN,' <- N:',bi,bj
398 adcroft 1.1 DO I=1,myd1
399 jmc 1.5 bufRecS(I,biN,bjN) = arrayN(I,bi,bj)
400 adcroft 1.1 ENDDO
401 jmc 1.5 ELSEIF ( northCommMode .NE. COMM_NONE ) THEN
402 adcroft 1.1 STOP ' S/R EXCH: Invalid commN mode.'
403     ENDIF
404    
405     ENDDO
406     ENDDO
407    
408 jmc 1.8 _END_MASTER(myThid)
409    
410 adcroft 1.1 C-- Signal completetion ( making sure system-wide memory state is
411     C-- consistent ).
412    
413     C ** NOTE ** We are relying on being able to produce strong-ordered
414     C memory semantics here. In other words we assume that there is a
415     C mechanism which can ensure that by the time the Ack is seen the
416     C overlap region data that will be exchanged is up to date.
417     IF ( exchNeedsMemSync ) CALL MEMSYNC
418    
419     DO bj=myByLo(myThid),myByHi(myThid)
420     DO bi=myBxLo(myThid),myBxHi(myThid)
421     biN = _tileBiN(bi,bj)
422     bjN = _tileBjN(bi,bj)
423     biS = _tileBiS(bi,bj)
424     bjS = _tileBjS(bi,bj)
425 jmc 1.6 southCommMode = _tileCommModeS(bi,bj)
426 adcroft 1.1 northCommMode = _tileCommModeN(bi,bj)
427 jmc 1.6 IF ( southCommMode .EQ. COMM_PUT ) northRecvAck(1,biS,bjS) = 1
428     IF ( northCommMode .EQ. COMM_PUT ) southRecvAck(1,biN,bjN) = 1
429     IF ( southCommMode .EQ. COMM_GET ) northRecvAck(1,biS,bjS) = 1
430     IF ( northCommMode .EQ. COMM_GET ) southRecvAck(1,biN,bjN) = 1
431 adcroft 1.1 ENDDO
432     ENDDO
433    
434     C-- Make sure "ack" setting is seen system-wide.
435     C Here strong-ordering is not an issue but we want to make
436     C sure that processes that might spin on the above Ack settings
437     C will see the setting.
438     C ** NOTE ** On some machines we wont spin on the Ack setting
439     C ( particularly the T90 ), instead we will use s system barrier.
440 jmc 1.2 C On the T90 the system barrier is very fast and switches out the
441 adcroft 1.1 C thread while it waits. On most machines the system barrier
442     C is much too slow and if we own the machine and have one thread
443     C per process preemption is not a problem.
444     IF ( exchNeedsMemSync ) CALL MEMSYNC
445    
446 jmc 1.8 C Wait until all threads finish filling buffer <-- jmc: really needed ?
447     _BARRIER
448    
449 jmc 1.2 RETURN
450 adcroft 1.1 END

  ViewVC Help
Powered by ViewVC 1.1.22