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

Annotation 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.1 - (hide annotations) (download)
Tue May 29 14:06:38 2001 UTC (23 years ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint40pre3, checkpoint40pre1, checkpoint40pre7, checkpoint40pre6, checkpoint40pre9, checkpoint40pre8, checkpoint40pre2, checkpoint40pre4, checkpoint40pre5, checkpoint40
Merge from branch pre38 :
 o Templating of exch* routines.

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

  ViewVC Help
Powered by ViewVC 1.1.22