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

Contents of /MITgcm/pkg/exch2/exch2_put_rx2.template

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


Revision 1.4 - (show annotations) (download)
Sat Sep 15 23:01:07 2012 UTC (11 years, 8 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.3: +108 -114 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 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_put_rx2.template,v 1.3 2012/09/03 19:40:33 jmc Exp $
2 C $Name: $
3
4 #include "CPP_EEOPTIONS.h"
5 #include "W2_OPTIONS.h"
6
7 CBOP 0
8 C !ROUTINE: EXCH2_PUT_RX2
9
10 C !INTERFACE:
11 SUBROUTINE EXCH2_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 iBufr1, iBufr2,
19 O e2Bufr1_RX, e2Bufr2_RX,
20 I array1,
21 I array2,
22 I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
23 I i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,
24 O e2_msgHandle,
25 I commSetting, withSigns, myThid )
26
27 C !DESCRIPTION:
28 C Two components vector field Exchange:
29 C Put into buffer exchanged data from this source tile.
30 C Those data are intended to fill-in the
31 C target-neighbour-edge overlap region.
32
33 C !USES:
34 IMPLICIT NONE
35
36 #include "SIZE.h"
37 #include "EEPARAMS.h"
38 #include "W2_EXCH2_SIZE.h"
39 #include "W2_EXCH2_TOPOLOGY.h"
40 #ifdef W2_E2_DEBUG_ON
41 # include "W2_EXCH2_PARAMS.h"
42 #endif
43
44 C !INPUT/OUTPUT PARAMETERS:
45 C === Routine arguments ===
46 C tIlo1, tIhi1 :: index range in I that will be filled in target "array1"
47 C tIlo2, tIhi2 :: index range in I that will be filled in target "array2"
48 C tIstride :: index step in I that will be filled in target arrays
49 C tJlo1, tJhi1 :: index range in J that will be filled in target "array1"
50 C tJlo2, tJhi2 :: index range in J that will be filled in target "array2"
51 C tJstride :: index step in J that will be filled in target arrays
52 C tKlo, tKhi :: index range in K that will be filled in target arrays
53 C tKstride :: index step in K that will be filled in target arrays
54 C oIs1, oJs1 :: I,J index offset in target to source-1 connection
55 C oIs2, oJs2 :: I,J index offset in target to source-2 connection
56 C thisTile :: sending tile Id. number
57 C nN :: Neighbour entry that we are processing
58 C e2BufrRecSize :: Number of elements in each entry of e2Bufr[1,2]_RX
59 C iBufr1 :: number of buffer-1 elements filled in
60 C iBufr2 :: number of buffer-2 elements filled in
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 C :: For MPI MSG communication MPI_Wait uses handle to check
82 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 INTEGER iBufr1, iBufr2
94 _RX e2Bufr1_RX( e2BufrRecSize )
95 _RX e2Bufr2_RX( e2BufrRecSize )
96 INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
97 INTEGER i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi
98 _RX array1(i1Lo:i1Hi,j1Lo:j1Hi,k1Lo:k1Hi)
99 _RX array2(i2Lo:i2Hi,j2Lo:j2Hi,k2Lo:k2Hi)
100 INTEGER e2_msgHandle(2)
101 CHARACTER commSetting
102 LOGICAL withSigns
103 INTEGER myThid
104 CEOP
105
106 C !LOCAL VARIABLES:
107 C == Local variables ==
108 C itl,jtl,ktl :: Loop counters
109 C :: itl etc... target local
110 C :: itc etc... target canonical
111 C :: isl etc... source local
112 C :: isc etc... source canonical
113 C tgT :: Target tile
114 C itb, jtb :: Target local to canonical offsets
115 INTEGER itl, jtl, ktl
116 INTEGER itc, jtc
117 INTEGER isc, jsc
118 INTEGER isl, jsl
119 INTEGER tgT
120 INTEGER itb, jtb
121 INTEGER isb, jsb
122 INTEGER pi(2), pj(2)
123 INTEGER iLoc
124 _RX sa1, sa2, val1, val2
125
126 CHARACTER*(MAX_LEN_MBUF) msgBuf
127 #ifdef W2_E2_DEBUG_ON
128 LOGICAL prtFlag
129 #endif
130
131 IF ( commSetting .EQ. 'P' ) THEN
132 C Need to check that buffer synchronisation token is decremented
133 C before filling buffer. This is needed for parallel processing
134 C shared memory modes only.
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 IF ( ABS(W2_printMsg).GE.2 ) THEN
162 WRITE(msgBuf,'(2A,I5,I3,A,I5)') 'EXCH2_PUT_RX2',
163 & ' sourceTile,neighb=', thisTile, nN, ' : targetTile=', tgT
164 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
165 I SQUEEZE_BOTH, myThid )
166 ENDIF
167 prtFlag = ABS(W2_printMsg).GE.3
168 #endif /* W2_E2_DEBUG_ON */
169 iBufr1=0
170 DO ktl=tKlo,tKhi,tkStride
171 DO jtl=tJlo1, tJhi1, tjStride
172 DO itl=tIlo1, tIhi1, tiStride
173 iBufr1=iBufr1+1
174 itc = itl+itb
175 jtc = jtl+jtb
176 isc = pi(1)*itc+pi(2)*jtc+oIs1
177 jsc = pj(1)*itc+pj(2)*jtc+oJs1
178 isl = isc-isb
179 jsl = jsc-jsb
180 #ifdef W2_E2_DEBUG_ON
181 IF ( prtFlag ) THEN
182 WRITE(msgBuf,'(A,2I5)')
183 & 'EXCH2_PUT_RX2 target u(itl,jtl) =', itl, jtl
184 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
185 I SQUEEZE_RIGHT, myThid )
186 IF ( pi(1) .EQ. 1 ) THEN
187 C i index aligns
188 WRITE(msgBuf,'(A,2I5)')
189 & ' source +u(isl,jsl) =', isl, jsl
190 ELSEIF ( pi(1) .EQ. -1 ) THEN
191 C reversed i index aligns
192 WRITE(msgBuf,'(A,2I5)')
193 & ' source -u(isl,jsl) =', isl, jsl
194 ELSEIF ( pj(1) .EQ. 1 ) THEN
195 WRITE(msgBuf,'(A,2I5)')
196 & ' source +v(isl,jsl) =', isl, jsl
197 ELSEIF ( pj(1) .EQ. -1 ) THEN
198 WRITE(msgBuf,'(A,2I5)')
199 & ' source -v(isl,jsl) =', isl, jsl
200 ENDIF
201 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
202 I SQUEEZE_RIGHT, myThid )
203 ENDIF
204 IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
205 C Forward mode send getting from points outside of the
206 C tiles exclusive domain bounds in X. This should not happen
207 WRITE(msgBuf,'(2A,I4,A,2I4,A)') 'EXCH2_PUT_RX2:',
208 & ' isl=', isl, ' is out of bounds (i1Lo,Hi=',i1Lo,i1Hi,')'
209 CALL PRINT_ERROR ( msgBuf, myThid )
210 WRITE(msgBuf,'(2A,2I4,A,3I6)') 'EXCH2_PUT_RX2:',
211 & ' for itl,jtl=', itl, jtl, ' itc,jtc,isc=', itc, jtc, isc
212 CALL PRINT_ERROR ( msgBuf, myThid )
213 STOP 'ABNORMAL END: S/R EXCH2_PUT_RX2 (isl out of bounds)'
214 ENDIF
215 IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
216 C Forward mode send getting from points outside of the
217 C tiles exclusive domain bounds in Y. This should not happen
218 WRITE(msgBuf,'(2A,I4,A,2I4,A)') 'EXCH2_PUT_RX2:',
219 & ' jsl=', jsl, ' is out of bounds (j1Lo,Hi=',j1Lo,j1Hi,')'
220 CALL PRINT_ERROR ( msgBuf, myThid )
221 WRITE(msgBuf,'(2A,2I4,A,3I6)') 'EXCH2_PUT_RX2:',
222 & ' for itl,jtl=', itl, jtl, ' itc,jtc,jsc=', itc, jtc, jsc
223 CALL PRINT_ERROR ( msgBuf, myThid )
224 STOP 'ABNORMAL END: S/R EXCH2_PUT_RX2 (jsl out of bounds)'
225 ENDIF
226 #endif /* W2_E2_DEBUG_ON */
227 #ifdef W2_USE_E2_SAFEMODE
228 iLoc = MIN( iBufr1, e2BufrRecSize )
229 #else
230 iLoc = iBufr1
231 #endif
232 val1 = sa1*array1(isl,jsl,ktl)
233 & + sa2*array2(isl,jsl,ktl)
234 e2Bufr1_RX(iLoc) = val1
235 ENDDO
236 ENDDO
237 ENDDO
238 IF ( iBufr1 .GT. e2BufrRecSize ) THEN
239 C Ran off end of buffer. This should not happen
240 WRITE(msgBuf,'(2A,I9,A,I9)') 'EXCH2_PUT_RX2:',
241 & ' iBufr1=', iBufr1, ' exceeds E2BUFR size=', e2BufrRecSize
242 CALL PRINT_ERROR ( msgBuf, myThid )
243 STOP 'ABNORMAL END: S/R EXCH2_PUT_RX2 (iBufr1 over limit)'
244 ENDIF
245
246 C Extract values into bufr2
247 C if pi(2) is 1 then +j in target <=> +i in source so bufr1 should get +array1
248 C if pi(2) is -1 then +j in target <=> -i in source so bufr1 should get -array1
249 C if pj(2) is 1 then +j in target <=> +j in source so bufr1 should get +array2
250 C if pj(2) is -1 then +j in target <=> -j in source so bufr1 should get -array2
251 sa1 = pi(2)
252 sa2 = pj(2)
253 IF ( .NOT. withSigns ) THEN
254 sa1 = ABS(sa1)
255 sa2 = ABS(sa2)
256 ENDIF
257 iBufr2=0
258 DO ktl=tKlo,tKhi,tkStride
259 DO jtl=tJlo2, tJhi2, tjStride
260 DO itl=tIlo2, tIhi2, tiStride
261 iBufr2=iBufr2+1
262 itc = itl+itb
263 jtc = jtl+jtb
264 isc = pi(1)*itc+pi(2)*jtc+oIs2
265 jsc = pj(1)*itc+pj(2)*jtc+oJs2
266 isl = isc-isb
267 jsl = jsc-jsb
268 #ifdef W2_E2_DEBUG_ON
269 IF ( prtFlag ) THEN
270 WRITE(msgBuf,'(A,2I5)')
271 & 'EXCH2_PUT_RX2 target v(itl,jtl) =', itl, jtl
272 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
273 I SQUEEZE_RIGHT, myThid )
274 IF ( pi(2) .EQ. 1 ) THEN
275 C i index aligns
276 WRITE(msgBuf,'(A,2I5)')
277 & ' source +u(isl,jsl) =', isl, jsl
278 ELSEIF ( pi(2) .EQ. -1 ) THEN
279 C reversed i index aligns
280 WRITE(msgBuf,'(A,2I5)')
281 & ' source -u(isl,jsl) =', isl, jsl
282 ELSEIF ( pj(2) .EQ. 1 ) THEN
283 WRITE(msgBuf,'(A,2I5)')
284 & ' source +v(isl,jsl) =', isl, jsl
285 ELSEIF ( pj(2) .EQ. -1 ) THEN
286 WRITE(msgBuf,'(A,2I5)')
287 & ' source -v(isl,jsl) =', isl, jsl
288 ENDIF
289 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
290 I SQUEEZE_RIGHT, myThid )
291 ENDIF
292 IF ( isl .LT. i2Lo .OR. isl .GT. i2Hi ) THEN
293 C Forward mode send getting from points outside of the
294 C tiles exclusive domain bounds in X. This should not happen
295 WRITE(msgBuf,'(2A,I4,A,2I4,A)') 'EXCH2_PUT_RX2:',
296 & ' isl=', isl, ' is out of bounds (i2Lo,Hi=',i2Lo,i2Hi,')'
297 CALL PRINT_ERROR ( msgBuf, myThid )
298 WRITE(msgBuf,'(2A,2I4,A,3I6)') 'EXCH2_PUT_RX2:',
299 & ' for itl,jtl=', itl, jtl, ' itc,jtc,isc=', itc, jtc, isc
300 CALL PRINT_ERROR ( msgBuf, myThid )
301 STOP 'ABNORMAL END: S/R EXCH2_PUT_RX2 (isl out of bounds)'
302 ENDIF
303 IF ( jsl .LT. j2Lo .OR. jsl .GT. j2Hi ) THEN
304 C Forward mode send getting from points outside of the
305 C tiles exclusive domain bounds in Y. This should not happen
306 WRITE(msgBuf,'(2A,I4,A,2I4,A)') 'EXCH2_PUT_RX2:',
307 & ' jsl=', jsl, ' is out of bounds (j2Lo,Hi=',j2Lo,j2Hi,')'
308 CALL PRINT_ERROR ( msgBuf, myThid )
309 WRITE(msgBuf,'(2A,2I4,A,3I6)') 'EXCH2_PUT_RX2:',
310 & ' for itl,jtl=', itl, jtl, ' itc,jtc,jsc=', itc, jtc, jsc
311 CALL PRINT_ERROR ( msgBuf, myThid )
312 STOP 'ABNORMAL END: S/R EXCH2_PUT_RX2 (jsl out of bounds)'
313 ENDIF
314 #endif /* W2_E2_DEBUG_ON */
315 #ifdef W2_USE_E2_SAFEMODE
316 iLoc = MIN( iBufr2, e2BufrRecSize )
317 #else
318 iLoc = iBufr2
319 #endif
320 val2 = sa1*array1(isl,jsl,ktl)
321 & + sa2*array2(isl,jsl,ktl)
322 e2Bufr2_RX(iLoc) = val2
323 ENDDO
324 ENDDO
325 ENDDO
326 IF ( iBufr2 .GT. e2BufrRecSize ) THEN
327 C Ran off end of buffer. This should not happen
328 WRITE(msgBuf,'(2A,I9,A,I9)') 'EXCH2_PUT_RX2:',
329 & ' iBufr2=', iBufr2, ' exceeds E2BUFR size=', e2BufrRecSize
330 CALL PRINT_ERROR ( msgBuf, myThid )
331 STOP 'ABNORMAL END: S/R EXCH2_PUT_RX2 (iBufr2 over limit)'
332 ENDIF
333
334 RETURN
335 END
336
337 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
338
339 CEH3 ;;; Local Variables: ***
340 CEH3 ;;; mode:fortran ***
341 CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22