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

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

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


Revision 1.6 - (hide annotations) (download)
Sun Jun 28 01:00:23 2009 UTC (14 years, 11 months ago) by jmc
Branch: MAIN
Changes since 1.5: +19 -19 lines
add bj in exch2 arrays and S/R.

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

  ViewVC Help
Powered by ViewVC 1.1.22