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

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

  ViewVC Help
Powered by ViewVC 1.1.22