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

Contents of /MITgcm/pkg/exch2/exch2_uv_xyz_rx.template

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


Revision 1.5 - (show annotations) (download)
Wed Feb 9 23:43:17 2005 UTC (19 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57g_pre, checkpoint57f_post, checkpoint57j_post, checkpoint57f_pre, checkpoint57g_post, checkpoint57h_pre, checkpoint57e_post, checkpoint57h_post, checkpoint57k_post, checkpoint57d_post, checkpoint57i_post, checkpoint57h_done, eckpoint57e_pre, checkpoint57l_post
Changes since 1.4: +5 -9 lines
temporary fix: add a 3rd call to the exchange to fix the 24.tiles CS set-up

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