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

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

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


Revision 1.1 - (hide annotations) (download)
Fri Jul 27 22:15:23 2007 UTC (16 years, 10 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59g, checkpoint59f, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint61a
Preparing exch2 adjoint, based on hand-written exch2 templates.

1 heimbach 1.1 C $Header:$
2     C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5    
6     #undef Dbg
7    
8     CBOP
9     C !ROUTINE: EXCH_RX_CUBE_AD
10    
11     C !INTERFACE:
12     SUBROUTINE EXCH2_RX1_CUBE_AD(
13     U array, fieldCode,
14     I myOLw, myOLe, myOLn, myOLs, myNz,
15     I exchWidthX, exchWidthY,
16     I simulationMode, cornerMode, myThid )
17     IMPLICIT NONE
18    
19     C !DESCRIPTION:
20    
21     C !USES:
22     C == Global data ==
23     #include "SIZE.h"
24     #include "EEPARAMS.h"
25     #include "EESUPPORT.h"
26     #include "EXCH.h"
27     #include "W2_EXCH2_TOPOLOGY.h"
28     #include "W2_EXCH2_PARAMS.h"
29    
30     C !INPUT/OUTPUT PARAMETERS:
31     C array :: Array with edges to exchange.
32     C myOLw :: West, East, North and South overlap region sizes.
33     C myOLe
34     C myOLn
35     C myOLs
36     C exchWidthX :: Width of data regi exchanged in X.
37     C exchWidthY :: Width of data region exchanged in Y.
38     C myThid :: Thread number of this instance of S/R EXCH...
39     CHARACTER*2 fieldCode
40     INTEGER myOLw
41     INTEGER myOLe
42     INTEGER myOLs
43     INTEGER myOLn
44     INTEGER myNz
45     INTEGER exchWidthX
46     INTEGER exchWidthY
47     INTEGER simulationMode
48     INTEGER cornerMode
49     INTEGER myThid
50     _RX array(1-myOLw:sNx+myOLe,
51     & 1-myOLs:sNy+myOLn,
52     & myNZ, nSx, nSy)
53    
54     C !LOCAL VARIABLES:
55     C theSimulationMode :: Holds working copy of simulation mode
56     C theCornerMode :: Holds working copy of corner mode
57     C I,J,K,bl,bt,bn,bs :: Loop and index counters
58     C be,bw
59     INTEGER theSimulationMode
60     INTEGER theCornerMode
61     c INTEGER I,J,K
62     c INTEGER bl,bt,bn,bs,be,bw
63     INTEGER I
64     C Variables for working through W2 topology
65     INTEGER e2_msgHandles(2,MAX_NEIGHBOURS, nSx)
66     INTEGER thisTile, farTile, N, nN, oN
67     INTEGER tIlo, tIhi, tJlo, tJhi, tKlo, tKhi
68     INTEGER tIStride, tJStride, tKStride
69     INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
70     INTEGER bi1Lo, bi1Hi, bj1Lo, bj1Hi
71     C == Statement function ==
72     C tilemod - Permutes indices to return neighboring tile index on
73     C six face cube.
74     c INTEGER tilemod
75    
76     C MPI stuff (should be in a routine call)
77     #ifdef ALLOW_USE_MPI
78     INTEGER mpiStatus(MPI_STATUS_SIZE)
79     INTEGER mpiRc
80     INTEGER wHandle
81     #endif
82     CEOP
83    
84     theSimulationMode = simulationMode
85     theCornerMode = cornerMode
86    
87     C For now tile<->tile exchanges are sequentialised through
88     C thread 1. This is a temporary feature for preliminary testing until
89     C general tile decomposistion is in place (CNH April 11, 2001)
90     CALL BAR2( myThid )
91    
92     C Receive messages or extract buffer copies
93     DO I=myBxLo(myThid), myBxHi(myThid)
94     thisTile=W2_myTileList(I)
95     nN=exch2_nNeighbours(thisTile)
96     DO N=1,nN
97     farTile=exch2_neighbourId(N,thisTile)
98     oN=exch2_opposingSend_Record(N,thisTile)
99     tIlo =exch2_itlo_c(oN,farTile)
100     tIhi =exch2_ithi_c(oN,farTile)
101     tJlo =exch2_jtlo_c(oN,farTile)
102     tJhi =exch2_jthi_c(oN,farTile)
103     CALL EXCH2_GET_RECV_BOUNDS(
104     I fieldCode, exchWidthX,
105     O tiStride, tjStride,
106     U tIlo, tiHi, tjLo, tjHi )
107     tKLo=1
108     tKHi=myNz
109     tKStride=1
110     i1Lo = 1-myOLw
111     i1Hi = sNx+myOLe
112     j1Lo = 1-myOLs
113     j1Hi = sNy+myOLs
114     k1Lo = 1
115     k1Hi = myNz
116     bi1Lo = I
117     bi1Hi = I
118     bj1Lo = 1
119     bj1Hi = 1
120    
121     C Receive from neighbour N to fill my points
122     C (tIlo:tIhi:tiStride,tJlo:tJhi,tJStride,tKlo:tKhi,tKStride)
123     C in "array".
124     C Note: when transferring data within a process:
125     C o e2Bufr entry to read is entry associated with opposing send record
126     C o e2_msgHandle entry to read is entry associated with opposing send
127     C record.
128     CALL EXCH2_RECV_RX1_AD(
129     I tIlo, tIhi, tiStride,
130     I tJlo, tJhi, tjStride,
131     I tKlo, tKhi, tkStride,
132     I thisTile, I, N,
133     I e2Bufr1_RX, e2BufrRecSize,
134     I MAX_NEIGHBOURS, nSx,
135     I array(1-myOLw,1-myOLs,1,I,1),
136     I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
137     U e2_msgHandles(1,N,I),
138     I W2_myTileList,
139     I W2_myCommFlag(N,I),
140     I myThid )
141     ENDDO
142     ENDDO
143    
144     C without MPI: wait until all threads finish filling buffer
145     CALL BAR2( myThid )
146    
147     C Post sends as messages or buffer copies
148     DO I=myBxLo(myThid), myBxHi(myThid)
149     thisTile=W2_myTileList(I)
150     nN=exch2_nNeighbours(thisTile)
151     DO N=1,nN
152     farTile=exch2_neighbourId(N,thisTile)
153     tIlo =exch2_itlo_c(N,thisTile)
154     tIhi =exch2_ithi_c(N,thisTile)
155     tJlo =exch2_jtlo_c(N,thisTile)
156     tJhi =exch2_jthi_c(N,thisTile)
157     CALL EXCH2_GET_SEND_BOUNDS(
158     I fieldCode, exchWidthX,
159     O tiStride, tjStride,
160     U tIlo, tiHi, tjLo, tjHi )
161     tKLo=1
162     tKHi=myNz
163     tKStride=1
164     i1Lo = 1-myOLw
165     i1Hi = sNx+myOLe
166     j1Lo = 1-myOLs
167     j1Hi = sNy+myOLs
168     k1Lo = 1
169     k1Hi = myNz
170     bi1Lo = I
171     bi1Hi = I
172     bj1Lo = 1
173     bj1Hi = 1
174     C Send to neighbour N to fill neighbor points
175     C (tIlo:tIhi:tiStride,tJlo:tJhi,tJStride,tKlo:tKhi,tKStride)
176     C in its copy of "array".
177     CALL EXCH2_SEND_RX1_AD(
178     I tIlo, tIhi, tiStride,
179     I tJlo, tJhi, tjStride,
180     I tKlo, tKhi, tkStride,
181     I thisTile, N,
182     I e2Bufr1_RX(1,N,I,1), e2BufrRecSize,
183     I array(1-myOLw,1-myOLs,1,I,1),
184     I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
185     O e2_msgHandles(1,N,I),
186     I W2_myCommFlag(N,I),
187     I myThid )
188     ENDDO
189     ENDDO
190    
191     C Clear message handles/locks
192     DO I=1,nSx
193     thisTile=W2_myTileList(I)
194     nN=exch2_nNeighbours(thisTile)
195     DO N=1,nN
196     C Note: In a between process tile-tile data transport using
197     C MPI the sender needs to clear an Isend wait handle here.
198     C In a within process tile-tile data transport using true
199     C shared address space/or direct transfer through commonly
200     C addressable memory blocks the receiver needs to assert
201     C that is has consumed the buffer the sender filled here.
202     farTile=exch2_neighbourId(N,thisTile)
203     IF ( W2_myCommFlag(N,I) .EQ. 'M' ) THEN
204     #ifdef ALLOW_USE_MPI
205     wHandle = e2_msgHandles(1,N,I)
206     CALL MPI_Wait( wHandle, mpiStatus, mpiRc )
207     #endif
208     ELSEIF ( W2_myCommFlag(N,I) .EQ. 'P' ) THEN
209     ELSE
210     ENDIF
211     ENDDO
212     ENDDO
213    
214     CALL BAR2(myThid)
215    
216     RETURN
217     END
218    
219     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
220    
221     CEH3 ;;; Local Variables: ***
222     CEH3 ;;; mode:fortran ***
223     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22