/[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.3 - (hide annotations) (download)
Mon Apr 5 15:27:06 2004 UTC (20 years, 2 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint52n_post, checkpoint53d_post, checkpoint54a_pre, checkpoint55c_post, checkpoint54e_post, checkpoint54a_post, checkpoint53c_post, checkpoint57k_post, checkpoint55d_pre, checkpoint57d_post, checkpoint57g_post, checkpoint57b_post, checkpoint57c_pre, checkpoint55j_post, checkpoint56b_post, checkpoint57i_post, checkpoint57e_post, checkpoint55h_post, checkpoint53b_post, checkpoint57g_pre, checkpoint54b_post, checkpoint53b_pre, checkpoint55b_post, checkpoint54d_post, checkpoint56c_post, checkpoint52m_post, checkpoint55, checkpoint53a_post, checkpoint57f_pre, checkpoint57a_post, checkpoint54, checkpoint54f_post, checkpoint55g_post, checkpoint55f_post, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, checkpoint53, eckpoint57e_pre, checkpoint57h_done, checkpoint53g_post, checkpoint57f_post, checkpoint57c_post, checkpoint55e_post, checkpoint53f_post, checkpoint55a_post, checkpoint53d_pre, checkpoint54c_post, checkpoint57j_post, checkpoint57h_pre, checkpoint57l_post, checkpoint57h_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.2: +9 -0 lines
 o fix "make clean"
 o add CVS Header: and Name:

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

  ViewVC Help
Powered by ViewVC 1.1.22