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

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

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


Revision 1.4 - (hide annotations) (download)
Tue May 12 19:44:58 2009 UTC (15 years, 1 month ago) by jmc
Branch: MAIN
Changes since 1.3: +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.4 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_recv_rx1_ad.template,v 1.3 2008/08/05 18:31:55 cnh Exp $
2 heimbach 1.1 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 jmc 1.4 #include "W2_EXCH2_SIZE.h"
26 heimbach 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_msgHandle :: 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_msgHandle(1)
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     c INTEGER itc, jtc, ktc
82     c INTEGER isc, jsc, ksc
83     c 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     c INTEGER I, nri, nrj, nrk
95     INTEGER I
96    
97     C MPI setup
98     #ifdef ALLOW_USE_MPI
99     INTEGER theTag, theType, theHandle
100     INTEGER sProc, tProc
101     INTEGER nri, nrj, nrk
102     INTEGER mpiRc
103     #ifdef W2_E2_DEBUG_ON
104     CHARACTER*(MAX_LEN_MBUF) messageBuffer
105     #endif
106     #endif
107    
108     tt=exch2_neighbourId(nN, thisTile )
109 jmc 1.2 oN=exch2_opposingSend(nN, thisTile )
110 heimbach 1.1
111     C Handle receive end data transport according to communication mechanism between
112     C source and target tile
113     IF ( commSetting .EQ. 'P' ) THEN
114     C 1 Need to check and spin on data ready assertion for multithreaded mode, for now do nothing i.e.
115     C assume only one thread per process.
116    
117     C 2 Need to set e2Bufr to use put buffer from opposing send.
118     mb = oN
119     DO I=1,nt
120     IF ( myTiles(I) .EQ. tt ) THEN
121     nb = I
122     ir = 1
123     ENDIF
124     ENDDO
125     C Get data from e2Bufr(1,mb,nb)
126     ELSEIF ( commSetting .EQ. 'M' ) THEN
127     #ifdef ALLOW_USE_MPI
128     C Setup MPI stuff here
129     nb = thisI
130     mb = nN
131     ir = 2
132     #endif
133     ELSE
134     STOP 'EXCH2_RECV_RX1_AD:: commSetting VALUE IS INVALID'
135     ENDIF
136    
137     iBufr=0
138     DO ktl=tKlo,tKhi,tKStride
139     DO jtl=tJLo, tJHi, tjStride
140     DO itl=tILo, tIHi, tiStride
141     C Read from e2Bufr1_RX(iBufr,mb,nb)
142     iBufr=iBufr+1
143     e2Bufr1_RX(iBufr,mb,nb,ir) = array(itl,jtl,ktl)
144     array(itl,jtl,ktl) = 0. _d 0
145     ENDDO
146     ENDDO
147     ENDDO
148    
149     IF ( commSetting .EQ. 'P' ) THEN
150     ELSEIF ( commSetting .EQ. 'M' ) THEN
151     #ifdef ALLOW_USE_MPI
152     C Setup MPI stuff here
153     nb = thisI
154     mb = nN
155     ir = 2
156 jmc 1.4 theTag = (tt-1)*W2_maxNeighbours + oN
157 heimbach 1.1 tProc = exch2_tProc(thisTile)-1
158     sProc = exch2_tProc(tt)-1
159     theType = MPI_REAL8
160     nri = (tIhi-tIlo+1)/tiStride
161     nrj = (tJhi-tJlo+1)/tjStride
162     nrk = (tKhi-tKlo+1)/tkStride
163     iBufr = nri*nrj*nrk
164     CALL MPI_Isend( e2Bufr1_RX(1,mb,nb,ir), iBufr, theType, sProc,
165     & theTag, MPI_COMM_MODEL, theHandle, mpiRc )
166     C Store MPI_Wait token in messageHandle.
167     e2_msgHandle(1) = theHandle
168     #ifdef W2_E2_DEBUG_ON
169     WRITE(messageBuffer,'(A,I4,A,I4,A)') ' SEND TO TILE=', tt,
170     & ' (proc = ',sProc,')'
171     CALL PRINT_MESSAGE(messageBuffer,
172     I standardMessageUnit,SQUEEZE_RIGHT,
173     I myThid)
174     WRITE(messageBuffer,'(A,I4,A,I4,A)') ' INTO TILE=', thisTile,
175     & ' (proc = ',tProc,')'
176     CALL PRINT_MESSAGE(messageBuffer,
177     I standardMessageUnit,SQUEEZE_RIGHT,
178     I myThid)
179     WRITE(messageBuffer,'(A,I10)') ' TAG=', theTag
180     CALL PRINT_MESSAGE(messageBuffer,
181     I standardMessageUnit,SQUEEZE_RIGHT,
182     I myThid)
183     WRITE(messageBuffer,'(A,I4)') ' NEL=', iBufr
184     CALL PRINT_MESSAGE(messageBuffer,
185     I standardMessageUnit,SQUEEZE_RIGHT,
186     I myThid)
187     #endif /* W2_E2_DEBUG_ON */
188     #endif
189     ELSE
190     STOP 'EXCH2_RECV_RX1_AD:: commSetting VALUE IS INVALID'
191     ENDIF
192    
193     RETURN
194     END
195    
196     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
197    
198     CEH3 ;;; Local Variables: ***
199     CEH3 ;;; mode:fortran ***
200     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22