/[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.12 - (hide annotations) (download)
Mon Mar 26 19:13:15 2012 UTC (12 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o
Changes since 1.11: +6 -4 lines
add argument "updateCorners" to S/R exch2_get_uv_bounds (enable to
switch to EXCH_IGNORE_CORNERS in vector EXCH S/R)

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

  ViewVC Help
Powered by ViewVC 1.1.22