/[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.6 - (hide annotations) (download)
Sat May 30 21:26:31 2009 UTC (14 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61r, checkpoint61p, checkpoint61q
Changes since 1.5: +233 -192 lines
- take buffer copy from/to array out of S/R exch2_send/recv into new
  S/R exch2_put/get ; Exch of local variable now works with MPI+MTH
  (tested by removing commom block statement in SOLVE_FOR_PRESSURE.h).
- simplify argument list of S/R exch2_get_uv_bounds & get_scal_bounds
- implement EXCH_IGNORE_CORNERS in scalar exchange (rx1);

1 jmc 1.6 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_rx2_cube.template,v 1.9 2009/05/12 19:44:58 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.6 C For now tile <-> tile exchanges are sequentialised through
108 heimbach 1.1 C thread 1. This is a temporary feature for preliminary testing until
109 jmc 1.6 C general tile decomposition is in place (CNH April 11, 2001)
110 heimbach 1.1 CALL BAR2( myThid )
111    
112 jmc 1.6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
113    
114     C-- Extract from buffer (either from level 1 if local exch,
115     C or level 2 if coming from an other Proc)
116     C AD: = fill buffer from my-tile-edge overlap-region, level 1 or 2 depending
117     C AD: on local (to this Proc) or remote Proc tile destination
118     DO bj=myByLo(myThid), myByHi(myThid)
119     DO bi=myBxLo(myThid), myBxHi(myThid)
120     thisTile=W2_myTileList(bi)
121     nN=exch2_nNeighbours(thisTile)
122     DO N=1,nN
123     CALL EXCH2_GET_UV_BOUNDS(
124     I fieldCode, exchWidthX,
125     I thisTile, N,
126     O tIlo1, tIhi1, tJlo1, tJhi1,
127     O tIlo2, tIhi2, tJlo2, tJhi2,
128     O tiStride, tjStride,
129     O oIs1, oJs1, oIs2, oJs2,
130     I myThid )
131     tKLo=1
132     tKHi=myNz
133     tKStride=1
134    
135     C From buffer, get my points
136     C (tIlo:tIhi:tiStride,tJlo:tJhi,tJStride,tKlo:tKhi,tKStride) in "array1,2":
137     C Note: when transferring data within a process:
138     C o e2Bufr entry to read is entry associated with opposing send record
139     C o e2_msgHandle entry to read is entry associated with opposing send record.
140     CALL EXCH2_AD_GET_RX2(
141     I tIlo1, tIhi1, tIlo2, tIhi2, tiStride,
142     I tJlo1, tJhi1, tJlo2, tJhi2, tjStride,
143     I tKlo, tKhi, tkStride,
144     I thisTile, N, bi, bj,
145     I e2BufrRecSize, W2_maxNeighbours, nSx, nSy,
146     O iBuf1Filled(N,bi), iBuf2Filled(N,bi),
147     O e2Bufr1_RX, e2Bufr2_RX,
148     U array1(1-myOLw,1-myOLs,1,bi,bj),
149     U array2(1-myOLw,1-myOLs,1,bi,bj),
150     I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
151     I i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,
152     U e2_msgHandles,
153     I W2_myCommFlag(N,bi), myThid )
154     ENDDO
155 heimbach 1.1 ENDDO
156     ENDDO
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     C AD: b) the length of transfered buffer (<- match the ad_put/ad_get)
164    
165     C wait until all threads finish filling buffer
166 heimbach 1.1 CALL BAR2( myThid )
167 jmc 1.6 _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     thisTile=W2_myTileList(bi)
173     nN=exch2_nNeighbours(thisTile)
174     DO N=1,nN
175     C- Skip the call if this is an internal exchange
176     IF ( W2_myCommFlag(N,bi) .EQ. 'M' ) THEN
177     CALL EXCH2_SEND_RX2(
178     I thisTile, N,
179     I e2BufrRecSize,
180     I iBuf1Filled(N,bi), iBuf2Filled(N,bi),
181     I e2Bufr1_RX(1,N,bi,2), e2Bufr2_RX(1,N,bi,2),
182     O e2_msgHandles(1,N,bi,bj),
183     I W2_myCommFlag(N,bi), myThid )
184     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     thisTile=W2_myTileList(bi)
193     nN=exch2_nNeighbours(thisTile)
194     DO N=1,nN
195     C- Skip the call if this is an internal exchange
196     IF ( W2_myCommFlag(N,bi) .EQ. 'M' ) THEN
197     farTile=exch2_neighbourId(N,thisTile)
198     oN = exch2_opposingSend(N,thisTile)
199     CALL EXCH2_GET_UV_BOUNDS(
200     I fieldCode, exchWidthX,
201     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     I e2Bufr1_RX(1,N,bi,1), e2Bufr2_RX(1,N,bi,1),
219     I W2_myCommFlag(N,bi), myThid )
220     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     thisTile=W2_myTileList(bi)
229     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     IF ( W2_myCommFlag(N,bi) .EQ. 'M' ) THEN
239     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     ELSEIF ( W2_myCommFlag(N,bi) .EQ. 'P' ) THEN
244     ELSE
245     ENDIF
246     ENDDO
247 heimbach 1.1 ENDDO
248     ENDDO
249    
250 jmc 1.6 _END_MASTER( myThid )
251     #endif /* ALLOW_USE_MPI */
252    
253     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
254     C Wait until all threads finish receiving or filling buffer
255     CALL BAR2( myThid )
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     thisTile=W2_myTileList(bi)
261     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     O e2Bufr1_RX(1,N,bi,1), e2Bufr2_RX(1,N,bi,1),
287     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     I W2_myCommFlag(N,bi), signOption, myThid )
293     ENDDO
294 heimbach 1.1 ENDDO
295     ENDDO
296    
297     CALL BAR2(myThid)
298 jmc 1.3
299 heimbach 1.1 RETURN
300     END
301    
302     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
303    
304     CEH3 ;;; Local Variables: ***
305     CEH3 ;;; mode:fortran ***
306     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22