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

Contents of /MITgcm/pkg/exch2/exch2_ad_get_rx1.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: +6 -6 lines
fix propagating typo (& others) in variable description

1 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_ad_get_rx1.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_RX1
9
10 C !INTERFACE:
11 SUBROUTINE EXCH2_AD_GET_RX1(
12 I tIlo, tIhi, tiStride,
13 I tJlo, tJhi, tjStride,
14 I tKlo, tKhi, tkStride,
15 I thisTile, nN, bi, bj,
16 I e2BufrRecSize, sizeNb, sizeBi, sizeBj,
17 O iBufr,
18 O e2Bufr1_RX,
19 U array,
20 I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
21 U e2_msgHandles,
22 I commSetting, myThid )
23
24 C !DESCRIPTION:
25 C---------------
26 C AD: IMPORTANT: All comments (except AD:) are taken from the Forward S/R
27 C AD: and need to be interpreted in the reverse sense: put <-> get,
28 C AD: send <-> recv, source <-> target ...
29 C---------------
30 C Scalar field (1 component) Exchange:
31 C Get from buffer exchanged data to fill in this tile-egde overlap region.
32
33 C !USES:
34 IMPLICIT NONE
35
36 #include "SIZE.h"
37 #include "EEPARAMS.h"
38 #include "W2_EXCH2_SIZE.h"
39 #include "W2_EXCH2_TOPOLOGY.h"
40
41 C !INPUT/OUTPUT PARAMETERS:
42 C === Routine arguments ===
43 C tIlo,tIhi :: index range in I that will be filled in target "array"
44 C tIstride :: index step in I that will be filled in target "array"
45 C tJlo,tJhi :: index range in J that will be filled in target "array"
46 C tJstride :: index step in J that will be filled in target "array"
47 C tKlo,tKhi :: index range in K that will be filled in target "array"
48 C tKstride :: index step in K that will be filled in target "array"
49 C thisTile :: receiving tile Id. number
50 C nN :: Neighbour entry that we are processing
51 C bi,bj :: Indices of the receiving tile within this process
52 C :: (used to select buffer slots that are allowed).
53 C e2BufrRecSize :: Number of elements in each entry of e2Bufr1_RX
54 C sizeNb :: Second dimension of e2Bufr1_RX
55 C sizeBi :: Third dimension of e2Bufr1_RX
56 C sizeBj :: Fourth dimension of e2Bufr1_RX
57 C iBufr :: number of buffer elements to transfer
58 C e2Bufr1_RX :: Data transport buffer array. This array is used in one of
59 C :: two ways. For PUT communication the entry in the buffer
60 C :: associated with the source for this receive (determined
61 C :: from the opposing_send index) is read.
62 C :: For MSG communication the entry in the buffer associated
63 C :: with this neighbor of this tile is used as a receive
64 C :: location for loading a linear stream of bytes.
65 C array :: Target array that this receive writes to.
66 C i1Lo, i1Hi :: I coordinate bounds of target array
67 C j1Lo, j1Hi :: J coordinate bounds of target array
68 C k1Lo, k1Hi :: K coordinate bounds of target array
69 C e2_msgHandles :: Synchronization and coordination data structure used to
70 C :: coordinate access to e2Bufr1_RX or to regulate message
71 C :: buffering. In PUT communication sender will increment
72 C :: handle entry once data is ready in buffer. Receiver will
73 C :: decrement handle once data is consumed from buffer.
74 C :: For MPI MSG communication MPI_Wait uses handle to check
75 C :: Isend has cleared. This is done in routine after receives.
76 C commSetting :: Mode of communication used to exchange with this neighbor
77 C myThid :: my Thread Id. number
78
79 INTEGER tILo, tIHi, tiStride
80 INTEGER tJLo, tJHi, tjStride
81 INTEGER tKLo, tKHi, tkStride
82 INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
83 INTEGER thisTile, nN, bi, bj
84 INTEGER e2BufrRecSize, sizeNb, sizeBi, sizeBj
85 INTEGER iBufr
86 _RX e2Bufr1_RX( e2BufrRecSize, sizeNb, sizeBi, sizeBj, 2 )
87 _RX array(i1Lo:i1Hi,j1Lo:j1Hi,k1Lo:k1Hi)
88 INTEGER e2_msgHandles( 2, sizeNb, sizeBi, sizeBj )
89 CHARACTER commSetting
90 INTEGER myThid
91 CEOP
92
93 C !LOCAL VARIABLES:
94 C == Local variables ==
95 C itl,jtl,ktl :: Loop counters (this tile)
96 C soT :: Source tile Id number
97 C oNb :: Opposing send record number
98 C sNb :: buffer (source) Neighbour index to get data from
99 C sBi :: buffer (source) Tile index (for this Proc) to get data from
100 C sBj :: buffer (source) Tile index (for this Proc) to get data from
101 C sLv :: buffer (source) level index to get data from
102 C i,j :: Loop counters
103 INTEGER itl, jtl, ktl
104 INTEGER soT
105 INTEGER oNb
106 INTEGER sNb, sBi, sBj, sLv
107 INTEGER i,j
108 c CHARACTER*(MAX_LEN_MBUF) msgBuf
109
110 soT = exch2_neighbourId( nN, thisTile )
111 oNb = exch2_opposingSend(nN, thisTile )
112
113 C Handle receive end data transport according to communication mechanism
114 C between source and target tile
115 IF ( commSetting .EQ. 'P' ) THEN
116 C AD: Need to check that buffer synchronisation token is decremented
117 C AD: before filling buffer.
118
119 C find the tile indices (local to this Proc) corresponding to
120 C this source tile Id "soT"
121 sLv = 1
122 sNb = oNb
123 DO j=1,sizeBj
124 DO i=1,sizeBi
125 IF ( W2_myTileList(i,j).EQ.soT ) THEN
126 sBi = i
127 sBj = j
128 ENDIF
129 ENDDO
130 ENDDO
131 #ifdef ALLOW_USE_MPI
132 ELSEIF ( commSetting .EQ. 'M' ) THEN
133 sLv = 2
134 sBi = bi
135 sBj = bj
136 sNb = nN
137 #endif /* ALLOW_USE_MPI */
138 ELSE
139 STOP 'EXCH2_AD_GET_RX1:: commSetting VALUE IS INVALID'
140 ENDIF
141
142 iBufr = 0
143 DO ktl=tKlo,tKhi,tKStride
144 DO jtl=tJLo, tJHi, tjStride
145 DO itl=tILo, tIHi, tiStride
146 C Read from e2Bufr1_RX(iBufr,sNb,sBi,sBj,sLv)
147 iBufr = iBufr+1
148 e2Bufr1_RX(iBufr,sNb,sBi,sBj,sLv) = array(itl,jtl,ktl)
149 array(itl,jtl,ktl) = 0.
150 ENDDO
151 ENDDO
152 ENDDO
153
154 RETURN
155 END
156
157 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
158
159 CEH3 ;;; Local Variables: ***
160 CEH3 ;;; mode:fortran ***
161 CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22