/[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.3 - (hide annotations) (download)
Fri Aug 1 00:50:18 2008 UTC (15 years, 9 months ago) by jmc
Branch: MAIN
Changes since 1.2: +10 -8 lines
Comment out 3rd exch call (no longer needed after changing index bounds);
for now, leave the V to U copy @ face corner (this induces truncation
 differences in adjoint-test global_ocean.cs32x15)

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

  ViewVC Help
Powered by ViewVC 1.1.22