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

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

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


Revision 1.3 - (show annotations) (download)
Sat Sep 15 23:01:07 2012 UTC (12 years 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: +46 -32 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_ad_put_rx1.template,v 1.2 2010/04/23 20:21:07 jmc Exp $
2 C $Name: $
3
4 #include "CPP_EEOPTIONS.h"
5 #include "W2_OPTIONS.h"
6
7 CBOP 0
8 C !ROUTINE: EXCH2_AD_PUT_RX1
9
10 C !INTERFACE:
11 SUBROUTINE EXCH2_AD_PUT_RX1 (
12 I tIlo, tIhi, tiStride,
13 I tJlo, tJhi, tjStride,
14 I tKlo, tKhi, tkStride,
15 I thisTile, nN,
16 I e2BufrRecSize,
17 I e2Bufr1_RX,
18 U array,
19 I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
20 O e2_msgHandle,
21 I commSetting, myThid )
22
23 C !DESCRIPTION:
24 C---------------
25 C AD: IMPORTANT: all comments (except AD:) are taken from the Forward S/R
26 C AD: and need to be interpreted in the reverse sense: put <-> get,
27 C AD: send <-> recv, source <-> target ...
28 C---------------
29 C Scalar field (1 component) Exchange:
30 C Put into buffer exchanged data from this source tile.
31 C Those data are intended to fill-in the
32 C target-neighbour-edge overlap region.
33
34 C !USES:
35 IMPLICIT NONE
36
37 #include "SIZE.h"
38 #include "EEPARAMS.h"
39 #include "W2_EXCH2_SIZE.h"
40 #include "W2_EXCH2_TOPOLOGY.h"
41 #ifdef W2_E2_DEBUG_ON
42 # include "W2_EXCH2_PARAMS.h"
43 #endif
44
45 C !INPUT/OUTPUT PARAMETERS:
46 C === Routine arguments ===
47 C tIlo, tIhi :: index range in I that will be filled in target "array"
48 C tIstride :: index step in I that will be filled in target "array"
49 C tJlo, tJhi :: index range in J that will be filled in target "array"
50 C tJstride :: index step in J that will be filled in target "array"
51 C tKlo, tKhi :: index range in K that will be filled in target "array"
52 C tKstride :: index step in K that will be filled in target "array"
53 C thisTile :: sending tile Id. number
54 C nN :: Neighbour entry that we are processing
55 C e2BufrRecSize :: Number of elements in each entry of e2Bufr1_RX
56 C e2Bufr1_RX :: Data transport buffer array. This array is used in one of
57 C :: two ways. For PUT communication the entry in the buffer
58 C :: associated with the source for this receive (determined
59 C :: from the opposing_send index) is read.
60 C :: For MSG communication the entry in the buffer associated
61 C :: with this neighbor of this tile is used as a receive
62 C :: location for loading a linear stream of bytes.
63 C array :: Source array where the data come from
64 C i1Lo, i1Hi :: I coordinate bounds of target array
65 C j1Lo, j1Hi :: J coordinate bounds of target array
66 C k1Lo, k1Hi :: K coordinate bounds of target array
67 C e2_msgHandles :: Synchronization and coordination data structure used to
68 C :: coordinate access to e2Bufr1_RX or to regulate message
69 C :: buffering. In PUT communication sender will increment
70 C :: handle entry once data is ready in buffer. Receiver will
71 C :: decrement handle once data is consumed from buffer.
72 C :: For MPI MSG communication MPI_Wait uses handle to check
73 C :: Isend has cleared. This is done in routine after receives.
74 C commSetting :: Mode of communication used to exchange with this neighbor
75 C myThid :: my Thread Id. number
76
77 INTEGER tILo, tIHi, tiStride
78 INTEGER tJLo, tJHi, tjStride
79 INTEGER tKLo, tKHi, tkStride
80 INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
81 INTEGER thisTile, nN
82 INTEGER e2BufrRecSize
83 _RX e2Bufr1_RX( e2BufrRecSize )
84 _RX array(i1Lo:i1Hi,j1Lo:j1Hi,k1Lo:k1Hi)
85 INTEGER e2_msgHandle(1)
86 CHARACTER commSetting
87 INTEGER myThid
88 CEOP
89
90 C !LOCAL VARIABLES:
91 C == Local variables ==
92 C itl,jtl,ktl :: Loop counters
93 C :: itl etc... target local
94 C :: itc etc... target canonical
95 C :: isl etc... source local
96 C :: isc etc... source canonical
97 C tgT :: Target tile Id. number
98 C itb, jtb :: Target local to canonical offsets
99 C iBufr :: number of buffer elements to transfer
100 INTEGER itl, jtl, ktl
101 INTEGER itc, jtc
102 INTEGER isc, jsc
103 INTEGER isl, jsl
104 INTEGER tgT
105 INTEGER itb, jtb
106 INTEGER isb, jsb
107 INTEGER pi(2), pj(2), oi, oj
108 INTEGER iBufr, iLoc
109
110 CHARACTER*(MAX_LEN_MBUF) msgBuf
111 #ifdef W2_E2_DEBUG_ON
112 LOGICAL prtFlag
113 #endif
114
115 c IF ( commSetting .EQ. 'P' ) THEN
116 C AD: 1 Need to check and spin on data ready assertion for multithreaded mode,
117 C AD: for now, ensure global sync using barrier.
118 C AD: 2 get directly data from 1rst level buffer (sLv=1);
119 c ENDIF
120
121 tgT = exch2_neighbourId(nN, thisTile )
122 itb = exch2_tBasex(tgT)
123 jtb = exch2_tBasey(tgT)
124 isb = exch2_tBasex(thisTile)
125 jsb = exch2_tBasey(thisTile)
126 pi(1)=exch2_pij(1,nN,thisTile)
127 pi(2)=exch2_pij(2,nN,thisTile)
128 pj(1)=exch2_pij(3,nN,thisTile)
129 pj(2)=exch2_pij(4,nN,thisTile)
130 oi = exch2_oi(nN,thisTile)
131 oj = exch2_oj(nN,thisTile)
132 #ifdef W2_E2_DEBUG_ON
133 IF ( ABS(W2_printMsg).GE.2 ) THEN
134 WRITE(msgBuf,'(2A,I5,I3,A,I5)') 'EXCH2_AD_PUT_RX1',
135 & ' sourceTile,neighb=', thisTile, nN, ' : targetTile=', tgT
136 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
137 I SQUEEZE_BOTH, myThid )
138 ENDIF
139 prtFlag = ABS(W2_printMsg).GE.3
140 #endif /* W2_E2_DEBUG_ON */
141 iBufr=0
142 DO ktl=tKlo,tKhi,tKStride
143 DO jtl=tJLo, tJHi, tjStride
144 DO itl=tILo, tIHi, tiStride
145 iBufr=iBufr+1
146 itc = itl+itb
147 jtc = jtl+jtb
148 isc = pi(1)*itc+pi(2)*jtc+oi
149 jsc = pj(1)*itc+pj(2)*jtc+oj
150 isl = isc-isb
151 jsl = jsc-jsb
152 #ifdef W2_E2_DEBUG_ON
153 IF ( prtFlag ) THEN
154 WRITE(msgBuf,'(A,2I5)')
155 & 'EXCH2_AD_PUT_RX1 target t(itl,jtl) =', itl, jtl
156 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
157 I SQUEEZE_RIGHT, myThid )
158 WRITE(msgBuf,'(A,2I5)')
159 & ' source (isl,jsl) =', isl, jsl
160 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
161 I SQUEEZE_RIGHT, myThid )
162 ENDIF
163 IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
164 C Forward mode send getting from points outside of the
165 C tiles exclusive domain bounds in X. This should not happen
166 WRITE(msgBuf,'(2A,I4,A,2I4,A)') 'EXCH2_AD_PUT_RX1:',
167 & ' isl=', isl, ' is out of bounds (i1Lo,Hi=',i1Lo,i1Hi,')'
168 CALL PRINT_ERROR ( msgBuf, myThid )
169 WRITE(msgBuf,'(2A,2I4,A,3I6)') 'EXCH2_AD_PUT_RX1:',
170 & ' for itl,jtl=', itl, jtl, ' itc,jtc,isc=', itc, jtc, isc
171 CALL PRINT_ERROR ( msgBuf, myThid )
172 STOP 'ABNORMAL END: S/R EXCH2_AD_PUT_RX1 (isl out of bounds)'
173 ENDIF
174 IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
175 C Forward mode send getting from points outside of the
176 C tiles exclusive domain bounds in Y. This should not happen
177 WRITE(msgBuf,'(2A,I4,A,2I4,A)') 'EXCH2_AD_PUT_RX1:',
178 & ' jsl=', jsl, ' is out of bounds (j1Lo,Hi=',j1Lo,j1Hi,')'
179 CALL PRINT_ERROR ( msgBuf, myThid )
180 WRITE(msgBuf,'(2A,2I4,A,3I6)') 'EXCH2_AD_PUT_RX1:',
181 & ' for itl,jtl=', itl, jtl, ' itc,jtc,jsc=', itc, jtc, jsc
182 CALL PRINT_ERROR ( msgBuf, myThid )
183 STOP 'ABNORMAL END: S/R EXCH2_AD_PUT_RX1 (jsl out of bounds)'
184 ENDIF
185 #endif /* W2_E2_DEBUG_ON */
186 #ifdef W2_USE_E2_SAFEMODE
187 iLoc = MIN( iBufr, e2BufrRecSize )
188 #else
189 iLoc = iBufr
190 #endif
191 array(isl,jsl,ktl) = array(isl,jsl,ktl) + e2Bufr1_RX(iLoc)
192 e2Bufr1_RX(iLoc) = 0. _d 0
193 ENDDO
194 ENDDO
195 ENDDO
196 IF ( iBufr .GT. e2BufrRecSize ) THEN
197 C Ran off end of buffer. This should not happen
198 WRITE(msgBuf,'(2A,I9,A,I9)') 'EXCH2_AD_PUT_RX1:',
199 & ' iBufr =', iBufr, ' exceeds E2BUFR size=', e2BufrRecSize
200 CALL PRINT_ERROR ( msgBuf, myThid )
201 STOP 'ABNORMAL END: S/R EXCH2_AD_PUT_RX1 (iBufr over limit)'
202 ENDIF
203
204 RETURN
205 END
206
207 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
208
209 CEH3 ;;; Local Variables: ***
210 CEH3 ;;; mode:fortran ***
211 CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22