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

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

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


Revision 1.4 - (hide annotations) (download)
Wed Jan 7 23:17:23 2009 UTC (15 years, 4 months ago) by jmc
Branch: MAIN
Changes since 1.3: +19 -66 lines
- improve criteria for finding which tile owns a float
- fix few Pb for case without MPI

1 jmc 1.4 C $Header: /u/gcmpack/MITgcm/pkg/flt/exch_recv_get_vec.F,v 1.3 2009/01/04 00:58:23 jmc Exp $
2 jmc 1.2 C $Name: $
3    
4 adcroft 1.1 #include "CPP_OPTIONS.h"
5 jmc 1.3
6     C-- Contents
7     C-- o EXCH_RL_RECV_GET_VEC_X
8     C-- o EXCH_RL_RECV_GET_VEC_Y
9    
10     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
11 adcroft 1.1
12 jmc 1.4 SUBROUTINE EXCH_RL_RECV_GET_VEC_X(
13     U arrayE, arrayW,
14     I myd1, myThid )
15 adcroft 1.1 C /==========================================================\
16     C | SUBROUTINE RECV_RL_GET_X |
17     C | o "Send" or "put" X edges for RL array. |
18     C |==========================================================|
19     C | Routine that invokes actual message passing send or |
20     C | direct "put" of data to update X faces of an XY[R] array.|
21     C \==========================================================/
22     IMPLICIT NONE
23    
24     C == Global variables ==
25     #include "SIZE.h"
26     #include "EEPARAMS.h"
27     #include "EESUPPORT.h"
28     #include "FLT.h"
29     #include "EXCH.h"
30    
31     C == Routine arguments ==
32     C arrayE - Arrays to exchange be exchanged.
33 jmc 1.2 C arrayW
34 adcroft 1.1 C myd1 - sizes.
35     C theSimulationMode - Forward or reverse mode exchange ( provides
36     C support for adjoint integration of code. )
37     C myThid - Thread number of this instance of S/R EXCH...
38     C eBl - Edge buffer level
39     INTEGER myd1
40     _RL arrayE(myd1, nSx, nSy), arrayW(myd1, nSx, nSy)
41     INTEGER myThid
42     CEndOfInterface
43    
44     C == Local variables ==
45     C I, J - Loop counters and extents
46     C bi, bj
47     C biW, bjW - West tile indices
48     C biE, bjE - East tile indices
49     C theProc, theTag, theType, - Variables used in message building
50     C theSize
51     C westCommMode - Working variables holding type
52     C eastCommMode of communication a particular
53     C tile face uses.
54 jmc 1.4 INTEGER bi, bj
55     c INTEGER biW, bjW, biE, bjE
56 adcroft 1.1 INTEGER westCommMode
57     INTEGER eastCommMode
58     INTEGER spinCount
59     #ifdef ALLOW_USE_MPI
60     INTEGER theProc, theTag, theType, theSize
61     INTEGER mpiStatus(MPI_STATUS_SIZE,4), mpiRc
62     #endif
63    
64    
65 jmc 1.2 C-- Under a "put" scenario we
66 adcroft 1.1 C-- i. set completetion signal for buffer we put into.
67 jmc 1.2 C-- ii. wait for completetion signal indicating data has been put in
68 adcroft 1.1 C-- our buffer.
69     C-- Under a messaging mode we "receive" the message.
70     C-- Under a "get" scenario we
71     C-- i. Check that the data is ready.
72     C-- ii. Read the data.
73     C-- iii. Set data read flag + memory sync.
74    
75    
76     DO bj=myByLo(myThid),myByHi(myThid)
77     DO bi=myBxLo(myThid),myBxHi(myThid)
78     westCommMode = _tileCommModeW(bi,bj)
79     eastCommMode = _tileCommModeE(bi,bj)
80 jmc 1.4 c biE = _tileBiE(bi,bj)
81     c bjE = _tileBjE(bi,bj)
82     c biW = _tileBiW(bi,bj)
83     c bjW = _tileBjW(bi,bj)
84 adcroft 1.1 IF ( westCommMode .EQ. COMM_MSG ) THEN
85     #ifdef ALLOW_USE_MPI
86     #ifndef ALWAYS_USE_MPI
87     IF ( usingMPI ) THEN
88     #endif
89     theProc = tilePidW(bi,bj)
90     theTag = _tileTagRecvW(bi,bj)
91     theType = MPI_DOUBLE_PRECISION
92     theSize = myd1
93     CALL MPI_Recv( arrayW(1,bi,bj), theSize, theType,
94     & theProc, theTag, MPI_COMM_MODEL,
95     & mpiStatus, mpiRc )
96     c if (theProc .eq. 0 .or. theProc .eq. 2) then
97     c if (arrayW(1,bi,bj) .ne. 0.) then
98     c write(errormessageunit,*) 'qq2y: ',myprocid,
99     c & theProc,theTag,theSize,(arrayW(i,bi,bj),i=1,32)
100     c else
101     c write(errormessageunit,*) 'qq2n: ',myprocid,
102     c & theProc,theTag,theSize,(arrayW(i,bi,bj),i=1,32)
103     c endif
104     c endif
105     #ifndef ALWAYS_USE_MPI
106 jmc 1.2 ENDIF
107 adcroft 1.1 #endif
108     #endif /* ALLOW_USE_MPI */
109     ENDIF
110     IF ( eastCommMode .EQ. COMM_MSG ) THEN
111     #ifdef ALLOW_USE_MPI
112     #ifndef ALWAYS_USE_MPI
113     IF ( usingMPI ) THEN
114     #endif
115     theProc = tilePidE(bi,bj)
116     theTag = _tileTagRecvE(bi,bj)
117     theType = MPI_DOUBLE_PRECISION
118     theSize = myd1
119     CALL MPI_Recv( arrayE(1,bi,bj), theSize, theType,
120     & theProc, theTag, MPI_COMM_MODEL,
121     & mpiStatus, mpiRc )
122     #ifndef ALWAYS_USE_MPI
123 jmc 1.2 ENDIF
124 adcroft 1.1 #endif
125     #endif /* ALLOW_USE_MPI */
126     ENDIF
127     ENDDO
128     ENDDO
129    
130     C-- Wait for buffers I am going read to be ready.
131     IF ( exchUsesBarrier ) THEN
132     C o On some machines ( T90 ) use system barrier rather than spinning.
133     CALL BARRIER( myThid )
134     ELSE
135     C o Spin waiting for completetion flag. This avoids a global-lock
136     C i.e. we only lock waiting for data that we need.
137     DO bj=myByLo(myThid),myByHi(myThid)
138     DO bi=myBxLo(myThid),myBxHi(myThid)
139     spinCount = 0
140     westCommMode = _tileCommModeW(bi,bj)
141     eastCommMode = _tileCommModeE(bi,bj)
142     10 CONTINUE
143     CALL FOOL_THE_COMPILER
144     spinCount = spinCount+1
145     C IF ( myThid .EQ. 1 .AND. spinCount .GT. _EXCH_SPIN_LIMIT ) THEN
146     C WRITE(0,*) ' eBl = ', ebl
147     C STOP ' S/R EXCH_RECV_GET_X: spinCount .GT. _EXCH_SPIN_LIMIT'
148     C ENDIF
149     IF ( westRecvAck(1,bi,bj) .EQ. 0. ) GOTO 10
150     IF ( eastRecvAck(1,bi,bj) .EQ. 0. ) GOTO 10
151     C Clear outstanding requests
152     westRecvAck(1,bi,bj) = 0.
153     eastRecvAck(1,bi,bj) = 0.
154    
155     c IF ( exchVReqsX(1,bi,bj) .GT. 0 ) THEN
156     IF ( exchNReqsX(1,bi,bj) .GT. 0 ) THEN
157     #ifdef ALLOW_USE_MPI
158     #ifndef ALWAYS_USE_MPI
159     IF ( usingMPI ) THEN
160     #endif
161     c CALL MPI_Waitall( exchVReqsX(1,bi,bj), exchReqVIdX(1,1,bi,bj),
162     CALL MPI_Waitall( exchNReqsX(1,bi,bj), exchReqIdX(1,1,bi,bj),
163     & mpiStatus, mpiRC )
164     #ifndef ALWAYS_USE_MPI
165 jmc 1.2 ENDIF
166 adcroft 1.1 #endif
167     #endif /* ALLOW_USE_MPI */
168     ENDIF
169     C Clear outstanding requests counter
170     c exchVReqsX(1,bi,bj) = 0
171     exchNReqsX(1,bi,bj) = 0
172     C Update statistics
173     ENDDO
174     ENDDO
175     ENDIF
176    
177     RETURN
178     END
179    
180 jmc 1.3 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
181 adcroft 1.1
182 jmc 1.4 SUBROUTINE EXCH_RL_RECV_GET_VEC_Y(
183     U arrayN, arrayS,
184     I myd1, myThid )
185 adcroft 1.1 C /==========================================================\
186     C | SUBROUTINE RECV_RL_GET_Y |
187     C | o "Send" or "put" Y edges for RL array. |
188     C |==========================================================|
189     C | Routine that invokes actual message passing send or |
190     C | direct "put" of data to update Y faces of an XY[R] array.|
191     C \==========================================================/
192     IMPLICIT NONE
193    
194     C == Global variables ==
195     #include "SIZE.h"
196     #include "EEPARAMS.h"
197     #include "EESUPPORT.h"
198     #include "FLT.h"
199     #include "EXCH.h"
200    
201     C == Routine arguments ==
202     C arrayN - Arrays to exchange be exchanged.
203 jmc 1.2 C arrayS
204 adcroft 1.1 C myd1 - sizes.
205     C theSimulationMode - Forward or reverse mode exchange ( provides
206     C support for adjoint integration of code. )
207     C myThid - Thread number of this instance of S/R EXCH...
208     INTEGER myd1
209     _RL arrayN(myd1, nSx, nSy), arrayS(myd1, nSx, nSy)
210     INTEGER myThid
211     CEndOfInterface
212    
213     C == Local variables ==
214     C I, J - Loop counters and extents
215     C bi, bj
216     C biS, bjS - South tile indices
217     C biE, bjE - North tile indices
218     C theProc, theTag, theType, - Variables used in message building
219     C theSize
220     C southCommMode - Working variables holding type
221     C northCommMode of communication a particular
222     C tile face uses.
223 jmc 1.4 INTEGER bi, bj
224     c INTEGER biS, bjS, biN, bjN
225 adcroft 1.1 INTEGER southCommMode
226     INTEGER northCommMode
227     INTEGER spinCount
228     #ifdef ALLOW_USE_MPI
229     INTEGER theProc, theTag, theType, theSize
230     INTEGER mpiStatus(MPI_STATUS_SIZE,4), mpiRc
231     #endif
232    
233    
234 jmc 1.2 C-- Under a "put" scenario we
235 adcroft 1.1 C-- i. set completetion signal for buffer we put into.
236 jmc 1.2 C-- ii. wait for completetion signal indicating data has been put in
237 adcroft 1.1 C-- our buffer.
238     C-- Under a messaging mode we "receive" the message.
239     C-- Under a "get" scenario we
240     C-- i. Check that the data is ready.
241     C-- ii. Read the data.
242     C-- iii. Set data read flag + memory sync.
243    
244    
245     DO bj=myByLo(myThid),myByHi(myThid)
246     DO bi=myBxLo(myThid),myBxHi(myThid)
247     southCommMode = _tileCommModeS(bi,bj)
248     northCommMode = _tileCommModeN(bi,bj)
249 jmc 1.4 c biN = _tileBiN(bi,bj)
250     c bjN = _tileBjN(bi,bj)
251     c biS = _tileBiS(bi,bj)
252     c bjS = _tileBjS(bi,bj)
253 adcroft 1.1 IF ( southCommMode .EQ. COMM_MSG ) THEN
254     #ifdef ALLOW_USE_MPI
255     #ifndef ALWAYS_USE_MPI
256     IF ( usingMPI ) THEN
257     #endif
258     theProc = tilePidS(bi,bj)
259     theTag = _tileTagRecvS(bi,bj)
260     theType = MPI_DOUBLE_PRECISION
261     theSize = myd1
262     CALL MPI_Recv( arrayS(1,bi,bj), theSize, theType,
263     & theProc, theTag, MPI_COMM_MODEL,
264     & mpiStatus, mpiRc )
265     #ifndef ALWAYS_USE_MPI
266 jmc 1.2 ENDIF
267 adcroft 1.1 #endif
268     #endif /* ALLOW_USE_MPI */
269     ENDIF
270     IF ( northCommMode .EQ. COMM_MSG ) THEN
271     #ifdef ALLOW_USE_MPI
272     #ifndef ALWAYS_USE_MPI
273     IF ( usingMPI ) THEN
274     #endif
275     theProc = tilePidN(bi,bj)
276     theTag = _tileTagRecvN(bi,bj)
277     theType = MPI_DOUBLE_PRECISION
278     theSize = myd1
279     CALL MPI_Recv( arrayN(1,bi,bj), theSize, theType,
280     & theProc, theTag, MPI_COMM_MODEL,
281     & mpiStatus, mpiRc )
282     #ifndef ALWAYS_USE_MPI
283 jmc 1.2 ENDIF
284 adcroft 1.1 #endif
285     #endif /* ALLOW_USE_MPI */
286     ENDIF
287     ENDDO
288     ENDDO
289    
290     C-- Wait for buffers I am going read to be ready.
291     IF ( exchUsesBarrier ) THEN
292     C o On some machines ( T90 ) use system barrier rather than spinning.
293     CALL BARRIER( myThid )
294     ELSE
295     C o Spin waiting for completetion flag. This avoids a global-lock
296     C i.e. we only lock waiting for data that we need.
297     DO bj=myByLo(myThid),myByHi(myThid)
298     DO bi=myBxLo(myThid),myBxHi(myThid)
299     spinCount = 0
300     southCommMode = _tileCommModeS(bi,bj)
301     northCommMode = _tileCommModeN(bi,bj)
302     10 CONTINUE
303     CALL FOOL_THE_COMPILER
304     spinCount = spinCount+1
305     C IF ( myThid .EQ. 1 .AND. spinCount .GT. _EXCH_SPIN_LIMIT ) THEN
306     C WRITE(0,*) ' eBl = ', ebl
307     C STOP ' S/R EXCH_RECV_GET_X: spinCount .GT. _EXCH_SPIN_LIMIT'
308     C ENDIF
309     IF ( southRecvAck(1,bi,bj) .EQ. 0. ) GOTO 10
310     IF ( northRecvAck(1,bi,bj) .EQ. 0. ) GOTO 10
311     C Clear outstanding requests
312     southRecvAck(1,bi,bj) = 0.
313     northRecvAck(1,bi,bj) = 0.
314    
315     c IF ( exchVReqsY(1,bi,bj) .GT. 0 ) THEN
316     IF ( exchNReqsY(1,bi,bj) .GT. 0 ) THEN
317     #ifdef ALLOW_USE_MPI
318     #ifndef ALWAYS_USE_MPI
319     IF ( usingMPI ) THEN
320     #endif
321     c CALL MPI_Waitall( exchVReqsY(1,bi,bj), exchReqVIdY(1,1,bi,bj),
322     CALL MPI_Waitall( exchNReqsY(1,bi,bj), exchReqIdY(1,1,bi,bj),
323     & mpiStatus, mpiRC )
324     #ifndef ALWAYS_USE_MPI
325 jmc 1.2 ENDIF
326 adcroft 1.1 #endif
327     #endif /* ALLOW_USE_MPI */
328     ENDIF
329     C Clear outstanding requests counter
330     c exchVReqsY(1,bi,bj) = 0
331     exchNReqsY(1,bi,bj) = 0
332     C Update statistics
333     ENDDO
334     ENDDO
335     ENDIF
336    
337     RETURN
338     END

  ViewVC Help
Powered by ViewVC 1.1.22