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

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

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


Revision 1.3 - (hide annotations) (download)
Sun Jun 28 00:57:51 2009 UTC (14 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61s, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.2: +5 -20 lines
-always call exch2_*_cube, not exch-1 anymore, if useCubedSphereExchange=F
-add bj in exch2 arrays and S/R.

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_uv_dgrid_3d_rx.template,v 1.2 2009/05/12 19:44:58 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5     #include "W2_OPTIONS.h"
6    
7     CBOP
8     C !ROUTINE: EXCH2_UV_DGRID_3D_RX
9    
10     C !INTERFACE:
11     SUBROUTINE EXCH2_UV_DGRID_3D_RX(
12     U uPhi, vPhi,
13     I withSigns, myNz, myThid )
14    
15     C !DESCRIPTION:
16     C*=====================================================================*
17     C Purpose: SUBROUTINE EXCH2_UV_DGRID_3D_RX
18     C handle exchanges for a 3D vector field on an D-grid.
19     C
20     C Input:
21     C uPhi(lon,lat,levs,bi,bj) :: first component of vector
22     C vPhi(lon,lat,levs,bi,bj) :: second component of vector
23     C withSigns (logical) :: true to use sign of components
24     C myNz :: 3rd dimension of input arrays uPhi,vPhi
25     C myThid :: my Thread Id number
26     C
27     C Output: uPhi and vPhi are updated (halo regions filled)
28     C
29     C Calls: EXCH_RX (EXCH2_RX2_CUBE) ignoring sign
30     C then put back the right signs
31     C
32     C*=====================================================================*
33    
34     C !USES:
35     IMPLICIT NONE
36    
37     #include "SIZE.h"
38     #include "EEPARAMS.h"
39 jmc 1.2 #include "W2_EXCH2_SIZE.h"
40 jmc 1.1 #include "W2_EXCH2_TOPOLOGY.h"
41    
42     C !INPUT/OUTPUT PARAMETERS:
43     C == Argument list variables ==
44     INTEGER myNz
45     _RX uPhi(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNz,nSx,nSy)
46     _RX vPhi(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNz,nSx,nSy)
47     LOGICAL withSigns
48     INTEGER myThid
49    
50     C !LOCAL VARIABLES:
51     C == Local variables ==
52     C i,j,k,bi,bj :: loop indices.
53     C OL[wens] :: Overlap extents in west, east, north, south.
54     C exchWidth[XY] :: Extent of regions that will be exchanged.
55    
56     INTEGER i,j,k,bi,bj
57     INTEGER OLw, OLe, OLn, OLs, exchWidthX, exchWidthY
58     _RX negOne
59     INTEGER myTile, myFace
60     CEOP
61    
62     OLw = OLx
63     OLe = OLx
64     OLn = OLy
65     OLs = OLy
66     exchWidthX = OLx
67     exchWidthY = OLy
68     negOne = 1.
69     IF (withSigns) negOne = -1.
70    
71     C-- First call the exchanges for the two components, ignoring the Sign
72     C note the order: vPhi,uPhi on D-grid are co-located with (u,v)_Cgrid
73    
74     c CALL EXCH2_RX2_CUBE( vPhi, uPhi, .FALSE., 'UV',
75     c I OLw, OLe, OLs, OLn, myNz,
76     c I exchWidthX, exchWidthY,
77     c I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
78     c CALL EXCH2_RX2_CUBE( vPhi, uPhi, .FALSE., 'UV',
79     c I OLw, OLe, OLs, OLn, myNz,
80     c I exchWidthX, exchWidthY,
81     c I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
82     c CALL EXCH2_RX2_CUBE( vPhi, uPhi, .FALSE., 'UV',
83     c I OLw, OLe, OLs, OLn, myNz,
84     c I exchWidthX, exchWidthY,
85     c I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
86    
87     C- note: can substitute the low-level S/R calls above with:
88     #ifdef W2_USE_R1_ONLY
89     CALL EXCH2_UV_CGRID_3D_RX(
90     U vPhi, uPhi,
91     I .FALSE., myNz, myThid )
92     #else
93     CALL EXCH2_UV_3D_RX(
94     U vPhi, uPhi,
95     I .FALSE., myNz, myThid )
96     #endif
97    
98 jmc 1.3 IF ( useCubedSphereExchange ) THEN
99     C--- using CubedSphereExchange:
100    
101 jmc 1.1 C-- Then we may need to switch the signs depending on which cube face
102     C we are located.
103    
104     C-- Loops on tile indices:
105     DO bj = myByLo(myThid), myByHi(myThid)
106     DO bi = myBxLo(myThid), myBxHi(myThid)
107    
108     C- Now choose what to do at each edge of the halo based on which face
109     C (we assume that bj is always=1)
110 jmc 1.3 myTile = W2_myTileList(bi,bj)
111 jmc 1.1 myFace = exch2_myFace(myTile)
112    
113     C-- Loops on level index:
114     DO k = 1,myNz
115    
116     C- odd faces share disposition of all sections of the halo
117     IF ( MOD(myFace,2).EQ.1 ) THEN
118     C- North:
119     IF (exch2_isNedge(myTile).EQ.1) THEN
120     DO j = 1,exchWidthY
121     DO i = 1-OLx,sNx+OLx
122     uPhi(i,sNy+j,k,bi,bj) = uPhi(i,sNy+j,k,bi,bj)*negOne
123     c vPhi(i,sNy+j,k,bi,bj) = vPhi(i,sNy+j,k,bi,bj)
124     ENDDO
125     ENDDO
126     ENDIF
127     C- South: (nothing to change)
128     c IF (exch2_isSedge(myTile).EQ.1) THEN
129     c DO j = 1,exchWidthY
130     c DO i = 1-OLx,sNx+OLx
131     c uPhi(i,1-j,k,bi,bj) = uPhi(i,1-j,k,bi,bj)
132     c vPhi(i,1-j,k,bi,bj) = vPhi(i,1-j,k,bi,bj)
133     c ENDDO
134     c ENDDO
135     c ENDIF
136     C- East: (nothing to change)
137     c IF (exch2_isEedge(myTile).EQ.1) THEN
138     c DO j = 1-OLy,sNy+OLy
139     c DO i = 1,exchWidthX
140     c uPhi(sNx+i,j,k,bi,bj) = uPhi(sNx+i,j,k,bi,bj)
141     c vPhi(sNx+i,j,k,bi,bj) = vPhi(sNx+i,j,k,bi,bj)
142     c ENDDO
143     c ENDDO
144     c ENDIF
145     C- West:
146     IF (exch2_isWedge(myTile).EQ.1) THEN
147     DO j = 1-OLy,sNy+OLy
148     DO i = 1,exchWidthX
149     c uPhi(1-i,j,k,bi,bj) = uPhi(1-i,j,k,bi,bj)
150     vPhi(1-i,j,k,bi,bj) = vPhi(1-i,j,k,bi,bj)*negOne
151     ENDDO
152     ENDDO
153     ENDIF
154    
155     ELSE
156     C- Now the even faces (share disposition of all sections of the halo)
157    
158     C- East:
159     IF (exch2_isEedge(myTile).EQ.1) THEN
160     DO j = 1-OLy,sNy+OLy
161     DO i = 1,exchWidthX
162     c uPhi(sNx+i,j,k,bi,bj) = uPhi(sNx+i,j,k,bi,bj)
163     vPhi(sNx+i,j,k,bi,bj) = vPhi(sNx+i,j,k,bi,bj)*negOne
164     ENDDO
165     ENDDO
166     ENDIF
167     C- West: (nothing to change)
168     c IF (exch2_isWedge(myTile).EQ.1) THEN
169     c DO j = 1-OLy,sNy+OLy
170     c DO i = 1,exchWidthX
171     c uPhi(1-i,j,k,bi,bj) = uPhi(1-i,j,k,bi,bj)
172     c vPhi(1-i,j,k,bi,bj) = vPhi(1-i,j,k,bi,bj)
173     c ENDDO
174     c ENDDO
175     c ENDIF
176     C- North: (nothing to change)
177     c IF (exch2_isNedge(myTile).EQ.1) THEN
178     c DO j = 1,exchWidthY
179     c DO i = 1-OLx,sNx+OLx
180     c uPhi(i,sNy+j,k,bi,bj) = uPhi(i,sNy+j,k,bi,bj)
181     c vPhi(i,sNy+j,k,bi,bj) = vPhi(i,sNy+j,k,bi,bj)
182     c ENDDO
183     c ENDDO
184     c ENDIF
185     C- South:
186     IF (exch2_isSedge(myTile).EQ.1) THEN
187     DO j = 1,exchWidthY
188     DO i = 1-OLx,sNx+OLx
189     uPhi(i,1-j,k,bi,bj) = uPhi(i,1-j,k,bi,bj)*negOne
190     c vPhi(i,1-j,k,bi,bj) = vPhi(i,1-j,k,bi,bj)
191     ENDDO
192     ENDDO
193     ENDIF
194    
195     C end odd / even faces
196     ENDIF
197    
198     C-- end of Loops on tile and level indices (k,bi,bj).
199     ENDDO
200     ENDDO
201     ENDDO
202    
203     C--- using or not using CubedSphereExchange: end
204     ENDIF
205    
206     RETURN
207     END
208    
209     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
210    
211     CEH3 ;;; Local Variables: ***
212     CEH3 ;;; mode:fortran ***
213     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22