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

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

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


Revision 1.8 - (hide annotations) (download)
Tue May 12 19:44:58 2009 UTC (15 years ago) by jmc
Branch: MAIN
Changes since 1.7: +3 -2 lines
new header files "W2_EXCH2_SIZE.h" (taken out of W2_EXCH2_TOPOLOGY.h)
             and "W2_EXCH2_BUFFER.h" (taken out of W2_EXCH2_PARAMS.h)

1 jmc 1.8 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_recv_rx1.template,v 1.7 2008/08/05 18:31:55 cnh 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_RX1(
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_msgHandles, myTiles,
17     I commSetting,
18     I myThid )
19    
20     IMPLICIT NONE
21    
22 jmc 1.4 #include "SIZE.h"
23     #include "EEPARAMS.h"
24     #include "EESUPPORT.h"
25 jmc 1.8 #include "W2_EXCH2_SIZE.h"
26 afe 1.1 #include "W2_EXCH2_TOPOLOGY.h"
27    
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 jmc 1.3 c INTEGER itc, jtc, ktc
82     c INTEGER isc, jsc, ksc
83     c INTEGER isl, jsl, ksl
84 afe 1.1 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 jmc 1.3 c INTEGER I, nri, nrj, nrk
95     INTEGER I
96 afe 1.1
97     C MPI setup
98 jmc 1.3 #ifdef ALLOW_USE_MPI
99     c INTEGER theTag, theSize, theType
100     INTEGER theTag, theType
101 afe 1.1 INTEGER sProc, tProc
102 jmc 1.3 INTEGER nri, nrj, nrk
103 afe 1.1 INTEGER mpiStatus(MPI_STATUS_SIZE), mpiRc
104 jmc 1.3 #ifdef W2_E2_DEBUG_ON
105     CHARACTER*(MAX_LEN_MBUF) messageBuffer
106     #endif
107 afe 1.1 #endif
108    
109     tt=exch2_neighbourId(nN, thisTile )
110 jmc 1.6 oN=exch2_opposingSend(nN, thisTile )
111 afe 1.1
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 jmc 1.6 oN = exch2_opposingSend(nN, thisTile )
120 afe 1.1 mb = oN
121     DO I=1,nt
122     IF ( myTiles(I) .EQ. tt ) THEN
123     nb = I
124     ir = 1
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 jmc 1.8 theTag = (tt-1)*W2_maxNeighbours + oN
135 afe 1.1 tProc = exch2_tProc(thisTile)-1
136     sProc = exch2_tProc(tt)-1
137     theType = MPI_REAL8
138     nri = (tIhi-tIlo+1)/tiStride
139     nrj = (tJhi-tJlo+1)/tjStride
140     nrk = (tKhi-tKlo+1)/tkStride
141     iBufr = nri*nrj*nrk
142     CALL MPI_Recv( e2Bufr1_RX(1,mb,nb,ir), iBufr, theType, sProc,
143     & theTag, MPI_COMM_MODEL, mpiStatus, mpiRc )
144     #ifdef W2_E2_DEBUG_ON
145     WRITE(messageBuffer,'(A,I4,A,I4,A)') ' RECV FROM TILE=', tt,
146     & ' (proc = ',sProc,')'
147     CALL PRINT_MESSAGE(messageBuffer,
148     I standardMessageUnit,SQUEEZE_RIGHT,
149     I myThid)
150 heimbach 1.5 WRITE(messageBuffer,'(A,I4,A,I4,A)') ' INTO TILE=', thisTile,
151 afe 1.1 & ' (proc = ',tProc,')'
152     CALL PRINT_MESSAGE(messageBuffer,
153     I standardMessageUnit,SQUEEZE_RIGHT,
154     I myThid)
155     WRITE(messageBuffer,'(A,I10)') ' TAG=', theTag
156     CALL PRINT_MESSAGE(messageBuffer,
157     I standardMessageUnit,SQUEEZE_RIGHT,
158     I myThid)
159     WRITE(messageBuffer,'(A,I4)') ' NEL=', iBufr
160     CALL PRINT_MESSAGE(messageBuffer,
161     I standardMessageUnit,SQUEEZE_RIGHT,
162     I myThid)
163     #endif /* W2_E2_DEBUG_ON */
164     C Set mb to neighbour entry
165     C Set nt to this tiles rank
166     mb = nN
167     #endif
168     ELSE
169     STOP 'EXCH2_RECV_RX1:: commSetting VALUE IS INVALID'
170     ENDIF
171    
172     iBufr=0
173     DO ktl=tKlo,tKhi,tKStride
174     DO jtl=tJLo, tJHi, tjStride
175     DO itl=tILo, tIHi, tiStride
176     C Read from e2Bufr1_RX(iBufr,mb,nb)
177     iBufr=iBufr+1
178     array(itl,jtl,ktl)=e2Bufr1_RX(iBufr,mb,nb,ir)
179     ENDDO
180     ENDDO
181     ENDDO
182    
183     RETURN
184     END
185 edhill 1.2
186     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
187    
188     CEH3 ;;; Local Variables: ***
189     CEH3 ;;; mode:fortran ***
190     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22