/[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.6 - (hide annotations) (download)
Fri Jan 9 21:08:27 2009 UTC (15 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i
Changes since 1.5: +123 -85 lines
- fix a bug (typo) in EXCH_RL_SEND_PUT_VEC_Y
- better type matching (use "_MPI_TYPE_RL", set & compare integer with integer)
- add some debug print
- just includes CPP_EEOPTIONS.h

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

  ViewVC Help
Powered by ViewVC 1.1.22