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

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

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


Revision 1.2 - (hide annotations) (download)
Mon Jan 19 18:59:19 2004 UTC (20 years, 5 months ago) by afe
Branch: MAIN
CVS Tags: checkpoint52l_pre, hrcube4, checkpoint52j_post, checkpoint52l_post, checkpoint52k_post, hrcube5, checkpoint52i_post, checkpoint52j_pre, checkpoint52i_pre, checkpoint52h_pre, hrcube_2, hrcube_3
Changes since 1.1: +10 -5 lines
shortened offending lines in exch2_send_rx?.template

1 afe 1.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 afe 1.2 WRITE(messageBuffer,'(A,I4,A,I4)') 'EXCH2_SEND_RX1 sourceTile= ',
80     & thisTile,
81 afe 1.1 & 'targetTile= ',tt
82     CALL PRINT_MESSAGE(messageBuffer,
83     I standardMessageUnit,SQUEEZE_BOTH,
84     I myThid)
85     #endif /* W2_E2_DEBUG_ON */
86     DO ktl=tKlo,tKhi,tKStride
87     DO jtl=tJLo, tJHi, tjStride
88     DO itl=tILo, tIHi, tiStride
89     iBufr=iBufr+1
90     itc=itl+itb
91     jtc=jtl+jtb
92     isc=pi(1)*itc+pi(2)*jtc+oi
93     jsc=pj(1)*itc+pj(2)*jtc+oj
94     isl=isc-isb
95     jsl=jsc-jsb
96     e2Bufr1_RX(iBufr)=array(isl,jsl,ktl)
97     #ifdef W2_E2_DEBUG_ON
98 afe 1.2 WRITE(messageBuffer,'(A,2I4)')
99     & 'EXCH2_SEND_RX1 target t(itl,jtl) = ', itl, jtl
100 afe 1.1 CALL PRINT_MESSAGE(messageBuffer,
101     I standardMessageUnit,SQUEEZE_RIGHT,
102     I myThid)
103 afe 1.2 WRITE(messageBuffer,'(A,2I4)')
104     & ' source (isl,jsl) = ', isl, jsl
105 afe 1.1 CALL PRINT_MESSAGE(messageBuffer,
106     I standardMessageUnit,SQUEEZE_RIGHT,
107     I myThid)
108     IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
109 afe 1.2 WRITE(messageBuffer,'(A,2I4)')
110     & ' *** isl is out of bounds'
111 afe 1.1 CALL PRINT_MESSAGE(messageBuffer,
112     I standardMessageUnit,SQUEEZE_RIGHT,
113     I myThid)
114     ENDIF
115     IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
116 afe 1.2 WRITE(messageBuffer,'(A,2I4)')
117     & ' *** jsl is out of bounds'
118 afe 1.1 CALL PRINT_MESSAGE(messageBuffer,
119     I standardMessageUnit,SQUEEZE_RIGHT,
120     I myThid)
121     ENDIF
122     #endif /* W2_E2_DEBUG_ON */
123     #ifdef W2_USE_E2_SAFEMODE
124     IF ( iBufr .GT. e2BufrRecSize ) THEN
125     C Ran off end of buffer. This should not happen
126     STOP 'EXCH2_SEND_RX1:: E2BUFR LIMIT EXCEEDED'
127     ENDIF
128     IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
129     C Forward mode send getting from points outside of the
130     C tiles exclusive domain bounds in X. This should not happen
131     STOP 'EXCH2_SEND_RX1:: ISL OUTSIDE TILE EXCLUSIVE DOMAIN'
132     ENDIF
133     IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
134     C Forward mode send getting from points outside of the
135     C tiles exclusive domain bounds in Y. This should not happen
136     STOP 'EXCH2_SEND_RX1:: JSL OUTSIDE TILE EXCLUSIVE DOMAIN'
137     ENDIF
138     #endif /* W2_USE_E2_SAFEMODE */
139     ENDDO
140     ENDDO
141     ENDDO
142    
143     C Do data transport depending on communication mechanism between source and target tile
144     IF ( commSetting .EQ. 'P' ) THEN
145     C Need to set data ready assertion (increment buffer synchronisation token)
146     C for multithreaded mode, for now do nothing i.e. assume only one thread per process.
147     ELSEIF ( commSetting .EQ. 'M' ) THEN
148     #ifdef ALLOW_USE_MPI
149     C Setup MPI stuff here
150     theTag = (thisTile-1)*MAX_NEIGHBOURS + nN
151     & + 10000*(
152     & (tt-1)*MAX_NEIGHBOURS + nN
153     & )
154     tProc = exch2_tProc(tt)-1
155     sProc = exch2_tProc(thisTile)-1
156     theType = MPI_REAL8
157     #ifdef W2_E2_DEBUG_ON
158     WRITE(messageBuffer,'(A,I4,A,I4,A)') ' SEND FROM TILE=', thisTile,
159     & ' (proc = ',sProc,')'
160     CALL PRINT_MESSAGE(messageBuffer,
161     I standardMessageUnit,SQUEEZE_RIGHT,
162     I myThid)
163     WRITE(messageBuffer,'(A,I4,A,I4,A)') ' TO TILE=', tt,
164     & ' (proc = ',tProc,')'
165     CALL PRINT_MESSAGE(messageBuffer,
166     I standardMessageUnit,SQUEEZE_RIGHT,
167     I myThid)
168     WRITE(messageBuffer,'(A,I10)') ' TAG=', theTag
169     CALL PRINT_MESSAGE(messageBuffer,
170     I standardMessageUnit,SQUEEZE_RIGHT,
171     I myThid)
172     WRITE(messageBuffer,'(A,I4)') ' NEL=', iBufr
173     CALL PRINT_MESSAGE(messageBuffer,
174     I standardMessageUnit,SQUEEZE_RIGHT,
175     I myThid)
176     #endif /* W2_E2_DEBUG_ON */
177     CALL MPI_Isend( e2Bufr1_RX, iBufr, theType,
178     I tProc, theTag, MPI_COMM_MODEL,
179     O theHandle, mpiRc )
180     C Store MPI_Wait token in messageHandle.
181     e2_msgHandle(1) = theHandle
182     #endif
183     ELSE
184     STOP 'EXCH2_SEND_RX1:: commSetting VALUE IS INVALID'
185     ENDIF
186    
187     RETURN
188     END

  ViewVC Help
Powered by ViewVC 1.1.22