/[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.6 - (show annotations) (download)
Fri Jul 27 22:15:24 2007 UTC (16 years, 10 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59g, checkpoint59f, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint61a
Changes since 1.5: +3 -3 lines
Preparing exch2 adjoint, based on hand-written exch2 templates.

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