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

Annotation of /MITgcm/pkg/exch2/exch2_recv_rx2.template

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


Revision 1.9 - (hide annotations) (download)
Wed May 20 21:01:45 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61o
Changes since 1.8: +2 -2 lines
use the right MPI type in MPI_SEND/RECV call. (replace MPI_REAL8
 by _MPI_TYPE_RX in template)

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

  ViewVC Help
Powered by ViewVC 1.1.22