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

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

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


Revision 1.2 - (hide annotations) (download)
Fri Apr 23 20:21:07 2010 UTC (14 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62g, checkpoint62f, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.1: +3 -3 lines
fix propagating typo (& others) in variable description

1 jmc 1.2 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_ad_put_rx2.template,v 1.1 2009/05/30 21:18:59 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5     #include "W2_OPTIONS.h"
6    
7     CBOP 0
8     C !ROUTINE: EXCH2_AD_PUT_RX2
9    
10     C !INTERFACE:
11     SUBROUTINE EXCH2_AD_PUT_RX2 (
12     I tIlo1, tIhi1, tIlo2, tIhi2, tiStride,
13     I tJlo1, tJhi1, tJlo2, tJhi2, tjStride,
14     I tKlo, tKhi, tkStride,
15     I oIs1, oJs1, oIs2, oJs2,
16     I thisTile, nN,
17     I e2BufrRecSize,
18     O e2Bufr1_RX, e2Bufr2_RX,
19     I array1,
20     I array2,
21     I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
22     I i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,
23     O e2_msgHandle,
24     I commSetting, withSigns, myThid )
25    
26     C !DESCRIPTION:
27     C---------------
28 jmc 1.2 C AD: IMPORTANT: all comments (except AD:) are taken from the Forward S/R
29 jmc 1.1 C AD: and need to be interpreted in the reverse sense: put <-> get,
30     C AD: send <-> recv, source <-> target ...
31     C---------------
32     C Two components vector field Exchange:
33     C Put into buffer exchanged data from this source tile.
34     C Those data are intended to fill-in the
35     C target-neighbour-edge overlap region.
36    
37     C !USES:
38     IMPLICIT NONE
39    
40     #include "SIZE.h"
41     #include "EEPARAMS.h"
42     #include "W2_EXCH2_SIZE.h"
43     #include "W2_EXCH2_TOPOLOGY.h"
44    
45    
46     C !INPUT/OUTPUT PARAMETERS:
47     C === Routine arguments ===
48     C tIlo1, tIhi1 :: index range in I that will be filled in target "array1"
49     C tIlo2, tIhi2 :: index range in I that will be filled in target "array2"
50     C tIstride :: index step in I that will be filled in target arrays
51     C tJlo1, tJhi1 :: index range in J that will be filled in target "array1"
52     C tJlo2, tJhi2 :: index range in J that will be filled in target "array2"
53     C tJstride :: index step in J that will be filled in target arrays
54     C tKlo, tKhi :: index range in K that will be filled in target arrays
55     C tKstride :: index step in K that will be filled in target arrays
56     C oIs1, oJs1 :: I,J index offset in target to source-1 connection
57     C oIs2, oJs2 :: I,J index offset in target to source-2 connection
58     C thisTile :: sending tile Id. number
59     C nN :: Neighbour entry that we are processing
60     C e2BufrRecSize :: Number of elements in each entry of e2Bufr[1,2]_RX
61     C e2Bufr1_RX :: Data transport buffer array. This array is used in one of
62     C e2Bufr2_RX :: two ways. For PUT communication the entry in the buffer
63     C :: associated with the source for this receive (determined
64     C :: from the opposing_send index) is read.
65     C :: For MSG communication the entry in the buffer associated
66     C :: with this neighbor of this tile is used as a receive
67     C :: location for loading a linear stream of bytes.
68     C array1 :: 1rst Component target array that this receive writes to.
69     C array2 :: 2nd Component target array that this receive writes to.
70     C i1Lo, i1Hi :: I coordinate bounds of target array1
71     C j1Lo, j1Hi :: J coordinate bounds of target array1
72     C k1Lo, k1Hi :: K coordinate bounds of target array1
73     C i2Lo, i2Hi :: I coordinate bounds of target array2
74     C j2Lo, j2Hi :: J coordinate bounds of target array2
75     C k2Lo, k2Hi :: K coordinate bounds of target array2
76     C e2_msgHandles :: Synchronization and coordination data structure used to
77     C :: coordinate access to e2Bufr1_RX or to regulate message
78     C :: buffering. In PUT communication sender will increment
79     C :: handle entry once data is ready in buffer. Receiver will
80     C :: decrement handle once data is consumed from buffer.
81 jmc 1.2 C :: For MPI MSG communication MPI_Wait uses handle to check
82 jmc 1.1 C :: Isend has cleared. This is done in routine after receives.
83     C commSetting :: Mode of communication used to exchange with this neighbor
84     C withSigns :: Flag controlling whether vector field is signed.
85     C myThid :: my Thread Id. number
86    
87     INTEGER tIlo1, tIhi1, tIlo2, tIhi2, tiStride
88     INTEGER tJlo1, tJhi1, tJlo2, tJhi2, tjStride
89     INTEGER tKlo, tKhi, tkStride
90     INTEGER oIs1, oJs1, oIs2, oJs2
91     INTEGER thisTile, nN
92     INTEGER e2BufrRecSize
93     _RX e2Bufr1_RX( e2BufrRecSize )
94     _RX e2Bufr2_RX( e2BufrRecSize )
95     INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
96     INTEGER i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi
97     _RX array1(i1Lo:i1Hi,j1Lo:j1Hi,k1Lo:k1Hi)
98     _RX array2(i2Lo:i2Hi,j2Lo:j2Hi,k2Lo:k2Hi)
99     INTEGER e2_msgHandle(2)
100     CHARACTER commSetting
101     LOGICAL withSigns
102     INTEGER myThid
103     CEOP
104    
105     C !LOCAL VARIABLES:
106     C == Local variables ==
107     C itl,jtl,ktl :: Loop counters
108     C :: itl etc... target local
109     C :: itc etc... target canonical
110     C :: isl etc... source local
111     C :: isc etc... source canonical
112     C tgT :: Target tile
113     C itb, jtb :: Target local to canonical offsets
114     C iBufr1 :: number of buffer-1 elements filled in
115     C iBufr2 :: number of buffer-2 elements filled in
116     INTEGER itl, jtl, ktl
117     INTEGER itc, jtc
118     INTEGER isc, jsc
119     INTEGER isl, jsl
120     INTEGER tgT
121     INTEGER itb, jtb
122     INTEGER isb, jsb
123     INTEGER iBufr1, iBufr2
124     INTEGER pi(2), pj(2)
125     _RX sa1, sa2, val1, val2
126    
127     #if ( (defined W2_E2_DEBUG_ON) || (defined W2_USE_E2_SAFEMODE) )
128     CHARACTER*(MAX_LEN_MBUF) msgBuf
129     #endif
130    
131     IF ( commSetting .EQ. 'P' ) THEN
132     C AD: 1 Need to check and spin on data ready assertion for multithreaded mode,
133     C AD: for now, ensure global sync using barrier.
134     C AD: 2 get directly data from 1rst level buffer (sLv=1);
135     ENDIF
136    
137     tgT = exch2_neighbourId(nN, thisTile )
138     itb = exch2_tBasex(tgT)
139     jtb = exch2_tBasey(tgT)
140     isb = exch2_tBasex(thisTile)
141     jsb = exch2_tBasey(thisTile)
142     pi(1)=exch2_pij(1,nN,thisTile)
143     pi(2)=exch2_pij(2,nN,thisTile)
144     pj(1)=exch2_pij(3,nN,thisTile)
145     pj(2)=exch2_pij(4,nN,thisTile)
146    
147     C Extract into bufr1 (target i-index array)
148     C if pi(1) is 1 then +i in target <=> +i in source so bufr1 should get +array1
149     C if pi(1) is -1 then +i in target <=> -i in source so bufr1 should get -array1
150     C if pj(1) is 1 then +i in target <=> +j in source so bufr1 should get +array2
151     C if pj(1) is -1 then +i in target <=> -j in source so bufr1 should get -array2
152     sa1 = pi(1)
153     sa2 = pj(1)
154     IF ( .NOT. withSigns ) THEN
155     sa1 = ABS(sa1)
156     sa2 = ABS(sa2)
157     ENDIF
158     C if pi(1) is 1 then +i in source aligns with +i in target
159     C if pj(1) is 1 then +i in source aligns with +j in target
160     #ifdef W2_E2_DEBUG_ON
161     WRITE(msgBuf,'(A,I5,A,I5)')
162     & 'EXCH2_AD_PUT_RX2 sourceTile=', thisTile, ' targetTile=', tgT
163     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
164     I SQUEEZE_BOTH, myThid )
165     #endif /* W2_E2_DEBUG_ON */
166     iBufr1=0
167     DO ktl=tKlo,tKhi,tkStride
168     DO jtl=tJlo1, tJhi1, tjStride
169     DO itl=tIlo1, tIhi1, tiStride
170     iBufr1=iBufr1+1
171     itc = itl+itb
172     jtc = jtl+jtb
173     isc = pi(1)*itc+pi(2)*jtc+oIs1
174     jsc = pj(1)*itc+pj(2)*jtc+oJs1
175     isl = isc-isb
176     jsl = jsc-jsb
177     #ifdef W2_E2_DEBUG_ON
178     WRITE(msgBuf,'(A,2I4)')
179     & 'EXCH2_AD_PUT_RX2 target u(itl, jtl) = ', itl, jtl
180     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
181     I SQUEEZE_RIGHT, myThid )
182     IF ( pi(1) .EQ. 1 ) THEN
183     C i index aligns
184     WRITE(msgBuf,'(A,2I4)')
185     & ' source +u(isl, jsl) = ', isl, jsl
186     ELSEIF ( pi(1) .EQ. -1 ) THEN
187     C reversed i index aligns
188     WRITE(msgBuf,'(A,2I4)')
189     & ' source -u(isl, jsl) = ', isl, jsl
190     ELSEIF ( pj(1) .EQ. 1 ) THEN
191     WRITE(msgBuf,'(A,2I4)')
192     & ' source +v(isl, jsl) = ', isl, jsl
193     ELSEIF ( pj(1) .EQ. -1 ) THEN
194     WRITE(msgBuf,'(A,2I4)')
195     & ' source -v(isl, jsl) = ', isl, jsl
196     ENDIF
197     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
198     I SQUEEZE_RIGHT, myThid )
199     IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
200     WRITE(msgBuf,'(A,2I4)')
201     & ' *** isl is out of bounds '
202     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
203     I SQUEEZE_RIGHT, myThid )
204     ENDIF
205     IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
206     WRITE(msgBuf,'(A,2I4)')
207     & ' *** jsl is out of bounds '
208     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
209     I SQUEEZE_RIGHT, myThid )
210     ENDIF
211     #endif /* W2_E2_DEBUG_ON */
212     #ifdef W2_USE_E2_SAFEMODE
213     IF ( iBufr1 .GT. e2BufrRecSize ) THEN
214     C Ran off end of buffer. This should not happen
215     STOP 'EXCH2_AD_PUT_RX2:: E2BUFR LIMIT EXCEEDED'
216     ENDIF
217     IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
218     C Forward mode send getting from points outside of the
219     C tiles exclusive domain bounds in X. This should not happen
220     WRITE(msgBuf,'(A,I4,I4)')
221     & 'EXCH2_AD_PUT_RX2 tIlo1,tIhi1=', tIlo1, tIhi1
222     CALL PRINT_ERROR (msgBuf, myThid )
223     WRITE(msgBuf,'(A,3I4)')
224     & 'EXCH2_AD_PUT_RX2 itl, jtl, isl =', itl, jtl, isl
225     CALL PRINT_ERROR (msgBuf, myThid )
226     STOP 'EXCH2_AD_PUT_RX2:: ISL OUTSIDE TILE EXCLUSIVE DOMAIN'
227     ENDIF
228     IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
229     C Forward mode send getting from points outside of the
230     C tiles exclusive domain bounds in Y. This should not happen
231     WRITE(msgBuf,'(A,I4,I4)')
232     & 'EXCH2_AD_PUT_RX2 tJlo1,tJhi1=', tJlo1, tJhi1
233     CALL PRINT_ERROR (msgBuf, myThid )
234     WRITE(msgBuf,'(A,2I4)')
235     & 'EXCH2_AD_PUT_RX2 itl, jtl =', itl, jtl
236     CALL PRINT_ERROR (msgBuf, myThid )
237     WRITE(msgBuf,'(A,2I4)')
238     & 'EXCH2_AD_PUT_RX2 isl, jsl =', isl, jsl
239     CALL PRINT_ERROR (msgBuf, myThid )
240     STOP 'EXCH2_AD_PUT_RX2:: JSL OUTSIDE TILE EXCLUSIVE DOMAIN'
241     ENDIF
242     #endif /* W2_USE_E2_SAFEMODE */
243     val1 = e2Bufr1_RX(iBufr1)
244     array1(isl,jsl,ktl) = array1(isl,jsl,ktl) + sa1*val1
245     array2(isl,jsl,ktl) = array2(isl,jsl,ktl) + sa2*val1
246     ENDDO
247     ENDDO
248     ENDDO
249    
250     C Extract values into bufr2
251     C if pi(2) is 1 then +j in target <=> +i in source so bufr1 should get +array1
252     C if pi(2) is -1 then +j in target <=> -i in source so bufr1 should get -array1
253     C if pj(2) is 1 then +j in target <=> +j in source so bufr1 should get +array2
254     C if pj(2) is -1 then +j in target <=> -j in source so bufr1 should get -array2
255     sa1 = pi(2)
256     sa2 = pj(2)
257     IF ( .NOT. withSigns ) THEN
258     sa1 = ABS(sa1)
259     sa2 = ABS(sa2)
260     ENDIF
261     iBufr2=0
262     DO ktl=tKlo,tKhi,tkStride
263     DO jtl=tJlo2, tJhi2, tjStride
264     DO itl=tIlo2, tIhi2, tiStride
265     iBufr2=iBufr2+1
266     itc = itl+itb
267     jtc = jtl+jtb
268     isc = pi(1)*itc+pi(2)*jtc+oIs2
269     jsc = pj(1)*itc+pj(2)*jtc+oJs2
270     isl = isc-isb
271     jsl = jsc-jsb
272     #ifdef W2_E2_DEBUG_ON
273     WRITE(msgBuf,'(A,2I4)')
274     & 'EXCH2_AD_PUT_RX2 target v(itl, jtl) = ', itl, jtl
275     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
276     I SQUEEZE_RIGHT, myThid )
277     IF ( pi(2) .EQ. 1 ) THEN
278     C i index aligns
279     WRITE(msgBuf,'(A,2I4)')
280     & ' source +u(isl, jsl) = ', isl, jsl
281     ELSEIF ( pi(2) .EQ. -1 ) THEN
282     C reversed i index aligns
283     WRITE(msgBuf,'(A,2I4)')
284     & ' source -u(isl, jsl) = ', isl, jsl
285     ELSEIF ( pj(2) .EQ. 1 ) THEN
286     WRITE(msgBuf,'(A,2I4)')
287     & ' source +v(isl, jsl) = ', isl, jsl
288     ELSEIF ( pj(2) .EQ. -1 ) THEN
289     WRITE(msgBuf,'(A,2I4)')
290     & ' source -v(isl, jsl) = ', isl, jsl
291     ENDIF
292     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
293     I SQUEEZE_RIGHT, myThid )
294     IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
295     WRITE(msgBuf,'(A,2I4)')
296     & ' *** isl is out of bounds '
297     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
298     I SQUEEZE_RIGHT, myThid )
299     ENDIF
300     IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
301     WRITE(msgBuf,'(A,2I4)')
302     & ' *** jsl is out of bounds '
303     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
304     I SQUEEZE_RIGHT, myThid )
305     ENDIF
306     #endif /* W2_E2_DEBUG_ON */
307     #ifdef W2_USE_E2_SAFEMODE
308     IF ( iBufr2 .GT. e2BufrRecSize ) THEN
309     C Ran off end of buffer. This should not happen
310     STOP 'EXCH2_AD_PUT_RX2:: E2BUFR LIMIT EXCEEDED'
311     ENDIF
312     IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
313     C Forward mode send getting from points outside of the
314     C tiles exclusive domain bounds in X. This should not happen
315     WRITE(msgBuf,'(A,I4,I4)')
316     & 'EXCH2_AD_PUT_RX2 tIlo2,tIhi2=', tIlo2, tIhi2
317     CALL PRINT_ERROR (msgBuf, myThid )
318     WRITE(msgBuf,'(A,3I4)')
319     & 'EXCH2_AD_PUT_RX2 itl, jtl, isl =', itl, jtl, isl
320     CALL PRINT_ERROR (msgBuf, myThid )
321     STOP 'EXCH2_AD_PUT_RX2:: ISL OUTSIDE TILE EXCLUSIVE DOMAIN'
322     ENDIF
323     IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
324     C Forward mode send getting from points outside of the
325     C tiles exclusive domain bounds in Y. This should not happen
326     WRITE(msgBuf,'(A,I4,I4)')
327     & 'EXCH2_AD_PUT_RX2 tJlo2,tJhi2=', tJlo2, tJhi2
328     CALL PRINT_ERROR (msgBuf, myThid )
329     WRITE(msgBuf,'(A,2I4)')
330     & 'EXCH2_AD_PUT_RX2 itl, jtl =', itl, jtl
331     CALL PRINT_ERROR (msgBuf, myThid )
332     WRITE(msgBuf,'(A,2I4)')
333     & 'EXCH2_AD_PUT_RX2 isl, jsl =', isl, jsl
334     CALL PRINT_ERROR (msgBuf, myThid )
335     STOP 'EXCH2_AD_PUT_RX2:: JSL OUTSIDE TILE EXCLUSIVE DOMAIN'
336     ENDIF
337     #endif /* W2_USE_E2_SAFEMODE */
338     val2 = e2Bufr2_RX(iBufr2)
339     array1(isl,jsl,ktl) = array1(isl,jsl,ktl) + sa1*val2
340     array2(isl,jsl,ktl) = array2(isl,jsl,ktl) + sa2*val2
341     ENDDO
342     ENDDO
343     ENDDO
344    
345     RETURN
346     END
347    
348     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
349    
350     CEH3 ;;; Local Variables: ***
351     CEH3 ;;; mode:fortran ***
352     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22