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

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

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


Revision 1.6 - (hide annotations) (download)
Tue May 12 19:44:58 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61o, checkpoint61r, checkpoint61p, checkpoint61q
Changes since 1.5: +4 -1 lines
new header files "W2_EXCH2_SIZE.h" (taken out of W2_EXCH2_TOPOLOGY.h)
             and "W2_EXCH2_BUFFER.h" (taken out of W2_EXCH2_PARAMS.h)

1 jmc 1.6 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_uv_3d_rx.template,v 1.5 2009/04/27 04:06:11 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5     #include "W2_OPTIONS.h"
6 jmc 1.4 #undef DO_CORNER_COPY_V2U
7 jmc 1.1
8     CBOP
9     C !ROUTINE: EXCH2_UV_3D_RX
10    
11     C !INTERFACE:
12     SUBROUTINE EXCH2_UV_3D_RX(
13     U Uphi, Vphi,
14     I withSigns, myNz, myThid )
15    
16     C !DESCRIPTION:
17     C *==========================================================*
18     C | SUBROUTINE EXCH2_UV_3D_RX
19     C | o Handle exchanges for _RX, 3-dimensional vector arrays.
20     C *==========================================================*
21     C | Vector arrays need to be rotated and interchaged for
22     C | exchange operations on some grids. This driver routine
23     C | branches to support this.
24     C *==========================================================*
25    
26     C !USES:
27     IMPLICIT NONE
28     C === Global data ===
29     #include "SIZE.h"
30     #include "EEPARAMS.h"
31 jmc 1.6 #include "W2_EXCH2_SIZE.h"
32 jmc 1.1 #include "W2_EXCH2_TOPOLOGY.h"
33 jmc 1.6 #ifdef W2_FILL_NULL_REGIONS
34 jmc 1.1 #include "W2_EXCH2_PARAMS.h"
35 jmc 1.6 #endif
36 jmc 1.1
37     C !INPUT/OUTPUT PARAMETERS:
38     C === Routine arguments ===
39     C phi :: Array with overlap regions are to be exchanged
40     C Note - The interface to EXCH_RX assumes that
41     C the standard Fortran 77 sequence association rules
42     C apply.
43     C myNz :: 3rd dimension of array to exchange
44     C myThid :: My thread id.
45     INTEGER myNz
46     _RX Uphi(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNz,nSx,nSy)
47     _RX Vphi(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNz,nSx,nSy)
48     LOGICAL withSigns
49     INTEGER myThid
50    
51     C !LOCAL VARIABLES:
52     C == Local variables ==
53     C OL[wens] :: Overlap extents in west, east, north, south.
54     C exchWidth[XY] :: Extent of regions that will be exchanged.
55     INTEGER OLw, OLe, OLn, OLs, exchWidthX, exchWidthY
56     INTEGER bi, bj, myTile, k, j
57     #ifdef W2_FILL_NULL_REGIONS
58     INTEGER i
59     #endif
60     CEOP
61    
62     OLw = OLx
63     OLe = OLx
64     OLn = OLy
65     OLs = OLy
66     exchWidthX = OLx
67     exchWidthY = OLy
68     C ** NOTE ** The exchange routine we use here does not
69     C require the preceeding and following barriers.
70     C However, the slow, simple exchange interface
71     C that is calling it here is meant to ensure
72     C that threads are synchronised before exchanges
73     C begine.
74    
75     IF (useCubedSphereExchange) THEN
76    
77 jmc 1.3 CALL EXCH2_RX2_CUBE( Uphi, Vphi, withSigns, 'Cg',
78 jmc 1.1 I OLw, OLe, OLs, OLn, myNz,
79     I exchWidthX, exchWidthY,
80     I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
81 jmc 1.3 CALL EXCH2_RX2_CUBE( Uphi, Vphi, withSigns, 'Cg',
82 jmc 1.1 I OLw, OLe, OLs, OLn, myNz,
83     I exchWidthX, exchWidthY,
84     I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
85 jmc 1.3 c CALL EXCH2_RX2_CUBE( Uphi, Vphi, withSigns, 'Cg',
86     c I OLw, OLe, OLs, OLn, myNz,
87     c I exchWidthX, exchWidthY,
88     c I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
89 jmc 1.1
90     DO bj=myByLo(myThid),myByHi(myThid)
91     DO bi=myBxLo(myThid),myBxHi(myThid)
92     myTile = W2_myTileList(bi)
93    
94 jmc 1.3 #ifdef DO_CORNER_COPY_V2U
95 jmc 1.1 IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
96     & exch2_isSedge(myTile) .EQ. 1 ) THEN
97     DO k=1,myNz
98     C Uphi(snx+1, 0,k,bi,bj)= vPhi(snx+1, 1,k,bi,bj)
99     DO j=1-olx,0
100     Uphi(snx+1, j,k,bi,bj)= vPhi(snx+(1-j), 1,k,bi,bj)
101     ENDDO
102     ENDDO
103     ENDIF
104     IF ( withSigns ) THEN
105     IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
106     & exch2_isNedge(myTile) .EQ. 1 ) THEN
107     DO k=1,myNz
108     C Uphi(snx+1,sny+1,k,bi,bj)=-vPhi(snx+1,sny+1,k,bi,bj)
109     DO j=1,olx
110     Uphi(snx+1,sny+j,k,bi,bj)=-vPhi(snx+j,sny+1,k,bi,bj)
111     ENDDO
112     ENDDO
113     ENDIF
114     ELSE
115     IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
116     & exch2_isNedge(myTile) .EQ. 1 ) THEN
117     DO k=1,myNz
118     C Uphi(snx+1,sny+1,k,bi,bj)= vPhi(snx+1,sny+1,k,bi,bj)
119     DO j=1,olx
120     Uphi(snx+1,sny+j,k,bi,bj)= vPhi(snx+j,sny+1,k,bi,bj)
121     ENDDO
122     ENDDO
123     ENDIF
124     ENDIF
125 jmc 1.4 #endif /* DO_CORNER_COPY_V2U */
126 jmc 1.1
127     C-- Now zero out the null areas that should not be used in the numerics
128     C Also add one valid u,v value next to the corner, that allows
129     C to compute vorticity on a wider stencil (e.g., vort3(0,1) & (1,0))
130    
131     IF ( exch2_isWedge(myTile) .EQ. 1 .AND.
132     & exch2_isSedge(myTile) .EQ. 1 ) THEN
133     C Zero SW corner points
134     DO K=1,myNz
135     #ifdef W2_FILL_NULL_REGIONS
136     DO J=1-OLx,0
137     DO I=1-OLx,0
138     uPhi(I,J,K,bi,bj)=e2FillValue_RX
139     ENDDO
140     ENDDO
141     DO J=1-OLx,0
142     DO I=1-OLx,0
143     vPhi(I,J,K,bi,bj)=e2FillValue_RX
144     ENDDO
145     ENDDO
146     #endif
147     uPhi(0,0,K,bi,bj)=vPhi(1,0,K,bi,bj)
148     vPhi(0,0,K,bi,bj)=uPhi(0,1,K,bi,bj)
149     ENDDO
150     ENDIF
151    
152     IF ( exch2_isWedge(myTile) .EQ. 1 .AND.
153     & exch2_isNedge(myTile) .EQ. 1 ) THEN
154     C Zero NW corner points
155     DO K=1,myNz
156     #ifdef W2_FILL_NULL_REGIONS
157     DO J=sNy+1,sNy+OLy
158     DO I=1-OLx,0
159     uPhi(I,J,K,bi,bj)=e2FillValue_RX
160     ENDDO
161     ENDDO
162     DO J=sNy+2,sNy+OLy
163     DO I=1-OLx,0
164     vPhi(I,J,K,bi,bj)=e2FillValue_RX
165     ENDDO
166     ENDDO
167     #endif
168     IF ( withSigns ) THEN
169     uPhi(0,sNy+1,K,bi,bj)=-vPhi(1,sNy+2,K,bi,bj)
170     vPhi(0,sNy+2,K,bi,bj)=-uPhi(0,sNy,K,bi,bj)
171     ELSE
172     uPhi(0,sNy+1,K,bi,bj)= vPhi(1,sNy+2,K,bi,bj)
173     vPhi(0,sNy+2,K,bi,bj)= uPhi(0,sNy,K,bi,bj)
174     ENDIF
175     ENDDO
176     ENDIF
177    
178     IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
179     & exch2_isSedge(myTile) .EQ. 1 ) THEN
180     C Zero SE corner points
181     DO K=1,myNz
182     #ifdef W2_FILL_NULL_REGIONS
183     DO J=1-OLx,0
184     DO I=sNx+2,sNx+OLx
185     uPhi(I,J,K,bi,bj)=e2FillValue_RX
186     ENDDO
187     ENDDO
188     DO J=1-OLx,0
189     DO I=sNx+1,sNx+OLx
190     vPhi(I,J,K,bi,bj)=e2FillValue_RX
191     ENDDO
192     ENDDO
193     #endif
194     IF ( withSigns ) THEN
195     uPhi(sNx+2,0,K,bi,bj)=-vPhi(sNx,0,K,bi,bj)
196     vPhi(sNx+1,0,K,bi,bj)=-uPhi(sNx+2,1,K,bi,bj)
197     ELSE
198     uPhi(sNx+2,0,K,bi,bj)= vPhi(sNx,0,K,bi,bj)
199     vPhi(sNx+1,0,K,bi,bj)= uPhi(sNx+2,1,K,bi,bj)
200     ENDIF
201     ENDDO
202     ENDIF
203    
204     IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
205     & exch2_isNedge(myTile) .EQ. 1 ) THEN
206     C Zero NE corner points
207     DO K=1,myNz
208     #ifdef W2_FILL_NULL_REGIONS
209     DO J=sNy+1,sNy+OLy
210     DO I=sNx+2,sNx+OLx
211     uPhi(I,J,K,bi,bj)=e2FillValue_RX
212     ENDDO
213     ENDDO
214     DO J=sNy+2,sNy+OLy
215     DO I=sNx+1,sNx+OLx
216     vPhi(I,J,K,bi,bj)=e2FillValue_RX
217     ENDDO
218     ENDDO
219     #endif
220     uPhi(sNx+2,sNy+1,K,bi,bj)=vPhi(sNx,sNy+2,K,bi,bj)
221     vPhi(sNx+1,sNy+2,K,bi,bj)=uPhi(sNx+2,sNy,K,bi,bj)
222     ENDDO
223     ENDIF
224     ENDDO
225     ENDDO
226    
227     ELSE
228    
229     c CALL EXCH_RX( Uphi,
230     c I OLw, OLe, OLs, OLn, myNz,
231     c I exchWidthX, exchWidthY,
232     c I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
233     c CALL EXCH_RX( Vphi,
234     c I OLw, OLe, OLs, OLn, myNz,
235     c I exchWidthX, exchWidthY,
236     c I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
237 jmc 1.5 CALL EXCH_3D_RX( Uphi, myNz, myThid )
238     CALL EXCH_3D_RX( Vphi, myNz, myThid )
239 jmc 1.1
240     ENDIF
241    
242     RETURN
243     END
244    
245     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
246    
247     CEH3 ;;; Local Variables: ***
248     CEH3 ;;; mode:fortran ***
249     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22