/[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.1 - (show annotations) (download)
Sat May 30 21:18:59 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62e, checkpoint62d, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
take buffer copy from/to array out of S/R exch2_send/recv into new
 S/R exch2_put/get ; adjoint of send/recv no longer needed.

1 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_send_rx1.template,v 1.10 2009/05/20 21:01:45 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
38
39 C !INPUT/OUTPUT PARAMETERS:
40 C === Routine arguments ===
41 C tIlo, tIhi :: index range in I that will be filled in target "array"
42 C tIstride :: index step in I that will be filled in target "array"
43 C tJlo, tJhi :: index range in J that will be filled in target "array"
44 C tJstride :: index step in J that will be filled in target "array"
45 C tKlo, tKhi :: index range in K that will be filled in target "array"
46 C tKstride :: index step in K that will be filled in target "array"
47 C thisTile :: sending tile Id. number
48 C nN :: Neighbour entry that we are processing
49 C e2BufrRecSize :: Number of elements in each entry of e2Bufr1_RX
50 C iBufr :: number of buffer elements filled in
51 C e2Bufr1_RX :: Data transport buffer array. This array is used in one of
52 C :: two ways. For PUT communication the entry in the buffer
53 C :: associated with the source for this receive (determined
54 C :: from the opposing_send index) is read.
55 C :: For MSG communication the entry in the buffer associated
56 C :: with this neighbor of this tile is used as a receive
57 C :: location for loading a linear stream of bytes.
58 C array :: Source array where the data come from
59 C i1Lo, i1Hi :: I coordinate bounds of target array
60 C j1Lo, j1Hi :: J coordinate bounds of target array
61 C k1Lo, k1Hi :: K coordinate bounds of target array
62 C e2_msgHandles :: Synchronization and coordination data structure used to
63 C :: coordinate access to e2Bufr1_RX or to regulate message
64 C :: buffering. In PUT communication sender will increment
65 C :: handle entry once data is ready in buffer. Receiver will
66 C :: decrement handle once data is consumed from buffer.
67 C :: For MPI MSG communication MPI_Wait uses hanlde to check
68 C :: Isend has cleared. This is done in routine after receives.
69 C commSetting :: Mode of communication used to exchange with this neighbor
70 C myThid :: my Thread Id. number
71
72 INTEGER tILo, tIHi, tiStride
73 INTEGER tJLo, tJHi, tjStride
74 INTEGER tKLo, tKHi, tkStride
75 INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
76 INTEGER thisTile, nN
77 INTEGER e2BufrRecSize
78 INTEGER iBufr
79 _RX e2Bufr1_RX( e2BufrRecSize )
80 _RX array(i1Lo:i1Hi,j1Lo:j1Hi,k1Lo:k1Hi)
81 INTEGER e2_msgHandle(1)
82 INTEGER myThid
83 CHARACTER commSetting
84 CEOP
85
86 C !LOCAL VARIABLES:
87 C == Local variables ==
88 C itl,jtl,ktl :: Loop counters
89 C :: itl etc... target local
90 C :: itc etc... target canonical
91 C :: isl etc... source local
92 C :: isc etc... source canonical
93 C tgT :: Target tile Id. number
94 C itb, jtb :: Target local to canonical offsets
95 INTEGER itl, jtl, ktl
96 INTEGER itc, jtc
97 INTEGER isc, jsc
98 INTEGER isl, jsl
99 INTEGER tgT
100 INTEGER itb, jtb
101 INTEGER isb, jsb
102 INTEGER pi(2), pj(2), oi, oj
103
104 #ifdef W2_E2_DEBUG_ON
105 CHARACTER*(MAX_LEN_MBUF) msgBuf
106 #endif
107
108 c IF ( commSetting .EQ. 'P' ) THEN
109 C Need to check that buffer synchronisation token is decremented
110 C before filling buffer.
111 c ENDIF
112
113 tgT = exch2_neighbourId(nN, thisTile )
114 itb = exch2_tBasex(tgT)
115 jtb = exch2_tBasey(tgT)
116 isb = exch2_tBasex(thisTile)
117 jsb = exch2_tBasey(thisTile)
118 pi(1)=exch2_pij(1,nN,thisTile)
119 pi(2)=exch2_pij(2,nN,thisTile)
120 pj(1)=exch2_pij(3,nN,thisTile)
121 pj(2)=exch2_pij(4,nN,thisTile)
122 oi = exch2_oi(nN,thisTile)
123 oj = exch2_oj(nN,thisTile)
124 #ifdef W2_E2_DEBUG_ON
125 WRITE(msgBuf,'(A,I5,A,I5)')
126 & 'EXCH2_PUT_RX1 sourceTile=', thisTile, 'targetTile=', tgT
127 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
128 I SQUEEZE_BOTH, myThid )
129 #endif /* W2_E2_DEBUG_ON */
130 iBufr=0
131 DO ktl=tKlo,tKhi,tKStride
132 DO jtl=tJLo, tJHi, tjStride
133 DO itl=tILo, tIHi, tiStride
134 iBufr=iBufr+1
135 itc = itl+itb
136 jtc = jtl+jtb
137 isc = pi(1)*itc+pi(2)*jtc+oi
138 jsc = pj(1)*itc+pj(2)*jtc+oj
139 isl = isc-isb
140 jsl = jsc-jsb
141 #ifdef W2_E2_DEBUG_ON
142 WRITE(msgBuf,'(A,2I5)')
143 & 'EXCH2_PUT_RX1 target t(itl,jtl) =', itl, jtl
144 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
145 I SQUEEZE_RIGHT, myThid )
146 WRITE(msgBuf,'(A,2I5)')
147 & ' source (isl,jsl) =', isl, jsl
148 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
149 I SQUEEZE_RIGHT, myThid )
150 IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
151 WRITE(msgBuf,'(A,2I5)')
152 & ' *** isl is out of bounds'
153 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
154 I SQUEEZE_RIGHT, myThid )
155 ENDIF
156 IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
157 WRITE(msgBuf,'(A,2I5)')
158 & ' *** jsl is out of bounds'
159 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
160 I SQUEEZE_RIGHT, myThid )
161 ENDIF
162 #endif /* W2_E2_DEBUG_ON */
163 #ifdef W2_USE_E2_SAFEMODE
164 IF ( iBufr .GT. e2BufrRecSize ) THEN
165 C Ran off end of buffer. This should not happen
166 STOP 'EXCH2_PUT_RX1:: E2BUFR LIMIT EXCEEDED'
167 ENDIF
168 IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
169 C Forward mode send getting from points outside of the
170 C tiles exclusive domain bounds in X. This should not happen
171 STOP 'EXCH2_PUT_RX1:: ISL OUTSIDE TILE EXCLUSIVE DOMAIN'
172 ENDIF
173 IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
174 C Forward mode send getting from points outside of the
175 C tiles exclusive domain bounds in Y. This should not happen
176 STOP 'EXCH2_PUT_RX1:: JSL OUTSIDE TILE EXCLUSIVE DOMAIN'
177 ENDIF
178 #endif /* W2_USE_E2_SAFEMODE */
179 e2Bufr1_RX(iBufr) = array(isl,jsl,ktl)
180 ENDDO
181 ENDDO
182 ENDDO
183
184 RETURN
185 END
186
187 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
188
189 CEH3 ;;; Local Variables: ***
190 CEH3 ;;; mode:fortran ***
191 CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22