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

Contents of /MITgcm/pkg/exch2/exch2_ad_get_rx2.template

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


Revision 1.3 - (show annotations) (download)
Fri Apr 23 20:21:06 2010 UTC (14 years 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.2: +7 -7 lines
fix propagating typo (& others) in variable description

1 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_ad_get_rx2.template,v 1.2 2009/06/28 01:00:23 jmc Exp $
2 C $Name: $
3
4 #include "CPP_EEOPTIONS.h"
5 #include "W2_OPTIONS.h"
6
7 CBOP 0
8 C !ROUTINE: EXCH2_AD_GET_RX2
9
10 C !INTERFACE:
11 SUBROUTINE EXCH2_AD_GET_RX2 (
12 I tIlo1, tIhi1, tIlo2, tIhi2, tiStride,
13 I tJlo1, tJhi1, tJlo2, tJhi2, tjStride,
14 I tKlo, tKhi, tkStride,
15 I thisTile, nN, bi, bj,
16 I e2BufrRecSize, sizeNb, sizeBi, sizeBj,
17 O iBufr1, iBufr2,
18 O e2Bufr1_RX, e2Bufr2_RX,
19 U array1,
20 U array2,
21 I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
22 I i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,
23 U e2_msgHandles,
24 I commSetting, myThid )
25
26 C !DESCRIPTION:
27 C---------------
28 C AD: IMPORTANT: All comments (except AD:) are taken from the Forward S/R
29 C AD: and need to be interpreted in the reverse sense: put <-> get,
30 C AD: send <-> recv, source <-> target ...
31 C---------------
32 C Two components vector field Exchange:
33 C Get from buffer exchanged data to fill in this tile-egde overlap region.
34
35 C !USES:
36 IMPLICIT NONE
37
38 #include "SIZE.h"
39 #include "EEPARAMS.h"
40 #include "W2_EXCH2_SIZE.h"
41 #include "W2_EXCH2_TOPOLOGY.h"
42
43 C !INPUT/OUTPUT PARAMETERS:
44 C === Routine arguments ===
45 C tIlo1, tIhi1 :: index range in I that will be filled in target "array1"
46 C tIlo2, tIhi2 :: index range in I that will be filled in target "array2"
47 C tIstride :: index step in I that will be filled in target arrays
48 C tJlo1, tJhi1 :: index range in J that will be filled in target "array1"
49 C tJlo2, tJhi2 :: index range in J that will be filled in target "array2"
50 C tJstride :: index step in J that will be filled in target arrays
51 C tKlo, tKhi :: index range in K that will be filled in target arrays
52 C tKstride :: index step in K that will be filled in target arrays
53 C oIs1, oJs1 :: I,J index offset in target "array1" to source connection
54 C oIs2, oJs2 :: I,J index offset in target "array2" to source connection
55 C thisTile :: receiving tile Id. number
56 C nN :: Neighbour entry that we are processing
57 C bi,bj :: Indices of the receiving tile within this process
58 C :: (used to select buffer slots that are allowed).
59 C e2BufrRecSize :: Number of elements in each entry of e2Bufr[1,2]_RX
60 C sizeNb :: Second dimension of e2Bufr1_RX & e2Bufr2_RX
61 C sizeBi :: Third dimension of e2Bufr1_RX & e2Bufr2_RX
62 C sizeBj :: Fourth dimension of e2Bufr1_RX & e2Bufr2_RX
63 C iBufr1 :: number of buffer-1 elements to transfer
64 C iBufr2 :: number of buffer-2 elements to transfer
65 C e2Bufr1_RX :: Data transport buffer array. This array is used in one of
66 C e2Bufr2_RX :: two ways. For PUT communication the entry in the buffer
67 C :: associated with the source for this receive (determined
68 C :: from the opposing_send index) is read.
69 C :: For MSG communication the entry in the buffer associated
70 C :: with this neighbor of this tile is used as a receive
71 C :: location for loading a linear stream of bytes.
72 C array1 :: 1rst Component target array that this receive writes to.
73 C array2 :: 2nd Component target array that this receive writes to.
74 C i1Lo, i1Hi :: I coordinate bounds of target array1
75 C j1Lo, j1Hi :: J coordinate bounds of target array1
76 C k1Lo, k1Hi :: K coordinate bounds of target array1
77 C i2Lo, i2Hi :: I coordinate bounds of target array2
78 C j2Lo, j2Hi :: J coordinate bounds of target array2
79 C k2Lo, k2Hi :: K coordinate bounds of target array2
80 C e2_msgHandles :: Synchronization and coordination data structure used to
81 C :: coordinate access to e2Bufr1_RX or to regulate message
82 C :: buffering. In PUT communication sender will increment
83 C :: handle entry once data is ready in buffer. Receiver will
84 C :: decrement handle once data is consumed from buffer.
85 C :: For MPI MSG communication MPI_Wait uses handle to check
86 C :: Isend has cleared. This is done in routine after receives.
87 C commSetting :: Mode of communication used to exchange with this neighbor
88 C withSigns :: Flag controlling whether vector field is signed.
89 C myThid :: my Thread Id. number
90
91 INTEGER tIlo1, tIhi1, tIlo2, tIhi2, tiStride
92 INTEGER tJlo1, tJhi1, tJlo2, tJhi2, tjStride
93 INTEGER tKlo, tKhi, tkStride
94 INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
95 INTEGER i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi
96 INTEGER thisTile, nN, bi, bj
97 INTEGER e2BufrRecSize, sizeNb, sizeBi, sizeBj
98 INTEGER iBufr1, iBufr2
99 _RX e2Bufr1_RX( e2BufrRecSize, sizeNb, sizeBi, sizeBj, 2 )
100 _RX e2Bufr2_RX( e2BufrRecSize, sizeNb, sizeBi, sizeBj, 2 )
101 _RX array1(i1Lo:i1Hi,j1Lo:j1Hi,k1Lo:k1Hi)
102 _RX array2(i2Lo:i2Hi,j2Lo:j2Hi,k2Lo:k2Hi)
103 INTEGER e2_msgHandles( 2, sizeNb, sizeBi, sizeBj )
104 CHARACTER commSetting
105 INTEGER myThid
106 CEOP
107
108 C !LOCAL VARIABLES:
109 C == Local variables ==
110 C itl,jtl,ktl :: Loop counters (this tile)
111 C soT :: Source tile Id number
112 C oNb :: Opposing send record number
113 C sNb :: buffer(source) Neighbour index to get data from
114 C sBi :: buffer(source) local(to this Proc) Tile index to get data from
115 C sBj :: buffer(source) local(to this Proc) Tile index to get data from
116 C sLv :: buffer(source) level index to get data from
117 C i,j :: Loop counters
118
119 INTEGER itl, jtl, ktl
120 INTEGER soT
121 INTEGER oNb
122 INTEGER sNb, sBi, sBj, sLv
123 INTEGER i,j
124 c CHARACTER*(MAX_LEN_MBUF) msgBuf
125
126 soT = exch2_neighbourId( nN, thisTile )
127 oNb = exch2_opposingSend(nN, thisTile )
128
129 C Handle receive end data transport according to communication mechanism between
130 C source and target tile
131 IF ( commSetting .EQ. 'P' ) THEN
132 C AD: Need to check that buffer synchronisation token is decremented
133 C AD: before filling buffer.
134
135 C find the tile indices (local to this Proc) corresponding to
136 C this source tile Id "soT"
137 sLv = 1
138 sNb = oNb
139 DO j=1,sizeBj
140 DO i=1,sizeBi
141 IF ( W2_myTileList(i,j).EQ.soT ) THEN
142 sBi = i
143 sBj = j
144 ENDIF
145 ENDDO
146 ENDDO
147 #ifdef ALLOW_USE_MPI
148 ELSEIF ( commSetting .EQ. 'M' ) THEN
149 sLv = 2
150 sBi = bi
151 sBj = bj
152 sNb = nN
153 #endif /* ALLOW_USE_MPI */
154 ELSE
155 STOP 'EXCH2_AD_GET_RX2:: commSetting VALUE IS INVALID'
156 ENDIF
157
158 iBufr1=0
159 DO ktl=tKlo,tKhi,tkStride
160 DO jtl=tJLo1, tJHi1, tjStride
161 DO itl=tILo1, tIHi1, tiStride
162 C Read from e2Bufr1_RX(iBufr,sNb,sBi,sBj,sLv)
163 iBufr1 = iBufr1+1
164 e2Bufr1_RX(iBufr1,sNb,sBi,sBj,sLv) = array1(itl,jtl,ktl)
165 array1(itl,jtl,ktl) = 0.
166 ENDDO
167 ENDDO
168 ENDDO
169
170 iBufr2=0
171 DO ktl=tKlo,tKhi,tkStride
172 DO jtl=tJLo2, tJHi2, tjStride
173 DO itl=tILo2, tIHi2, tiStride
174 C Read from e2Bufr2_RX(iBufr,sNb,sBi,sBj,sLv)
175 iBufr2 = iBufr2+1
176 e2Bufr2_RX(iBufr2,sNb,sBi,sBj,sLv) = array2(itl,jtl,ktl)
177 array2(itl,jtl,ktl) = 0.
178 ENDDO
179 ENDDO
180 ENDDO
181
182 RETURN
183 END
184
185 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
186
187 CEH3 ;;; Local Variables: ***
188 CEH3 ;;; mode:fortran ***
189 CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22