/[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.4 - (show annotations) (download)
Fri Jul 22 18:21:55 2005 UTC (18 years, 11 months ago) by jmc
Branch: MAIN
Changes since 1.3: +10 -5 lines
comment out unused variable declaration (get less warnings for unused var)

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

  ViewVC Help
Powered by ViewVC 1.1.22