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

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

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


Revision 1.2 - (hide annotations) (download)
Fri Apr 23 20:21:07 2010 UTC (14 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62g, checkpoint62f, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.1: +5 -5 lines
fix propagating typo (& others) in variable description

1 jmc 1.2 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_ad_put_rx1.template,v 1.1 2009/05/30 21:18:59 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5     #include "W2_OPTIONS.h"
6    
7     CBOP 0
8     C !ROUTINE: EXCH2_AD_PUT_RX1
9    
10     C !INTERFACE:
11     SUBROUTINE EXCH2_AD_PUT_RX1 (
12     I tIlo, tIhi, tiStride,
13     I tJlo, tJhi, tjStride,
14     I tKlo, tKhi, tkStride,
15     I thisTile, nN,
16     I e2BufrRecSize,
17     I e2Bufr1_RX,
18     U array,
19     I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
20     O e2_msgHandle,
21     I commSetting, myThid )
22    
23     C !DESCRIPTION:
24     C---------------
25 jmc 1.2 C AD: IMPORTANT: all comments (except AD:) are taken from the Forward S/R
26 jmc 1.1 C AD: and need to be interpreted in the reverse sense: put <-> get,
27     C AD: send <-> recv, source <-> target ...
28     C---------------
29     C Scalar field (1 component) Exchange:
30     C Put into buffer exchanged data from this source tile.
31 jmc 1.2 C Those data are intended to fill-in the
32 jmc 1.1 C target-neighbour-edge overlap region.
33    
34     C !USES:
35     IMPLICIT NONE
36    
37     #include "SIZE.h"
38     #include "EEPARAMS.h"
39     #include "W2_EXCH2_SIZE.h"
40     #include "W2_EXCH2_TOPOLOGY.h"
41    
42    
43     C !INPUT/OUTPUT PARAMETERS:
44     C === Routine arguments ===
45     C tIlo, tIhi :: index range in I that will be filled in target "array"
46     C tIstride :: index step in I that will be filled in target "array"
47     C tJlo, tJhi :: index range in J that will be filled in target "array"
48     C tJstride :: index step in J that will be filled in target "array"
49     C tKlo, tKhi :: index range in K that will be filled in target "array"
50     C tKstride :: index step in K that will be filled in target "array"
51     C thisTile :: sending tile Id. number
52     C nN :: Neighbour entry that we are processing
53     C e2BufrRecSize :: Number of elements in each entry of e2Bufr1_RX
54     C e2Bufr1_RX :: Data transport buffer array. This array is used in one of
55     C :: two ways. For PUT communication the entry in the buffer
56     C :: associated with the source for this receive (determined
57     C :: from the opposing_send index) is read.
58     C :: For MSG communication the entry in the buffer associated
59     C :: with this neighbor of this tile is used as a receive
60     C :: location for loading a linear stream of bytes.
61     C array :: Source array where the data come from
62     C i1Lo, i1Hi :: I coordinate bounds of target array
63     C j1Lo, j1Hi :: J coordinate bounds of target array
64     C k1Lo, k1Hi :: K coordinate bounds of target array
65     C e2_msgHandles :: Synchronization and coordination data structure used to
66     C :: coordinate access to e2Bufr1_RX or to regulate message
67     C :: buffering. In PUT communication sender will increment
68     C :: handle entry once data is ready in buffer. Receiver will
69     C :: decrement handle once data is consumed from buffer.
70 jmc 1.2 C :: For MPI MSG communication MPI_Wait uses handle to check
71 jmc 1.1 C :: Isend has cleared. This is done in routine after receives.
72     C commSetting :: Mode of communication used to exchange with this neighbor
73     C myThid :: my Thread Id. number
74    
75     INTEGER tILo, tIHi, tiStride
76     INTEGER tJLo, tJHi, tjStride
77     INTEGER tKLo, tKHi, tkStride
78     INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
79     INTEGER thisTile, nN
80     INTEGER e2BufrRecSize
81     _RX e2Bufr1_RX( e2BufrRecSize )
82     _RX array(i1Lo:i1Hi,j1Lo:j1Hi,k1Lo:k1Hi)
83     INTEGER e2_msgHandle(1)
84     CHARACTER commSetting
85     INTEGER myThid
86     CEOP
87    
88     C !LOCAL VARIABLES:
89     C == Local variables ==
90     C itl,jtl,ktl :: Loop counters
91     C :: itl etc... target local
92     C :: itc etc... target canonical
93     C :: isl etc... source local
94     C :: isc etc... source canonical
95     C tgT :: Target tile Id. number
96     C itb, jtb :: Target local to canonical offsets
97 jmc 1.2 C iBufr :: number of buffer elements to transfer
98 jmc 1.1 INTEGER itl, jtl, ktl
99     INTEGER itc, jtc
100     INTEGER isc, jsc
101     INTEGER isl, jsl
102     INTEGER tgT
103     INTEGER itb, jtb
104     INTEGER isb, jsb
105     INTEGER pi(2), pj(2), oi, oj
106     INTEGER iBufr
107    
108     #ifdef W2_E2_DEBUG_ON
109     CHARACTER*(MAX_LEN_MBUF) msgBuf
110     #endif
111    
112     c IF ( commSetting .EQ. 'P' ) THEN
113     C AD: 1 Need to check and spin on data ready assertion for multithreaded mode,
114     C AD: for now, ensure global sync using barrier.
115     C AD: 2 get directly data from 1rst level buffer (sLv=1);
116     c ENDIF
117    
118     tgT = exch2_neighbourId(nN, thisTile )
119     itb = exch2_tBasex(tgT)
120     jtb = exch2_tBasey(tgT)
121     isb = exch2_tBasex(thisTile)
122     jsb = exch2_tBasey(thisTile)
123     pi(1)=exch2_pij(1,nN,thisTile)
124     pi(2)=exch2_pij(2,nN,thisTile)
125     pj(1)=exch2_pij(3,nN,thisTile)
126     pj(2)=exch2_pij(4,nN,thisTile)
127     oi = exch2_oi(nN,thisTile)
128     oj = exch2_oj(nN,thisTile)
129     #ifdef W2_E2_DEBUG_ON
130     WRITE(msgBuf,'(A,I5,A,I5)')
131     & 'EXCH2_AD_PUT_RX1 sourceTile=', thisTile, 'targetTile=', tgT
132     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
133     I SQUEEZE_BOTH, myThid )
134     #endif /* W2_E2_DEBUG_ON */
135     iBufr=0
136     DO ktl=tKlo,tKhi,tKStride
137     DO jtl=tJLo, tJHi, tjStride
138     DO itl=tILo, tIHi, tiStride
139     iBufr=iBufr+1
140     itc = itl+itb
141     jtc = jtl+jtb
142     isc = pi(1)*itc+pi(2)*jtc+oi
143     jsc = pj(1)*itc+pj(2)*jtc+oj
144     isl = isc-isb
145     jsl = jsc-jsb
146     #ifdef W2_E2_DEBUG_ON
147     WRITE(msgBuf,'(A,2I5)')
148     & 'EXCH2_AD_PUT_RX1 target t(itl,jtl) =', itl, jtl
149     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
150     I SQUEEZE_RIGHT, myThid )
151     WRITE(msgBuf,'(A,2I5)')
152     & ' source (isl,jsl) =', isl, jsl
153     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
154     I SQUEEZE_RIGHT, myThid )
155     IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
156     WRITE(msgBuf,'(A,2I5)')
157     & ' *** isl is out of bounds'
158     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
159     I SQUEEZE_RIGHT, myThid )
160     ENDIF
161     IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
162     WRITE(msgBuf,'(A,2I5)')
163     & ' *** jsl is out of bounds'
164     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
165     I SQUEEZE_RIGHT, myThid )
166     ENDIF
167     #endif /* W2_E2_DEBUG_ON */
168     #ifdef W2_USE_E2_SAFEMODE
169     IF ( iBufr .GT. e2BufrRecSize ) THEN
170     C Ran off end of buffer. This should not happen
171     STOP 'EXCH2_AD_PUT_RX1:: E2BUFR LIMIT EXCEEDED'
172     ENDIF
173     IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN
174     C Forward mode send getting from points outside of the
175     C tiles exclusive domain bounds in X. This should not happen
176     STOP 'EXCH2_AD_PUT_RX1:: ISL OUTSIDE TILE EXCLUSIVE DOMAIN'
177     ENDIF
178     IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN
179     C Forward mode send getting from points outside of the
180     C tiles exclusive domain bounds in Y. This should not happen
181     STOP 'EXCH2_AD_PUT_RX1:: JSL OUTSIDE TILE EXCLUSIVE DOMAIN'
182     ENDIF
183     #endif /* W2_USE_E2_SAFEMODE */
184     array(isl,jsl,ktl) = array(isl,jsl,ktl) + e2Bufr1_RX(iBufr)
185     e2Bufr1_RX(iBufr) = 0. _d 0
186     ENDDO
187     ENDDO
188     ENDDO
189    
190     RETURN
191     END
192    
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