/[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.3 - (hide annotations) (download)
Sat Sep 15 23:01:07 2012 UTC (11 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint64, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.2: +108 -116 lines
improve W2_USE_E2_SAFEMODE (faster) and W2_E2_DEBUG_ON:
  always check buffer-size (but outside the loop); move checking for valid
  index from W2_USE_E2_SAFEMODE to W2_E2_DEBUG_ON; in W2_E2_DEBUG_ON,
  print each tile and point connextion only if |W2_printMsg|>= 2 and 3.

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

  ViewVC Help
Powered by ViewVC 1.1.22