/[MITgcm]/MITgcm/eesupp/src/exch1_bg_rx_cube.template
ViewVC logotype

Annotation of /MITgcm/eesupp/src/exch1_bg_rx_cube.template

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


Revision 1.1 - (hide annotations) (download)
Wed May 19 01:46:11 2010 UTC (14 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint65, checkpoint63, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint62g, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, HEAD
rename all exch_*rx_cube.F to exch1_*rx_cube.F and remove argument "simulationMode"

1 jmc 1.1 C $Header: /u/gcmpack/MITgcm/eesupp/src/exch_bg_rx_cube.template,v 1.3 2010/05/04 00:39:52 jmc Exp $
2     C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5    
6     CBOP
7    
8     C !ROUTINE: EXCH1_BG_RX_CUBE
9    
10     C !INTERFACE:
11     SUBROUTINE EXCH1_BG_RX_CUBE(
12     U uField, vField,
13     I withSigns,
14     I myOLw, myOLe, myOLs, myOLn, myNz,
15     I exchWidthX, exchWidthY,
16     I cornerMode, myThid )
17    
18     C !DESCRIPTION:
19     C *==========================================================*
20     C | SUBROUTINE EXCH1_BG_RX_CUBE
21     C | o Forward-mode edge exchanges for RX vector on CS config:
22     C | Fill overlap region through tile exchanges,
23     C | according to CS topology,
24     C | for a 2-Components B-Grid vector field RX arrays.
25     C *==========================================================*
26     C | Proceeds in 2 steps :
27     C | 1) fill the edges to get valid fields over (1:sNx+1,1:sNy+1)
28     C | 2) fill in overlap region:
29     C | (1-Olx:0 & sNx+2:sNx+Olx) x (1-Oly:0 & sNy+2:sNy+Oly)
30     C | Only works: a) with exactly 6 tiles (1 per face)
31     C | b) no MPI
32     C | c) thread shared arrays (in common block)
33     C *==========================================================*
34    
35     C !USES:
36     IMPLICIT NONE
37    
38     C == Global data ==
39     #include "SIZE.h"
40     #include "EEPARAMS.h"
41    
42     C !INPUT/OUTPUT PARAMETERS:
43     C == Routine arguments ==
44     C uField :: 1rst component array with overlap to exchange.
45     C vField :: 2nd component array with overlap to exchange.
46     C withSigns :: sign of uField,vField depends on orientation.
47     C myOLw,myOLe :: West and East overlap region sizes.
48     C myOLs,myOLn :: South and North overlap region sizes.
49     C exchWidthX :: Width of data region exchanged in X.
50     C exchWidthY :: Width of data region exchanged in Y.
51     C Note --
52     C 1. In theory one could have a send width and
53     C a receive width for each face of each tile. The only
54     C restriction would be that the send width of one
55     C face should equal the receive width of the sent to
56     C tile face. Dont know if this would be useful. I
57     C have left it out for now as it requires additional
58     C bookeeping.
59     C cornerMode :: Flag indicating whether corner updates are needed.
60     C myThid :: my Thread Id number
61    
62     INTEGER myOLw, myOLe, myOLs, myOLn, myNz
63     _RX uField( 1-myOLw:sNx+myOLe, 1-myOLs:sNy+myOLn,
64     & myNz, nSx, nSy )
65     _RX vField( 1-myOLw:sNx+myOLe, 1-myOLs:sNy+myOLn,
66     & myNz, nSx, nSy )
67     LOGICAL withSigns
68     INTEGER exchWidthX
69     INTEGER exchWidthY
70     INTEGER cornerMode
71     INTEGER myThid
72    
73     C !LOCAL VARIABLES:
74     C == Local variables ==
75     C theSimulationMode :: Holds working copy of simulation mode
76     C theCornerMode :: Holds working copy of corner mode
77     C i,j,k,repeat :: Loop counters and index
78     C bt,bn,bs,be,bw
79     c INTEGER theSimulationMode
80     c INTEGER theCornerMode
81     INTEGER i,j,k
82     INTEGER updateEdges, j1, j2, j3
83     INTEGER bt,bn,bs,be,bw
84     CHARACTER*(MAX_LEN_MBUF) msgBuf
85     _RX negOne
86    
87     C == Statement function ==
88     INTEGER tilemod
89     tilemod(i)=1+mod(i-1+6,6)
90     CEOP
91    
92     c theSimulationMode = FORWARD_SIMULATION
93     c theCornerMode = cornerMode
94    
95     c IF ( simulationMode.EQ.REVERSE_SIMULATION ) THEN
96     c WRITE(msgBuf,'(A)')'EXCH1_BG_RX_CUBE: AD mode not implemented'
97     c CALL PRINT_ERROR( msgBuf, myThid )
98     c STOP 'ABNORMAL END: EXCH1_BG_RX_CUBE: no AD code'
99     c ENDIF
100     IF ( sNx.NE.sNy .OR.
101     & nSx.NE.6 .OR. nSy.NE.1 .OR.
102     & nPx.NE.1 .OR. nPy.NE.1 ) THEN
103     WRITE(msgBuf,'(2A)') 'EXCH1_BG_RX_CUBE: Wrong Tiling'
104     CALL PRINT_ERROR( msgBuf, myThid )
105     WRITE(msgBuf,'(2A)') 'EXCH1_BG_RX_CUBE: ',
106     & 'works only with sNx=sNy & nSx=6 & nSy=nPx=nPy=1'
107     CALL PRINT_ERROR( msgBuf, myThid )
108     STOP 'ABNORMAL END: EXCH1_BG_RX_CUBE: Wrong Tiling'
109     ENDIF
110    
111     C-- Could by-pass 1rst step (with updateEdges= 0) if vector field is
112     C valid over (1:sNx+1,1:sNy+1); In general this should be the case
113     C for correct computation domain; but some exceptions ? + I/O problems
114     C-- Exch of 2-Components vector (assumed to be 90.deg apart) at corner
115     C point is ill defined since we have 3 axes @ 120.deg apart.
116     C go with 3 options :
117     C updateEdges = 1 : do not touch corner values ;
118     C updateEdges = 2 : copy from corresponding face S.W corner (<= clear owner)
119     C and do nothing for missing corners ;
120     C updateEdges = 3 : copy all corner values.
121     C------
122     updateEdges = 2
123     IF ( withSigns ) updateEdges = MIN(1,updateEdges)
124    
125     negOne = 1.
126     IF (withSigns) negOne = -1.
127    
128     C For now tile<->tile exchanges are sequentialised through
129     C thread 1. This is a temporary feature for preliminary testing until
130     C general tile decomposistion is in place (CNH April 11, 2001)
131     CALL BAR2( myThid )
132     _BEGIN_MASTER( myThid )
133    
134     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
135    
136     IF ( updateEdges.GT.0 ) THEN
137     C-- 1rst Step : Just fill-in North (j=sNy+1) & East (i=sNx+1) edges
138    
139     j1 = 2
140     j2 = 2
141     j3 = sNy
142     IF ( updateEdges.GE.2 ) THEN
143     j1 = 1
144     j3 = sNy+1
145     ENDIF
146     IF ( updateEdges.EQ.3 ) j2 = 1
147    
148     DO bt = 1,nSx
149     IF ( MOD(bt,2).EQ.1 ) THEN
150     C Odd face Number:
151    
152     bn=tilemod(bt+2)
153     bs=tilemod(bt-1)
154     be=tilemod(bt+1)
155     bw=tilemod(bt-2)
156    
157     i = 1
158     DO k = 1, myNz
159     C Tile Odd:Odd+2 [get] [North<-West]
160     DO j = j2, j3
161     uField(j,sNy+i,k,bt,1) = vField(i,sNy+2-j,k,bn,1)*negOne
162     vField(j,sNy+i,k,bt,1) = uField(i,sNy+2-j,k,bn,1)
163     ENDDO
164     C Tile Odd:Odd+1 [get] [East<-West]
165     DO j = j1, sNy
166     uField(sNx+i,j,k,bt,1) = uField(i,j,k,be,1)
167     vField(sNx+i,j,k,bt,1) = vField(i,j,k,be,1)
168     ENDDO
169     ENDDO
170    
171     ELSE
172     C Even face Number:
173    
174     bn=tilemod(bt+1)
175     bs=tilemod(bt-2)
176     be=tilemod(bt+2)
177     bw=tilemod(bt-1)
178    
179     i = 1
180     DO k = 1, myNz
181     C Tile Even:Even+1 [get] [North<-South]
182     DO j = j1, sNy
183     uField(j,sNy+i,k,bt,1) = uField(j,i,k,bn,1)
184     vField(j,sNy+i,k,bt,1) = vField(j,i,k,bn,1)
185     ENDDO
186     C Tile Even:Even+2 [get] [East<-South]
187     DO j = j2, j3
188     uField(sNx+i,j,k,bt,1) = vField(sNx+2-j,i,k,be,1)
189     vField(sNx+i,j,k,bt,1) = uField(sNx+2-j,i,k,be,1)*negOne
190     ENDDO
191     ENDDO
192    
193     C-- end odd/even face number
194     ENDIF
195     C-- end loop on tile index bt
196     ENDDO
197    
198     C-- End of 1rst Step
199     ENDIF
200    
201     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
202    
203     C-- 2nd Step: fill-in (true) overlap regions:
204    
205     DO bt = 1,nSx
206     IF ( MOD(bt,2).EQ.1 ) THEN
207     C Odd face Number:
208    
209     bn=tilemod(bt+2)
210     bs=tilemod(bt-1)
211     be=tilemod(bt+1)
212     bw=tilemod(bt-2)
213    
214     DO k = 1, myNz
215     DO j = 1, sNy+1
216     DO i = 2, exchWidthX
217    
218     C Tile Odd:Odd+2 [get] [North<-West]
219     uField(j,sNy+i,k,bt,1) = vField(i,sNy+2-j,k,bn,1)*negOne
220     vField(j,sNy+i,k,bt,1) = uField(i,sNy+2-j,k,bn,1)
221     C Tile Odd:Odd+1 [get] [East<-West]
222     uField(sNx+i,j,k,bt,1) = uField(i,j,k,be,1)
223     vField(sNx+i,j,k,bt,1) = vField(i,j,k,be,1)
224    
225     ENDDO
226     DO i = 1-exchWidthX, 0
227    
228     C Tile Odd:Odd-1 [get] [South<-North]
229     uField(j,i,k,bt,1) = uField(j,sNy+i,k,bs,1)
230     vField(j,i,k,bt,1) = vField(j,sNy+i,k,bs,1)
231     C Tile Odd:Odd-2 [get] [West<-North]
232     uField(i,j,k,bt,1) = vField(sNx+2-j,sNy+i,k,bw,1)
233     vField(i,j,k,bt,1) = uField(sNx+2-j,sNy+i,k,bw,1)*negOne
234    
235     ENDDO
236     ENDDO
237     ENDDO
238    
239     ELSE
240     C Even face Number:
241    
242     bn=tilemod(bt+1)
243     bs=tilemod(bt-2)
244     be=tilemod(bt+2)
245     bw=tilemod(bt-1)
246    
247     DO k = 1, myNz
248     DO j = 1, sNy+1
249     DO i = 2, exchWidthX
250    
251     C Tile Even:Even+2 [get] [East<-South]
252     uField(sNx+i,j,k,bt,1) = vField(sNx+2-j,i,k,be,1)
253     vField(sNx+i,j,k,bt,1) = uField(sNx+2-j,i,k,be,1)*negOne
254     C Tile Even:Even+1 [get] [North<-South]
255     uField(j,sNy+i,k,bt,1) = uField(j,i,k,bn,1)
256     vField(j,sNy+i,k,bt,1) = vField(j,i,k,bn,1)
257    
258     ENDDO
259     DO i = 1-exchWidthX, 0
260    
261     C Tile Even:Even-2 [get] [South<-East]
262     uField(j,i,k,bt,1) = vField(sNx+i,sNy+2-j,k,bs,1)*negOne
263     vField(j,i,k,bt,1) = uField(sNx+i,sNy+2-j,k,bs,1)
264     C Tile Even:Even-1 [get] [West<-East]
265     uField(i,j,k,bt,1) = uField(sNx+i,j,k,bw,1)
266     vField(i,j,k,bt,1) = vField(sNx+i,j,k,bw,1)
267    
268     ENDDO
269     ENDDO
270     ENDDO
271    
272     C-- end odd/even face number
273     ENDIF
274     C-- end loop on tile index bt
275     ENDDO
276    
277     _END_MASTER( myThid )
278     CALL BAR2(myThid)
279    
280     RETURN
281     END

  ViewVC Help
Powered by ViewVC 1.1.22