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

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

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


Revision 1.1 - (show annotations) (download)
Fri Jul 27 22:15:23 2007 UTC (16 years, 11 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59g, checkpoint59f, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint61a, checkpoint60, checkpoint61
Preparing exch2 adjoint, based on hand-written exch2 templates.

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

  ViewVC Help
Powered by ViewVC 1.1.22