/[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.1 - (hide annotations) (download)
Fri Jan 9 20:46:09 2004 UTC (20 years, 4 months ago) by afe
Branch: MAIN
CVS Tags: checkpoint52l_pre, hrcube4, checkpoint52j_post, checkpoint52l_post, checkpoint52k_post, checkpoint52f_post, hrcube5, checkpoint52i_post, checkpoint52j_pre, checkpoint52i_pre, checkpoint52h_pre, hrcube_2, hrcube_3
Added exch2 routines and pointed hs94.cs-32x32x5 at them

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

  ViewVC Help
Powered by ViewVC 1.1.22