/[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.11 - (hide annotations) (download)
Wed May 19 01:25:17 2010 UTC (14 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62g, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.10: +4 -4 lines
stwich order of arguments myOLn,myOLs to match calling S/R

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

  ViewVC Help
Powered by ViewVC 1.1.22