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

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

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


Revision 1.4 - (show annotations) (download)
Tue Aug 5 18:31:55 2008 UTC (15 years, 10 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61c, checkpoint61n, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i
Changes since 1.3: +1 -7 lines
Olivers awesome tag fixes.

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

  ViewVC Help
Powered by ViewVC 1.1.22