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

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

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


Revision 1.3 - (show annotations) (download)
Fri Jul 22 18:21:55 2005 UTC (18 years, 11 months ago) by jmc
Branch: MAIN
Changes since 1.2: +13 -10 lines
comment out unused variable declaration (get less warnings for unused var)

1 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_recv_rx2.template,v 1.2 2004/04/05 15:27:06 edhill Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 SUBROUTINE EXCH2_RECV_RX2(
7 I tIlo, tIhi, tiStride,
8 I tJlo, tJhi, tjStride,
9 I tKlo, tKhi, tkStride,
10 I thisTile, thisI, nN,
11 I e2Bufr1_RX, e2Bufr2_RX, e2BufrRecSize,
12 I mnb, nt,
13 U array1,
14 I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
15 U array2,
16 I i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,
17 U e2_msgHandles, myTiles,
18 I commSetting,
19 I myThid )
20
21 IMPLICIT NONE
22
23 C
24 #include "W2_OPTIONS.h"
25 #include "W2_EXCH2_TOPOLOGY.h"
26
27 #include "EEPARAMS.h"
28 C
29 C === Routine arguments ===
30 C tIlo, tIhi, tIstride :: index range in I that will be filled in target "array"
31 C tJlo, tJhi, tJstride :: index range in J that will be filled in target "array"
32 C tKlo, tKhi, tKstride :: index range in K that will be filled in target "array"
33 C thisTile :: Rank of the receiveing tile
34 C thisI :: Index of the receiving tile within this process (used
35 C :: to select buffer slots that are allowed).
36 C nN :: Neighbour entry that we are processing
37 C e2Bufr1_RX :: Data transport buffer array. This array is used in one of
38 C :: two ways. For PUT communication the entry in the buffer
39 C :: associated with the source for this receive (determined
40 C :: from the opposing_send index) is read. For MSG communication
41 C :: the entry in the buffer associated with this neighbor of this
42 C :: tile is used as a receive location for loading a linear
43 C :: stream of bytes.
44 C e2BufrRecSize :: Number of elements in each entry of e2Bufr1_RX
45 C mnb :: Second dimension of e2Bufr1_RX
46 C nt :: Third dimension of e2Bufr1_RX
47 C array :: Target array that this receive writes to.
48 C i1Lo, i1Hi :: I coordinate bounds of target array
49 C j1Lo, j1Hi :: J coordinate bounds of target array
50 C k1Lo, k1Hi :: K coordinate bounds of target array
51 C e2_msgHandles :: Synchronization and coordination data structure used to coordinate access
52 C :: to e2Bufr1_RX or to regulate message buffering. In PUT communication
53 C :: sender will increment handle entry once data is ready in buffer.
54 C :: Receiver will decrement handle once data is consumed from buffer. For
55 C :: MPI MSG communication MPI_Wait uses hanlde to check Isend has cleared.
56 C :: This is done in routine after receives.
57 C myTiles :: List of nt tiles that this process owns.
58 C commSetting :: Mode of communication used to exchnage with this neighbor
59 C myThid :: Thread number of this instance of EXCH2_RECV_RX1
60 C
61 INTEGER tILo, tIHi, tiStride
62 INTEGER tJLo, tJHi, tjStride
63 INTEGER tKLo, tKHi, tkStride
64 INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
65 INTEGER i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi
66 INTEGER thisTile, nN, thisI
67 INTEGER e2BufrRecSize
68 INTEGER mnb, nt
69 _RX e2Bufr1_RX( e2BufrRecSize, mnb, nt, 2 )
70 _RX e2Bufr2_RX( e2BufrRecSize, mnb, nt, 2 )
71 _RX array1(i1Lo:i1Hi,j1Lo:j1Hi,k1Lo:k1Hi)
72 _RX array2(i2Lo:i2Hi,j2Lo:j2Hi,k2Lo:k2Hi)
73 INTEGER e2_msgHandles(2, mnb, nt)
74 INTEGER myThid
75 INTEGER myTiles(nt)
76 CHARACTER commSetting
77
78 C == Local variables ==
79 C itl, jtl, ktl :: Loop counters
80 C :: itl etc... target local
81 C :: itc etc... target canonical
82 C :: isl etc... source local
83 C :: isc etc... source canonical
84 INTEGER itl, jtl, ktl
85 c INTEGER itc, jtc, ktc
86 c INTEGER isc, jsc, ksc
87 c INTEGER isl, jsl, ksl
88 C tt :: Target tile
89 C iBufr1 :: Buffer counter
90 C iBufr2 ::
91 INTEGER tt
92 INTEGER iBufr1, iBufr2
93 C mb, nb :: Selects e2Bufr, msgHandle record to use
94 C ir ::
95 INTEGER mb, nb, ir
96 C oN :: Opposing send record number
97 INTEGER oN
98 C Loop counters
99 INTEGER I
100 INTEGER itl1reduce, jtl1reduce
101 INTEGER itl2reduce, jtl2reduce
102
103 C MPI setup
104 #include "SIZE.h"
105 #include "EESUPPORT.h"
106 #ifdef ALLOW_USE_MPI
107 INTEGER nri1, nrj1, nrk1
108 INTEGER nri2, nrj2, nrk2
109 INTEGER theTag1, theTag2, theType
110 c INTEGER theSize1, theSize2
111 INTEGER sProc, tProc
112 INTEGER mpiStatus(MPI_STATUS_SIZE), mpiRc
113 #ifdef W2_E2_DEBUG_ON
114 CHARACTER*(MAX_LEN_MBUF) messageBuffer
115 #endif
116 #endif
117
118 tt=exch2_neighbourId(nN, thisTile )
119 oN=exch2_opposingSend_record(nN, thisTile )
120 itl1reduce=0
121 jtl1reduce=0
122 itl2reduce=0
123 jtl2reduce=0
124 IF ( exch2_pi(1,oN,tt) .EQ. -1 ) itl1reduce=1
125 IF ( exch2_pj(1,oN,tt) .EQ. -1 ) itl1reduce=1
126 IF ( exch2_pi(2,oN,tt) .EQ. -1 ) jtl2reduce=1
127 IF ( exch2_pj(2,oN,tt) .EQ. -1 ) jtl2reduce=1
128
129 C Handle receive end data transport according to communication mechanism between
130 C source and target tile
131 IF ( commSetting .EQ. 'P' ) THEN
132 C 1 Need to check and spin on data ready assertion for multithreaded mode, for now do nothing i.e.
133 C assume only one thread per process.
134
135 C 2 Need to set e2Bufr to use put buffer from opposing send.
136 oN = exch2_opposingSend_record(nN, thisTile )
137 mb = oN
138 ir = 1
139 DO I=1,nt
140 IF ( myTiles(I) .EQ. tt ) THEN
141 nb = I
142 ENDIF
143 ENDDO
144 C Get data from e2Bufr(1,mb,nb)
145 ELSEIF ( commSetting .EQ. 'M' ) THEN
146 #ifdef ALLOW_USE_MPI
147 C Setup MPI stuff here
148 nb = thisI
149 mb = nN
150 ir = 2
151 theTag1 = (tt-1)*MAX_NEIGHBOURS*2 + oN-1
152 & + 10000*(
153 & (thisTile-1)*MAX_NEIGHBOURS*2 + oN-1
154 & )
155 theTag2 = (tt-1)*MAX_NEIGHBOURS*2 + MAX_NEIGHBOURS + oN-1
156 & + 10000*(
157 & (thisTile-1)*MAX_NEIGHBOURS*2 + MAX_NEIGHBOURS + oN-1
158 & )
159 tProc = exch2_tProc(thisTile)-1
160 sProc = exch2_tProc(tt)-1
161 theType = MPI_REAL8
162 nri1 = (tIhi-tIlo+1-itl1reduce)/tiStride
163 nrj1 = (tJhi-tJlo+1-jtl1reduce)/tjStride
164 nrk1 = (tKhi-tKlo+1)/tkStride
165 iBufr1 = nri1*nrj1*nrk1
166 nri2 = (tIhi-tIlo+1-itl2reduce)/tiStride
167 nrj2 = (tJhi-tJlo+1-jtl2reduce)/tjStride
168 nrk2 = (tKhi-tKlo+1)/tkStride
169 iBufr2 = nri2*nrj2*nrk2
170 CALL MPI_Recv( e2Bufr1_RX(1,mb,nb,ir), iBufr1, theType, sProc,
171 & theTag1, MPI_COMM_MODEL, mpiStatus, mpiRc )
172 CALL MPI_Recv( e2Bufr2_RX(1,mb,nb,ir), iBufr2, theType, sProc,
173 & theTag2, MPI_COMM_MODEL, mpiStatus, mpiRc )
174 #ifdef W2_E2_DEBUG_ON
175 WRITE(messageBuffer,'(A,I4,A,I4,A)') ' RECV FROM TILE=', tt,
176 & ' (proc = ',sProc,')'
177 CALL PRINT_MESSAGE(messageBuffer,
178 I standardMessageUnit,SQUEEZE_RIGHT,
179 I myThid)
180 WRITE(messageBuffer,'(A,I4,A,I4,A)') ' INTO TILE=', thisTile,
181 & ' (proc = ',tProc,')'
182 CALL PRINT_MESSAGE(messageBuffer,
183 I standardMessageUnit,SQUEEZE_RIGHT,
184 I myThid)
185 WRITE(messageBuffer,'(A,I10)') ' TAG1=', theTag1
186 CALL PRINT_MESSAGE(messageBuffer,
187 I standardMessageUnit,SQUEEZE_RIGHT,
188 I myThid)
189 WRITE(messageBuffer,'(A,I4)') ' NEL1=', iBufr1
190 CALL PRINT_MESSAGE(messageBuffer,
191 I standardMessageUnit,SQUEEZE_RIGHT,
192 I myThid)
193 WRITE(messageBuffer,'(A,I10)') ' TAG2=', theTag2
194 CALL PRINT_MESSAGE(messageBuffer,
195 I standardMessageUnit,SQUEEZE_RIGHT,
196 I myThid)
197 WRITE(messageBuffer,'(A,I4)') ' NEL2=', iBufr2
198 CALL PRINT_MESSAGE(messageBuffer,
199 I standardMessageUnit,SQUEEZE_RIGHT,
200 I myThid)
201 #endif /* W2_E2_DEBUG_ON */
202 C Set mb to neighbour entry
203 C Set nt to this tiles rank
204 mb = nN
205 #endif
206 ELSE
207 STOP 'EXCH2_RECV_RX2:: commSetting VALUE IS INVALID'
208 ENDIF
209
210 iBufr1=0
211 DO ktl=tKlo,tKhi,tKStride
212 DO jtl=tJLo+jtl1reduce, tJHi, tjStride
213 DO itl=tILo+itl1reduce, tIHi, tiStride
214 C Read from e2Bufr1_RX(iBufr,mb,nb)
215 iBufr1=iBufr1+1
216 array1(itl,jtl,ktl)=e2Bufr1_RX(iBufr1,mb,nb,ir)
217 ENDDO
218 ENDDO
219 ENDDO
220
221 iBufr2=0
222 DO ktl=tKlo,tKhi,tKStride
223 DO jtl=tJLo+jtl2reduce, tJHi, tjStride
224 DO itl=tILo+itl2reduce, tIHi, tiStride
225 C Read from e2Bufr1_RX(iBufr,mb,nb)
226 iBufr2=iBufr2+1
227 array2(itl,jtl,ktl)=e2Bufr2_RX(iBufr2,mb,nb,ir)
228 ENDDO
229 ENDDO
230 ENDDO
231
232 RETURN
233 END
234
235 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
236
237 CEH3 ;;; Local Variables: ***
238 CEH3 ;;; mode:fortran ***
239 CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22