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

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

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


Revision 1.2 - (show annotations) (download)
Mon Apr 5 15:27:06 2004 UTC (20 years, 2 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint52n_post, checkpoint53d_post, checkpoint54a_pre, checkpoint55c_post, checkpoint54e_post, checkpoint54a_post, checkpoint53c_post, checkpoint57k_post, checkpoint55d_pre, checkpoint57d_post, checkpoint57g_post, checkpoint57b_post, checkpoint57c_pre, checkpoint55j_post, checkpoint56b_post, checkpoint57i_post, checkpoint57e_post, checkpoint55h_post, checkpoint53b_post, checkpoint57g_pre, checkpoint54b_post, checkpoint53b_pre, checkpoint55b_post, checkpoint54d_post, checkpoint56c_post, checkpoint52m_post, checkpoint55, checkpoint53a_post, checkpoint57f_pre, checkpoint57a_post, checkpoint54, checkpoint54f_post, checkpoint55g_post, checkpoint55f_post, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, checkpoint53, eckpoint57e_pre, checkpoint57h_done, checkpoint53g_post, checkpoint57f_post, checkpoint57c_post, checkpoint55e_post, checkpoint53f_post, checkpoint55a_post, checkpoint53d_pre, checkpoint54c_post, checkpoint57j_post, checkpoint57h_pre, checkpoint57l_post, checkpoint57h_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.1: +9 -0 lines
 o fix "make clean"
 o add CVS Header: and Name:

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

  ViewVC Help
Powered by ViewVC 1.1.22