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

Annotation of /MITgcm/eesupp/src/exch_rx_recv_get_y.template

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


Revision 1.2 - (hide annotations) (download)
Fri Sep 21 03:55:50 2001 UTC (22 years, 8 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint46n_post, checkpoint51k_post, checkpoint47e_post, checkpoint44e_post, checkpoint46l_post, checkpoint46g_pre, checkpoint47c_post, release1_p13_pre, checkpoint50c_post, checkpoint46f_post, checkpoint48e_post, checkpoint50c_pre, checkpoint44f_post, checkpoint46b_post, checkpoint43a-release1mods, checkpoint51o_pre, ecco_c50_e32, ecco_c50_e33, ecco_c50_e30, ecco_c50_e31, release1_p13, checkpoint51l_post, checkpoint48i_post, checkpoint46l_pre, chkpt44d_post, checkpoint51, checkpoint50, checkpoint52, release1_p8, release1_p9, checkpoint50d_post, release1_p1, release1_p2, release1_p3, release1_p4, release1_p5, release1_p6, release1_p7, checkpoint50b_pre, checkpoint44e_pre, checkpoint51f_post, release1_b1, ecco_c51_e34d, ecco_c51_e34e, ecco_c51_e34f, ecco_c51_e34g, ecco_c51_e34a, ecco_c51_e34b, ecco_c51_e34c, checkpoint48b_post, checkpoint43, checkpoint51d_post, checkpoint48c_pre, checkpoint47d_pre, checkpoint51t_post, checkpoint51n_post, release1_chkpt44d_post, checkpoint51s_post, checkpoint47a_post, checkpoint48d_pre, checkpoint51j_post, checkpoint47i_post, release1_p11, checkpoint51n_pre, checkpoint47d_post, icebear5, icebear4, icebear3, icebear2, checkpoint46d_pre, checkpoint48d_post, release1-branch_tutorials, checkpoint48f_post, checkpoint45d_post, checkpoint46j_pre, checkpoint51l_pre, chkpt44a_post, checkpoint44h_pre, checkpoint48h_post, checkpoint51q_post, ecco_c50_e29, checkpoint51b_pre, checkpoint46a_post, checkpoint47g_post, checkpoint46j_post, checkpoint51h_pre, checkpoint46k_post, ecco_c50_e28, chkpt44c_pre, checkpoint48a_post, checkpoint45a_post, checkpoint50f_post, checkpoint50a_post, checkpoint50f_pre, ecco_c44_e19, ecco_c44_e18, ecco_c44_e17, ecco_c44_e16, release1_p12, release1_p10, release1_p16, release1_p17, release1_p14, release1_p15, checkpoint47j_post, ecco_c50_e33a, branch-exfmods-tag, checkpoint44g_post, branchpoint-genmake2, checkpoint46e_pre, checkpoint51r_post, checkpoint48c_post, checkpoint45b_post, checkpoint46b_pre, checkpoint51i_post, release1-branch-end, release1_final_v1, checkpoint51b_post, checkpoint51c_post, checkpoint46c_pre, checkpoint46, checkpoint47b_post, checkpoint44b_post, ecco_c51_e34, checkpoint46h_pre, checkpoint46m_post, checkpoint46a_pre, checkpoint50g_post, checkpoint45c_post, ecco_ice2, ecco_ice1, checkpoint44h_post, checkpoint46g_post, release1_p12_pre, ecco_c44_e22, checkpoint50h_post, checkpoint50e_pre, checkpoint50i_post, ecco_c44_e25, checkpoint51i_pre, checkpoint47f_post, checkpoint50e_post, chkpt44a_pre, checkpoint46i_post, ecco_c44_e23, ecco_c44_e20, ecco_c44_e21, ecco_c44_e26, ecco_c44_e27, ecco_c44_e24, checkpoint46c_post, ecco-branch-mod1, ecco-branch-mod2, ecco-branch-mod3, ecco-branch-mod4, ecco-branch-mod5, checkpoint50d_pre, checkpoint46e_post, release1_beta1, checkpoint51e_post, checkpoint44b_pre, checkpoint42, checkpoint41, checkpoint47, checkpoint44, checkpoint45, checkpoint48, checkpoint49, checkpoint46h_post, checkpoint51o_post, checkpoint51f_pre, chkpt44c_post, checkpoint48g_post, checkpoint47h_post, checkpoint44f_pre, checkpoint51g_post, ecco_c52_e35, checkpoint46d_post, checkpoint50b_post, release1-branch_branchpoint, checkpoint51m_post, checkpoint51a_post, checkpoint51p_post, checkpoint51u_post
Branch point for: c24_e25_ice, branch-exfmods-curt, release1_final, release1-branch, branch-genmake2, release1, branch-nonh, tg2-branch, ecco-branch, release1_50yr, icebear, checkpoint51n_branch, release1_coupled
Changes since 1.1: +38 -29 lines
Starting to bring comments up to date and format comments
for document extraction of "prototypes".

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

  ViewVC Help
Powered by ViewVC 1.1.22