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

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

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


Revision 1.1 - (show annotations) (download)
Fri Jan 9 20:46:09 2004 UTC (20 years, 4 months ago) by afe
Branch: MAIN
CVS Tags: checkpoint52f_post
Added exch2 routines and pointed hs94.cs-32x32x5 at them

1 #include "CPP_OPTIONS.h"
2
3 SUBROUTINE EXCH2_SEND_RX1 (
4 I tIlo, tIhi, tiStride,
5 I tJlo, tJhi, tjStride,
6 I tKlo, tKhi, tkStride,
7 I thisTile, nN,
8 I e2Bufr1_RX, e2BufrRecSize,
9 I array,
10 I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
11 O e2_msgHandle,
12 I commSetting, myThid )
13
14 IMPLICIT NONE
15
16 C
17 #include "W2_OPTIONS.h"
18 #include "W2_EXCH2_TOPOLOGY.h"
19
20 #include "EEPARAMS.h"
21 CHARACTER*(MAX_LEN_MBUF) messageBuffer
22 C
23 C === Routine arguments ===
24 INTEGER tILo, tIHi, tiStride
25 INTEGER tJLo, tJHi, tjStride
26 INTEGER tKLo, tKHi, tkStride
27 INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
28 INTEGER thisTile, nN
29 INTEGER e2BufrRecSize
30 _RX e2Bufr1_RX( e2BufrRecSize )
31 _RX array(i1Lo:i1Hi,j1Lo:j1Hi,k1Lo:k1Hi)
32 INTEGER e2_msgHandle(1)
33 INTEGER myThid
34 CHARACTER commSetting
35
36 C == Local variables ==
37 C itl, jtl, ktl :: Loop counters
38 C :: itl etc... target local
39 C :: itc etc... target canonical
40 C :: isl etc... source local
41 C :: isc etc... source canonical
42 INTEGER itl, jtl, ktl
43 INTEGER itc, jtc, ktc
44 INTEGER isc, jsc, ksc
45 INTEGER isl, jsl, ksl
46 C tt :: Target tile
47 C itb, jtb :: Target local to canonical offsets
48 C
49 INTEGER tt
50 INTEGER itb, jtb
51 INTEGER isb, jsb
52 INTEGER pi(2), pj(2), oi, oj
53 INTEGER iBufr
54
55 C MPI setup
56 #include "SIZE.h"
57 #include "EESUPPORT.h"
58 INTEGER theTag, theType, theHandle
59 INTEGER sProc, tProc, mpiRc
60
61 IF ( commSetting .EQ. 'P' ) THEN
62 C Need to check that buffer synchronisation token is decremented
63 C before filling buffer.
64 ENDIF
65
66 tt=exch2_neighbourId(nN, thisTile )
67 itb=exch2_tbasex(tt)
68 jtb=exch2_tbasey(tt)
69 isb=exch2_tbasex(thisTile)
70 jsb=exch2_tbasey(thisTile)
71 pi(1)=exch2_pi(1,nN,thisTile)
72 pi(2)=exch2_pi(2,nN,thisTile)
73 pj(1)=exch2_pj(1,nN,thisTile)
74 pj(2)=exch2_pj(2,nN,thisTile)
75 oi=exch2_oi(nN,thisTile)
76 oj=exch2_oj(nN,thisTile)
77 iBufr=0
78 #ifdef W2_E2_DEBUG_ON
79 WRITE(messageBuffer,'(A,I4,A,I4)') 'EXCH2_SEND_RX1 sourceTile= ', thisTile,
80 & 'targetTile= ',tt
81 CALL PRINT_MESSAGE(messageBuffer,
82 I standardMessageUnit,SQUEEZE_BOTH,
83 I myThid)
84 #endif /* W2_E2_DEBUG_ON */
85 DO ktl=tKlo,tKhi,tKStride
86 DO jtl=tJLo, tJHi, tjStride
87 DO itl=tILo, tIHi, tiStride
88 iBufr=iBufr+1
89 itc=itl+itb
90 jtc=jtl+jtb
91 isc=pi(1)*itc+pi(2)*jtc+oi
92 jsc=pj(1)*itc+pj(2)*jtc+oj
93 isl=isc-isb
94 jsl=jsc-jsb
95 e2Bufr1_RX(iBufr)=array(isl,jsl,ktl)
96 #ifdef W2_E2_DEBUG_ON
97 WRITE(messageBuffer,'(A,2I4)') 'EXCH2_SEND_RX1 target t(itl,jtl) = ', itl, jtl
98 CALL PRINT_MESSAGE(messageBuffer,
99 I standardMessageUnit,SQUEEZE_RIGHT,
100 I myThid)
101 WRITE(messageBuffer,'(A,2I4)') ' source (isl,jsl) = ', isl, jsl
102 CALL PRINT_MESSAGE(messageBuffer,
103 I standardMessageUnit,SQUEEZE_RIGHT,
104 I myThid)
105 IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
106 WRITE(messageBuffer,'(A,2I4)') ' *** isl is out of bounds'
107 CALL PRINT_MESSAGE(messageBuffer,
108 I standardMessageUnit,SQUEEZE_RIGHT,
109 I myThid)
110 ENDIF
111 IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
112 WRITE(messageBuffer,'(A,2I4)') ' *** jsl is out of bounds'
113 CALL PRINT_MESSAGE(messageBuffer,
114 I standardMessageUnit,SQUEEZE_RIGHT,
115 I myThid)
116 ENDIF
117 #endif /* W2_E2_DEBUG_ON */
118 #ifdef W2_USE_E2_SAFEMODE
119 IF ( iBufr .GT. e2BufrRecSize ) THEN
120 C Ran off end of buffer. This should not happen
121 STOP 'EXCH2_SEND_RX1:: E2BUFR LIMIT EXCEEDED'
122 ENDIF
123 IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
124 C Forward mode send getting from points outside of the
125 C tiles exclusive domain bounds in X. This should not happen
126 STOP 'EXCH2_SEND_RX1:: ISL OUTSIDE TILE EXCLUSIVE DOMAIN'
127 ENDIF
128 IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
129 C Forward mode send getting from points outside of the
130 C tiles exclusive domain bounds in Y. This should not happen
131 STOP 'EXCH2_SEND_RX1:: JSL OUTSIDE TILE EXCLUSIVE DOMAIN'
132 ENDIF
133 #endif /* W2_USE_E2_SAFEMODE */
134 ENDDO
135 ENDDO
136 ENDDO
137
138 C Do data transport depending on communication mechanism between source and target tile
139 IF ( commSetting .EQ. 'P' ) THEN
140 C Need to set data ready assertion (increment buffer synchronisation token)
141 C for multithreaded mode, for now do nothing i.e. assume only one thread per process.
142 ELSEIF ( commSetting .EQ. 'M' ) THEN
143 #ifdef ALLOW_USE_MPI
144 C Setup MPI stuff here
145 theTag = (thisTile-1)*MAX_NEIGHBOURS + nN
146 & + 10000*(
147 & (tt-1)*MAX_NEIGHBOURS + nN
148 & )
149 tProc = exch2_tProc(tt)-1
150 sProc = exch2_tProc(thisTile)-1
151 theType = MPI_REAL8
152 #ifdef W2_E2_DEBUG_ON
153 WRITE(messageBuffer,'(A,I4,A,I4,A)') ' SEND FROM TILE=', thisTile,
154 & ' (proc = ',sProc,')'
155 CALL PRINT_MESSAGE(messageBuffer,
156 I standardMessageUnit,SQUEEZE_RIGHT,
157 I myThid)
158 WRITE(messageBuffer,'(A,I4,A,I4,A)') ' TO TILE=', tt,
159 & ' (proc = ',tProc,')'
160 CALL PRINT_MESSAGE(messageBuffer,
161 I standardMessageUnit,SQUEEZE_RIGHT,
162 I myThid)
163 WRITE(messageBuffer,'(A,I10)') ' TAG=', theTag
164 CALL PRINT_MESSAGE(messageBuffer,
165 I standardMessageUnit,SQUEEZE_RIGHT,
166 I myThid)
167 WRITE(messageBuffer,'(A,I4)') ' NEL=', iBufr
168 CALL PRINT_MESSAGE(messageBuffer,
169 I standardMessageUnit,SQUEEZE_RIGHT,
170 I myThid)
171 #endif /* W2_E2_DEBUG_ON */
172 CALL MPI_Isend( e2Bufr1_RX, iBufr, theType,
173 I tProc, theTag, MPI_COMM_MODEL,
174 O theHandle, mpiRc )
175 C Store MPI_Wait token in messageHandle.
176 e2_msgHandle(1) = theHandle
177 #endif
178 ELSE
179 STOP 'EXCH2_SEND_RX1:: commSetting VALUE IS INVALID'
180 ENDIF
181
182 RETURN
183 END

  ViewVC Help
Powered by ViewVC 1.1.22