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

  ViewVC Help
Powered by ViewVC 1.1.22