/[MITgcm]/MITgcm/pkg/exch2/exch2_rx2_cube_ad.template
ViewVC logotype

Annotation of /MITgcm/pkg/exch2/exch2_rx2_cube_ad.template

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


Revision 1.8 - (hide annotations) (download)
Mon Jun 29 23:46:50 2009 UTC (14 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62e, checkpoint62d, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61s, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.7: +10 -12 lines
remove last BARRIER (no need to synchronise after getting data from shared
 buffer (get) as long as any change to buffer (put,recv) is between BARRIER)

1 jmc 1.8 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_rx2_cube_ad.template,v 1.7 2009/06/28 01:00:23 jmc Exp $
2 heimbach 1.1 C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5 jmc 1.6 #undef LOCAL_DBUG
6 heimbach 1.1
7     CBOP
8 jmc 1.6 C !ROUTINE: EXCH_RX2_CUBE_AD
9 heimbach 1.1
10     C !INTERFACE:
11 jmc 1.3 SUBROUTINE EXCH2_RX2_CUBE_AD(
12 jmc 1.6 U array1, array2,
13     I signOption, fieldCode,
14 heimbach 1.1 I myOLw, myOLe, myOLn, myOLs, myNz,
15     I exchWidthX, exchWidthY,
16     I simulationMode, cornerMode, myThid )
17    
18     C !DESCRIPTION:
19 jmc 1.6 C Two components vector field AD-Exchange:
20     C Tile-edge overlap-region of a 2 component vector field is added to
21     C corresponding near-edge interior data point and then zero out.
22 heimbach 1.1
23     C !USES:
24 jmc 1.6 IMPLICIT NONE
25    
26 heimbach 1.1 C == Global data ==
27     #include "SIZE.h"
28     #include "EEPARAMS.h"
29     #include "EESUPPORT.h"
30 jmc 1.5 #include "W2_EXCH2_SIZE.h"
31 heimbach 1.1 #include "W2_EXCH2_TOPOLOGY.h"
32 jmc 1.5 #include "W2_EXCH2_BUFFER.h"
33 heimbach 1.1
34     C !INPUT/OUTPUT PARAMETERS:
35 jmc 1.6 C array1 :: 1rst component array with edges to exchange.
36     C array2 :: 2nd component array with edges to exchange.
37     C signOption :: Flag controlling whether vector is signed.
38     C fieldCode :: field code (position on staggered grid)
39     C myOLw,myOLe :: West and East overlap region sizes.
40     C myOLn,myOLs :: North and South overlap region sizes.
41     C exchWidthX :: Width of data region exchanged in X.
42     C exchWidthY :: Width of data region exchanged in Y.
43     C cornerMode :: halo-corner-region treatment: update/ignore corner region
44     C myThid :: Thread number of this instance of S/R EXCH...
45    
46     INTEGER myOLw, myOLe, myOLn, myOLs, myNz
47     _RX array1(1-myOLw:sNx+myOLe,
48     & 1-myOLs:sNy+myOLn,
49     & myNz, nSx, nSy)
50     _RX array2(1-myOLw:sNx+myOLe,
51     & 1-myOLs:sNy+myOLn,
52     & myNz, nSx, nSy)
53     LOGICAL signOption
54 heimbach 1.1 CHARACTER*2 fieldCode
55     INTEGER exchWidthX
56     INTEGER exchWidthY
57     INTEGER simulationMode
58     INTEGER cornerMode
59     INTEGER myThid
60    
61     C !LOCAL VARIABLES:
62 jmc 1.6 C e2_msgHandles :: Synchronization and coordination data structure used to
63     C :: coordinate access to e2Bufr1_RX or to regulate message
64     C :: buffering. In PUT communication sender will increment
65     C :: handle entry once data is ready in buffer. Receiver will
66     C :: decrement handle once data is consumed from buffer.
67     C :: For MPI MSG communication MPI_Wait uses hanlde to check
68     C :: Isend has cleared. This is done in routine after receives.
69     C note: a) current implementation does not use e2_msgHandles for communication
70     C between threads: all-threads barriers are used (see CNH note below).
71     C For a 2-threads synchro communication (future version),
72     C e2_msgHandles should be shared (in common block, moved to BUFFER.h)
73     INTEGER bi, bj
74 heimbach 1.1 C Variables for working through W2 topology
75 jmc 1.6 INTEGER e2_msgHandles( 2, W2_maxNeighbours, nSx, nSy )
76 heimbach 1.1 INTEGER thisTile, farTile, N, nN, oN
77 jmc 1.3 INTEGER tIlo1, tIhi1, tJlo1, tJhi1, oIs1, oJs1
78     INTEGER tIlo2, tIhi2, tJlo2, tJhi2, oIs2, oJs2
79     INTEGER tIStride, tJStride
80     INTEGER tKlo, tKhi, tKStride
81 heimbach 1.1 INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
82     INTEGER i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi
83    
84 jmc 1.6 #ifdef ALLOW_USE_MPI
85     INTEGER iBufr1, iBufr2, nri, nrj
86 heimbach 1.1 C MPI stuff (should be in a routine call)
87     INTEGER mpiStatus(MPI_STATUS_SIZE)
88     INTEGER mpiRc
89     INTEGER wHandle
90     #endif
91     CEOP
92    
93 jmc 1.6 C- Tile size of arrays to exchange:
94     i1Lo = 1-myOLw
95     i1Hi = sNx+myOLe
96     j1Lo = 1-myOLs
97     j1Hi = sNy+myOLn
98     k1Lo = 1
99     k1Hi = myNz
100     i2Lo = 1-myOLw
101     i2Hi = sNx+myOLe
102     j2Lo = 1-myOLs
103     j2Hi = sNy+myOLn
104     k2Lo = 1
105     k2Hi = myNz
106 heimbach 1.1
107 jmc 1.8 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
108    
109     C Prevent anyone to access shared buffer while an other thread modifies it
110 heimbach 1.1 CALL BAR2( myThid )
111    
112 jmc 1.6 C-- Extract from buffer (either from level 1 if local exch,
113     C or level 2 if coming from an other Proc)
114     C AD: = fill buffer from my-tile-edge overlap-region, level 1 or 2 depending
115     C AD: on local (to this Proc) or remote Proc tile destination
116     DO bj=myByLo(myThid), myByHi(myThid)
117     DO bi=myBxLo(myThid), myBxHi(myThid)
118 jmc 1.7 thisTile=W2_myTileList(bi,bj)
119 jmc 1.6 nN=exch2_nNeighbours(thisTile)
120     DO N=1,nN
121     CALL EXCH2_GET_UV_BOUNDS(
122     I fieldCode, exchWidthX,
123     I thisTile, N,
124     O tIlo1, tIhi1, tJlo1, tJhi1,
125     O tIlo2, tIhi2, tJlo2, tJhi2,
126     O tiStride, tjStride,
127     O oIs1, oJs1, oIs2, oJs2,
128     I myThid )
129     tKLo=1
130     tKHi=myNz
131     tKStride=1
132    
133     C From buffer, get my points
134     C (tIlo:tIhi:tiStride,tJlo:tJhi,tJStride,tKlo:tKhi,tKStride) in "array1,2":
135     C Note: when transferring data within a process:
136     C o e2Bufr entry to read is entry associated with opposing send record
137     C o e2_msgHandle entry to read is entry associated with opposing send record.
138     CALL EXCH2_AD_GET_RX2(
139     I tIlo1, tIhi1, tIlo2, tIhi2, tiStride,
140     I tJlo1, tJhi1, tJlo2, tJhi2, tjStride,
141     I tKlo, tKhi, tkStride,
142     I thisTile, N, bi, bj,
143     I e2BufrRecSize, W2_maxNeighbours, nSx, nSy,
144 jmc 1.7 O iBuf1Filled(N,bi,bj), iBuf2Filled(N,bi,bj),
145 jmc 1.6 O e2Bufr1_RX, e2Bufr2_RX,
146     U array1(1-myOLw,1-myOLs,1,bi,bj),
147     U array2(1-myOLw,1-myOLs,1,bi,bj),
148     I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
149     I i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,
150     U e2_msgHandles,
151 jmc 1.7 I W2_myCommFlag(N,bi,bj), myThid )
152 jmc 1.6 ENDDO
153 heimbach 1.1 ENDDO
154     ENDDO
155    
156 jmc 1.8 C Wait until all threads finish filling buffer
157     CALL BAR2( myThid )
158    
159 jmc 1.6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
160    
161     #ifdef ALLOW_USE_MPI
162     C AD: all MPI part is acting on buffer and is identical to forward code,
163     C AD: except a) the buffer level: send from lev.2, receive into lev.1
164     C AD: b) the length of transfered buffer (<- match the ad_put/ad_get)
165    
166     _BEGIN_MASTER( myThid )
167    
168     C-- Send my data (in buffer, level 1) to target Process
169     DO bj=1,nSy
170     DO bi=1,nSx
171 jmc 1.7 thisTile=W2_myTileList(bi,bj)
172 jmc 1.6 nN=exch2_nNeighbours(thisTile)
173     DO N=1,nN
174     C- Skip the call if this is an internal exchange
175 jmc 1.7 IF ( W2_myCommFlag(N,bi,bj) .EQ. 'M' ) THEN
176 jmc 1.6 CALL EXCH2_SEND_RX2(
177     I thisTile, N,
178     I e2BufrRecSize,
179 jmc 1.7 I iBuf1Filled(N,bi,bj), iBuf2Filled(N,bi,bj),
180     I e2Bufr1_RX(1,N,bi,bj,2), e2Bufr2_RX(1,N,bi,bj,2),
181 jmc 1.6 O e2_msgHandles(1,N,bi,bj),
182 jmc 1.7 I W2_myCommFlag(N,bi,bj), myThid )
183 jmc 1.6 ENDIF
184     ENDDO
185     ENDDO
186     ENDDO
187    
188     C-- Receive data (in buffer, level 1) from source Process
189     DO bj=1,nSy
190     DO bi=1,nSx
191 jmc 1.7 thisTile=W2_myTileList(bi,bj)
192 jmc 1.6 nN=exch2_nNeighbours(thisTile)
193     DO N=1,nN
194     C- Skip the call if this is an internal exchange
195 jmc 1.7 IF ( W2_myCommFlag(N,bi,bj) .EQ. 'M' ) THEN
196 jmc 1.6 farTile=exch2_neighbourId(N,thisTile)
197     oN = exch2_opposingSend(N,thisTile)
198     CALL EXCH2_GET_UV_BOUNDS(
199     I fieldCode, exchWidthX,
200     I farTile, oN,
201     O tIlo1, tIhi1, tJlo1, tJhi1,
202     O tIlo2, tIhi2, tJlo2, tJhi2,
203     O tiStride, tjStride,
204     O oIs1, oJs1, oIs2, oJs2,
205     I myThid )
206     nri = 1 + (tIhi1-tIlo1)/tiStride
207     nrj = 1 + (tJhi1-tJlo1)/tjStride
208     iBufr1 = nri*nrj*myNz
209     nri = 1 + (tIhi2-tIlo2)/tiStride
210     nrj = 1 + (tJhi2-tJlo2)/tjStride
211     iBufr2 = nri*nrj*myNz
212     C Receive from neighbour N to fill buffer and later on the array
213     CALL EXCH2_RECV_RX2(
214     I thisTile, N,
215     I e2BufrRecSize,
216     I iBufr1, iBufr2,
217 jmc 1.7 I e2Bufr1_RX(1,N,bi,bj,1), e2Bufr2_RX(1,N,bi,bj,1),
218     I W2_myCommFlag(N,bi,bj), myThid )
219 jmc 1.6 ENDIF
220     ENDDO
221     ENDDO
222     ENDDO
223 heimbach 1.1
224 jmc 1.6 C-- Clear message handles/locks
225     DO bj=1,nSy
226     DO bi=1,nSx
227 jmc 1.7 thisTile=W2_myTileList(bi,bj)
228 jmc 1.6 nN=exch2_nNeighbours(thisTile)
229     DO N=1,nN
230     C Note: In a between process tile-tile data transport using
231     C MPI the sender needs to clear an Isend wait handle here.
232     C In a within process tile-tile data transport using true
233     C shared address space/or direct transfer through commonly
234     C addressable memory blocks the receiver needs to assert
235     C that he has consumed the buffer the sender filled here.
236     farTile=exch2_neighbourId(N,thisTile)
237 jmc 1.7 IF ( W2_myCommFlag(N,bi,bj) .EQ. 'M' ) THEN
238 jmc 1.6 wHandle = e2_msgHandles(1,N,bi,bj)
239     CALL MPI_Wait( wHandle, mpiStatus, mpiRc )
240     wHandle = e2_msgHandles(2,N,bi,bj)
241     CALL MPI_Wait( wHandle, mpiStatus, mpiRc )
242 jmc 1.7 ELSEIF ( W2_myCommFlag(N,bi,bj) .EQ. 'P' ) THEN
243 jmc 1.6 ELSE
244     ENDIF
245     ENDDO
246 heimbach 1.1 ENDDO
247     ENDDO
248    
249 jmc 1.6 _END_MASTER( myThid )
250 jmc 1.8 C Everyone waits until master-thread finishes receiving
251     CALL BAR2( myThid )
252    
253 jmc 1.6 #endif /* ALLOW_USE_MPI */
254    
255     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
256    
257     C-- Post sends into buffer (buffer level 1):
258     DO bj=myByLo(myThid), myByHi(myThid)
259     DO bi=myBxLo(myThid), myBxHi(myThid)
260 jmc 1.7 thisTile=W2_myTileList(bi,bj)
261 jmc 1.6 nN=exch2_nNeighbours(thisTile)
262     DO N=1,nN
263     farTile=exch2_neighbourId(N,thisTile)
264     oN = exch2_opposingSend(N,thisTile)
265     CALL EXCH2_GET_UV_BOUNDS(
266     I fieldCode, exchWidthX,
267     I farTile, oN,
268     O tIlo1, tIhi1, tJlo1, tJhi1,
269     O tIlo2, tIhi2, tJlo2, tJhi2,
270     O tiStride, tjStride,
271     O oIs1, oJs1, oIs2, oJs2,
272     I myThid )
273     tKLo=1
274     tKHi=myNz
275     tKStride=1
276     C- Put my points in buffer for neighbour N to fill points
277     C (tIlo:tIhi:tiStride,tJlo:tJhi,tJStride,tKlo:tKhi,tKStride)
278     C in its copy of "array1" & "array2".
279     CALL EXCH2_AD_PUT_RX2(
280     I tIlo1, tIhi1, tIlo2, tIhi2, tiStride,
281     I tJlo1, tJhi1, tJlo2, tJhi2, tjStride,
282     I tKlo, tKhi, tkStride,
283     I oIs1, oJs1, oIs2, oJs2,
284     I thisTile, N,
285     I e2BufrRecSize,
286 jmc 1.7 O e2Bufr1_RX(1,N,bi,bj,1), e2Bufr2_RX(1,N,bi,bj,1),
287 jmc 1.6 I array1(1-myOLw,1-myOLs,1,bi,bj),
288     I array2(1-myOLw,1-myOLs,1,bi,bj),
289     I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
290     I i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,
291     O e2_msgHandles(1,N,bi,bj),
292 jmc 1.7 I W2_myCommFlag(N,bi,bj), signOption, myThid )
293 jmc 1.6 ENDDO
294 heimbach 1.1 ENDDO
295     ENDDO
296    
297     RETURN
298     END
299    
300     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
301    
302     CEH3 ;;; Local Variables: ***
303     CEH3 ;;; mode:fortran ***
304     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22