/[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.4 - (show annotations) (download)
Sun Jul 24 01:21:36 2005 UTC (18 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint57t_post, checkpoint57o_post, checkpoint58e_post, mitgcm_mapl_00, checkpoint58u_post, checkpoint58w_post, checkpoint57m_post, checkpoint57s_post, checkpoint60, checkpoint61, checkpoint58r_post, checkpoint57y_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58h_post, checkpoint57y_pre, checkpoint58q_post, checkpoint57v_post, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint57r_post, checkpoint59, checkpoint58, checkpoint58f_post, checkpoint57x_post, checkpoint57n_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint61a, checkpoint58b_post, checkpoint58m_post
Changes since 1.3: +6 -8 lines
no need for CPP_OPTIONS.h ; include CPP_EEOPTIONS.h instead (like other
exch2 S/R).

1 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_recv_rx2.template,v 1.3 2005/07/22 18:21:55 jmc Exp $
2 C $Name: $
3
4 #include "CPP_EEOPTIONS.h"
5 #include "W2_OPTIONS.h"
6
7 SUBROUTINE EXCH2_RECV_RX2(
8 I tIlo, tIhi, tiStride,
9 I tJlo, tJhi, tjStride,
10 I tKlo, tKhi, tkStride,
11 I thisTile, thisI, nN,
12 I e2Bufr1_RX, e2Bufr2_RX, e2BufrRecSize,
13 I mnb, nt,
14 U array1,
15 I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
16 U array2,
17 I i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,
18 U e2_msgHandles, myTiles,
19 I commSetting,
20 I myThid )
21
22 IMPLICIT NONE
23
24 #include "SIZE.h"
25 #include "EEPARAMS.h"
26 #include "EESUPPORT.h"
27 #include "W2_EXCH2_TOPOLOGY.h"
28
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 #ifdef ALLOW_USE_MPI
105 INTEGER nri1, nrj1, nrk1
106 INTEGER nri2, nrj2, nrk2
107 INTEGER theTag1, theTag2, theType
108 c INTEGER theSize1, theSize2
109 INTEGER sProc, tProc
110 INTEGER mpiStatus(MPI_STATUS_SIZE), mpiRc
111 #ifdef W2_E2_DEBUG_ON
112 CHARACTER*(MAX_LEN_MBUF) messageBuffer
113 #endif
114 #endif
115
116 tt=exch2_neighbourId(nN, thisTile )
117 oN=exch2_opposingSend_record(nN, thisTile )
118 itl1reduce=0
119 jtl1reduce=0
120 itl2reduce=0
121 jtl2reduce=0
122 IF ( exch2_pi(1,oN,tt) .EQ. -1 ) itl1reduce=1
123 IF ( exch2_pj(1,oN,tt) .EQ. -1 ) itl1reduce=1
124 IF ( exch2_pi(2,oN,tt) .EQ. -1 ) jtl2reduce=1
125 IF ( exch2_pj(2,oN,tt) .EQ. -1 ) jtl2reduce=1
126
127 C Handle receive end data transport according to communication mechanism between
128 C source and target tile
129 IF ( commSetting .EQ. 'P' ) THEN
130 C 1 Need to check and spin on data ready assertion for multithreaded mode, for now do nothing i.e.
131 C assume only one thread per process.
132
133 C 2 Need to set e2Bufr to use put buffer from opposing send.
134 oN = exch2_opposingSend_record(nN, thisTile )
135 mb = oN
136 ir = 1
137 DO I=1,nt
138 IF ( myTiles(I) .EQ. tt ) THEN
139 nb = I
140 ENDIF
141 ENDDO
142 C Get data from e2Bufr(1,mb,nb)
143 ELSEIF ( commSetting .EQ. 'M' ) THEN
144 #ifdef ALLOW_USE_MPI
145 C Setup MPI stuff here
146 nb = thisI
147 mb = nN
148 ir = 2
149 theTag1 = (tt-1)*MAX_NEIGHBOURS*2 + oN-1
150 & + 10000*(
151 & (thisTile-1)*MAX_NEIGHBOURS*2 + oN-1
152 & )
153 theTag2 = (tt-1)*MAX_NEIGHBOURS*2 + MAX_NEIGHBOURS + oN-1
154 & + 10000*(
155 & (thisTile-1)*MAX_NEIGHBOURS*2 + MAX_NEIGHBOURS + oN-1
156 & )
157 tProc = exch2_tProc(thisTile)-1
158 sProc = exch2_tProc(tt)-1
159 theType = MPI_REAL8
160 nri1 = (tIhi-tIlo+1-itl1reduce)/tiStride
161 nrj1 = (tJhi-tJlo+1-jtl1reduce)/tjStride
162 nrk1 = (tKhi-tKlo+1)/tkStride
163 iBufr1 = nri1*nrj1*nrk1
164 nri2 = (tIhi-tIlo+1-itl2reduce)/tiStride
165 nrj2 = (tJhi-tJlo+1-jtl2reduce)/tjStride
166 nrk2 = (tKhi-tKlo+1)/tkStride
167 iBufr2 = nri2*nrj2*nrk2
168 CALL MPI_Recv( e2Bufr1_RX(1,mb,nb,ir), iBufr1, theType, sProc,
169 & theTag1, MPI_COMM_MODEL, mpiStatus, mpiRc )
170 CALL MPI_Recv( e2Bufr2_RX(1,mb,nb,ir), iBufr2, theType, sProc,
171 & theTag2, MPI_COMM_MODEL, mpiStatus, mpiRc )
172 #ifdef W2_E2_DEBUG_ON
173 WRITE(messageBuffer,'(A,I4,A,I4,A)') ' RECV FROM TILE=', tt,
174 & ' (proc = ',sProc,')'
175 CALL PRINT_MESSAGE(messageBuffer,
176 I standardMessageUnit,SQUEEZE_RIGHT,
177 I myThid)
178 WRITE(messageBuffer,'(A,I4,A,I4,A)') ' INTO TILE=', thisTile,
179 & ' (proc = ',tProc,')'
180 CALL PRINT_MESSAGE(messageBuffer,
181 I standardMessageUnit,SQUEEZE_RIGHT,
182 I myThid)
183 WRITE(messageBuffer,'(A,I10)') ' TAG1=', theTag1
184 CALL PRINT_MESSAGE(messageBuffer,
185 I standardMessageUnit,SQUEEZE_RIGHT,
186 I myThid)
187 WRITE(messageBuffer,'(A,I4)') ' NEL1=', iBufr1
188 CALL PRINT_MESSAGE(messageBuffer,
189 I standardMessageUnit,SQUEEZE_RIGHT,
190 I myThid)
191 WRITE(messageBuffer,'(A,I10)') ' TAG2=', theTag2
192 CALL PRINT_MESSAGE(messageBuffer,
193 I standardMessageUnit,SQUEEZE_RIGHT,
194 I myThid)
195 WRITE(messageBuffer,'(A,I4)') ' NEL2=', iBufr2
196 CALL PRINT_MESSAGE(messageBuffer,
197 I standardMessageUnit,SQUEEZE_RIGHT,
198 I myThid)
199 #endif /* W2_E2_DEBUG_ON */
200 C Set mb to neighbour entry
201 C Set nt to this tiles rank
202 mb = nN
203 #endif
204 ELSE
205 STOP 'EXCH2_RECV_RX2:: commSetting VALUE IS INVALID'
206 ENDIF
207
208 iBufr1=0
209 DO ktl=tKlo,tKhi,tKStride
210 DO jtl=tJLo+jtl1reduce, tJHi, tjStride
211 DO itl=tILo+itl1reduce, tIHi, tiStride
212 C Read from e2Bufr1_RX(iBufr,mb,nb)
213 iBufr1=iBufr1+1
214 array1(itl,jtl,ktl)=e2Bufr1_RX(iBufr1,mb,nb,ir)
215 ENDDO
216 ENDDO
217 ENDDO
218
219 iBufr2=0
220 DO ktl=tKlo,tKhi,tKStride
221 DO jtl=tJLo+jtl2reduce, tJHi, tjStride
222 DO itl=tILo+itl2reduce, tIHi, tiStride
223 C Read from e2Bufr1_RX(iBufr,mb,nb)
224 iBufr2=iBufr2+1
225 array2(itl,jtl,ktl)=e2Bufr2_RX(iBufr2,mb,nb,ir)
226 ENDDO
227 ENDDO
228 ENDDO
229
230 RETURN
231 END
232
233 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
234
235 CEH3 ;;; Local Variables: ***
236 CEH3 ;;; mode:fortran ***
237 CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22