/[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.2 - (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.1: +2 -2 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.2 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_uv_dgrid_3d_rx.template,v 1.1 2007/08/17 18:21:30 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     c#include "EESUPPORT.h"
40 jmc 1.2 #include "W2_EXCH2_SIZE.h"
41 jmc 1.1 #include "W2_EXCH2_TOPOLOGY.h"
42    
43     C !INPUT/OUTPUT PARAMETERS:
44     C == Argument list variables ==
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 i,j,k,bi,bj :: loop indices.
54     C OL[wens] :: Overlap extents in west, east, north, south.
55     C exchWidth[XY] :: Extent of regions that will be exchanged.
56    
57     INTEGER i,j,k,bi,bj
58     INTEGER OLw, OLe, OLn, OLs, exchWidthX, exchWidthY
59     _RX negOne
60     INTEGER myTile, myFace
61     CEOP
62    
63     OLw = OLx
64     OLe = OLx
65     OLn = OLy
66     OLs = OLy
67     exchWidthX = OLx
68     exchWidthY = OLy
69     negOne = 1.
70     IF (withSigns) negOne = -1.
71    
72     IF ( useCubedSphereExchange ) THEN
73     C--- using CubedSphereExchange:
74    
75     C-- First call the exchanges for the two components, ignoring the Sign
76     C note the order: vPhi,uPhi on D-grid are co-located with (u,v)_Cgrid
77    
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     c CALL EXCH2_RX2_CUBE( vPhi, uPhi, .FALSE., 'UV',
87     c I OLw, OLe, OLs, OLn, myNz,
88     c I exchWidthX, exchWidthY,
89     c I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
90    
91     C- note: can substitute the low-level S/R calls above with:
92     #ifdef W2_USE_R1_ONLY
93     CALL EXCH2_UV_CGRID_3D_RX(
94     U vPhi, uPhi,
95     I .FALSE., myNz, myThid )
96     #else
97     CALL EXCH2_UV_3D_RX(
98     U vPhi, uPhi,
99     I .FALSE., myNz, myThid )
100     #endif
101    
102     C-- Then we may need to switch the signs depending on which cube face
103     C we are located.
104    
105     C-- Loops on tile indices:
106     DO bj = myByLo(myThid), myByHi(myThid)
107     DO bi = myBxLo(myThid), myBxHi(myThid)
108    
109     C- Now choose what to do at each edge of the halo based on which face
110     C (we assume that bj is always=1)
111     myTile = W2_myTileList(bi)
112     myFace = exch2_myFace(myTile)
113    
114     C-- Loops on level index:
115     DO k = 1,myNz
116    
117     C- odd faces share disposition of all sections of the halo
118     IF ( MOD(myFace,2).EQ.1 ) THEN
119     C- North:
120     IF (exch2_isNedge(myTile).EQ.1) THEN
121     DO j = 1,exchWidthY
122     DO i = 1-OLx,sNx+OLx
123     uPhi(i,sNy+j,k,bi,bj) = uPhi(i,sNy+j,k,bi,bj)*negOne
124     c vPhi(i,sNy+j,k,bi,bj) = vPhi(i,sNy+j,k,bi,bj)
125     ENDDO
126     ENDDO
127     ENDIF
128     C- South: (nothing to change)
129     c IF (exch2_isSedge(myTile).EQ.1) THEN
130     c DO j = 1,exchWidthY
131     c DO i = 1-OLx,sNx+OLx
132     c uPhi(i,1-j,k,bi,bj) = uPhi(i,1-j,k,bi,bj)
133     c vPhi(i,1-j,k,bi,bj) = vPhi(i,1-j,k,bi,bj)
134     c ENDDO
135     c ENDDO
136     c ENDIF
137     C- East: (nothing to change)
138     c IF (exch2_isEedge(myTile).EQ.1) THEN
139     c DO j = 1-OLy,sNy+OLy
140     c DO i = 1,exchWidthX
141     c uPhi(sNx+i,j,k,bi,bj) = uPhi(sNx+i,j,k,bi,bj)
142     c vPhi(sNx+i,j,k,bi,bj) = vPhi(sNx+i,j,k,bi,bj)
143     c ENDDO
144     c ENDDO
145     c ENDIF
146     C- West:
147     IF (exch2_isWedge(myTile).EQ.1) THEN
148     DO j = 1-OLy,sNy+OLy
149     DO i = 1,exchWidthX
150     c uPhi(1-i,j,k,bi,bj) = uPhi(1-i,j,k,bi,bj)
151     vPhi(1-i,j,k,bi,bj) = vPhi(1-i,j,k,bi,bj)*negOne
152     ENDDO
153     ENDDO
154     ENDIF
155    
156     ELSE
157     C- Now the even faces (share disposition of all sections of the halo)
158    
159     C- East:
160     IF (exch2_isEedge(myTile).EQ.1) THEN
161     DO j = 1-OLy,sNy+OLy
162     DO i = 1,exchWidthX
163     c uPhi(sNx+i,j,k,bi,bj) = uPhi(sNx+i,j,k,bi,bj)
164     vPhi(sNx+i,j,k,bi,bj) = vPhi(sNx+i,j,k,bi,bj)*negOne
165     ENDDO
166     ENDDO
167     ENDIF
168     C- West: (nothing to change)
169     c IF (exch2_isWedge(myTile).EQ.1) THEN
170     c DO j = 1-OLy,sNy+OLy
171     c DO i = 1,exchWidthX
172     c uPhi(1-i,j,k,bi,bj) = uPhi(1-i,j,k,bi,bj)
173     c vPhi(1-i,j,k,bi,bj) = vPhi(1-i,j,k,bi,bj)
174     c ENDDO
175     c ENDDO
176     c ENDIF
177     C- North: (nothing to change)
178     c IF (exch2_isNedge(myTile).EQ.1) THEN
179     c DO j = 1,exchWidthY
180     c DO i = 1-OLx,sNx+OLx
181     c uPhi(i,sNy+j,k,bi,bj) = uPhi(i,sNy+j,k,bi,bj)
182     c vPhi(i,sNy+j,k,bi,bj) = vPhi(i,sNy+j,k,bi,bj)
183     c ENDDO
184     c ENDDO
185     c ENDIF
186     C- South:
187     IF (exch2_isSedge(myTile).EQ.1) THEN
188     DO j = 1,exchWidthY
189     DO i = 1-OLx,sNx+OLx
190     uPhi(i,1-j,k,bi,bj) = uPhi(i,1-j,k,bi,bj)*negOne
191     c vPhi(i,1-j,k,bi,bj) = vPhi(i,1-j,k,bi,bj)
192     ENDDO
193     ENDDO
194     ENDIF
195    
196     C end odd / even faces
197     ENDIF
198    
199     C-- end of Loops on tile and level indices (k,bi,bj).
200     ENDDO
201     ENDDO
202     ENDDO
203    
204     ELSE
205     C--- not using CubedSphereExchange:
206    
207     #ifndef AUTODIFF_EXCH2
208     CALL EXCH_RX( uPhi,
209     I OLw, OLe, OLs, OLn, myNz,
210     I exchWidthX, exchWidthY,
211     I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
212     CALL EXCH_RX( vPhi,
213     I OLw, OLe, OLs, OLn, myNz,
214     I exchWidthX, exchWidthY,
215     I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
216     #endif
217    
218     C--- using or not using CubedSphereExchange: end
219     ENDIF
220    
221     RETURN
222     END
223    
224     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
225    
226     CEH3 ;;; Local Variables: ***
227     CEH3 ;;; mode:fortran ***
228     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22