/[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.6 - (show annotations) (download)
Fri Aug 1 00:45:16 2008 UTC (16 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61b
Changes since 1.5: +26 -41 lines
change index bounds in rx2_cube exchanges (new S/R: EXCH2_GET_UV_BOUNDS)
- no longer depend on the order sequence (N,S,E,W).
- 3rd exchange no longer needed (tested with 24 tiles).
- same modif to hand-written adjoint S/R (global_ocean.cs32x15: zero diff)
- exch_UV_A-grid readily available (but not yet tested).

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

  ViewVC Help
Powered by ViewVC 1.1.22