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

Diff of /MITgcm/pkg/exch2/exch2_uv_xy_rx.template

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

revision 1.5 by jmc, Wed Feb 9 23:43:17 2005 UTC revision 1.7 by jmc, Fri Nov 4 01:31:04 2005 UTC
# Line 2  C $Header$ Line 2  C $Header$
2  C $Name$  C $Name$
3    
4  #include "CPP_EEOPTIONS.h"  #include "CPP_EEOPTIONS.h"
5    #include "W2_OPTIONS.h"
6    
7  CBOP  CBOP
8    
9  C     !ROUTINE: EXCH_UV_XY_RX  C     !ROUTINE: EXCH_UV_XY_RX
10    
11  C     !INTERFACE:  C     !INTERFACE:
# Line 13  C     !INTERFACE: Line 15  C     !INTERFACE:
15        IMPLICIT NONE        IMPLICIT NONE
16  C     !DESCRIPTION:  C     !DESCRIPTION:
17  C     *==========================================================*  C     *==========================================================*
18  C     | SUBROUTINE EXCH_UV_XY_RX                                    C     | SUBROUTINE EXCH_UV_XY_RX
19  C     | o Handle exchanges for _RX, two-dimensional arrays.      C     | o Handle exchanges for _RX, two-dimensional arrays.
20  C     *==========================================================*  C     *==========================================================*
21  C     | Driver exchange routine which branches to cube sphere or  C     | Driver exchange routine which branches to cube sphere or
22  C     | global, simple cartesian index grid. Exchange routine is  C     | global, simple cartesian index grid. Exchange routine is
23  C     | called with two arrays that are components of a vector.  C     | called with two arrays that are components of a vector.
24  C     | These components are rotated and interchanged on the  C     | These components are rotated and interchanged on the
25  C     | rotated grid during cube exchanges.  C     | rotated grid during cube exchanges.
26  C     *==========================================================*  C     *==========================================================*
27    
# Line 49  C     == Local variables == Line 51  C     == Local variables ==
51  C     OL[wens]       :: Overlap extents in west, east, north, south.  C     OL[wens]       :: Overlap extents in west, east, north, south.
52  C     exchWidth[XY]  :: Extent of regions that will be exchanged.  C     exchWidth[XY]  :: Extent of regions that will be exchanged.
53        INTEGER OLw, OLe, OLn, OLs, exchWidthX, exchWidthY, myNz        INTEGER OLw, OLe, OLn, OLs, exchWidthX, exchWidthY, myNz
54        INTEGER bi, bj, myTile, i, j        INTEGER bi, bj, myTile, j
55    #ifdef W2_FILL_NULL_REGIONS
56          INTEGER i
57    #endif
58  CEOP  CEOP
59    
60        OLw        = OLx        OLw        = OLx
# Line 66  C                that is calling it here Line 71  C                that is calling it here
71  C                that threads are synchronised before exchanges  C                that threads are synchronised before exchanges
72  C                begine.  C                begine.
73        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
74    
75         CALL EXCH2_RX2_CUBE( Uphi, Vphi, withSigns, 'UV',         CALL EXCH2_RX2_CUBE( Uphi, Vphi, withSigns, 'UV',
76       I            OLw, OLe, OLs, OLn, myNz,       I            OLw, OLe, OLs, OLn, myNz,
77       I            exchWidthX, exchWidthY,       I            exchWidthX, exchWidthY,
# Line 78  C                begine. Line 84  C                begine.
84       I            OLw, OLe, OLs, OLn, myNz,       I            OLw, OLe, OLs, OLn, myNz,
85       I            exchWidthX, exchWidthY,       I            exchWidthX, exchWidthY,
86       I            FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )       I            FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
87    
88         DO bj=myByLo(myThid),myByHi(myThid)         DO bj=myByLo(myThid),myByHi(myThid)
89          DO bi=myBxLo(myThid),myBxHi(myThid)          DO bi=myBxLo(myThid),myBxHi(myThid)
90           myTile = W2_myTileList(bi)           myTile = W2_myTileList(bi)
91    
92           IF ( exch2_isEedge(myTile) .EQ. 1 .AND.           IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
93       &        exch2_isSedge(myTile) .EQ. 1 ) THEN       &        exch2_isSedge(myTile) .EQ. 1 ) THEN
94  C         Uphi(snx+1,    0,bi,bj)= vPhi(snx+1,    1,bi,bj)  C         Uphi(snx+1,    0,bi,bj)= vPhi(snx+1,    1,bi,bj)
# Line 106  C          Uphi(snx+1,sny+1,bi,bj)= vPhi Line 114  C          Uphi(snx+1,sny+1,bi,bj)= vPhi
114            ENDIF            ENDIF
115           ENDIF           ENDIF
116    
117  C        Now zero out the null areas that should not be used in the numerics  C--      Now zero out the null areas that should not be used in the numerics
118  C-       Also add one valid u,v value next to the corner, that allows  C        Also add one valid u,v value next to the corner, that allows
119  C         to compute vorticity on a wider stencil (e.g., vort3(0,1) & (1,0))  C         to compute vorticity on a wider stencil (e.g., vort3(0,1) & (1,0))
120    
121           IF ( exch2_isWedge(myTile) .EQ. 1 .AND.           IF ( exch2_isWedge(myTile) .EQ. 1 .AND.
122       &        exch2_isSedge(myTile) .EQ. 1 ) THEN       &        exch2_isSedge(myTile) .EQ. 1 ) THEN
123  C         Zero SW corner points  C         Zero SW corner points
124    #ifdef W2_FILL_NULL_REGIONS
125            DO J=1-OLx,0            DO J=1-OLx,0
126             DO I=1-OLx,0             DO I=1-OLx,0
127              uPhi(I,J,bi,bj)=0.              uPhi(I,J,bi,bj)=e2FillValue_RX
128             ENDDO             ENDDO
129            ENDDO            ENDDO
130            DO J=1-OLx,0            DO J=1-OLx,0
131             DO I=1-OLx,0             DO I=1-OLx,0
132              vPhi(I,J,bi,bj)=0.              vPhi(I,J,bi,bj)=e2FillValue_RX
133             ENDDO             ENDDO
134            ENDDO            ENDDO
135    #endif
136              uPhi(0,0,bi,bj)=vPhi(1,0,bi,bj)              uPhi(0,0,bi,bj)=vPhi(1,0,bi,bj)
137              vPhi(0,0,bi,bj)=uPhi(0,1,bi,bj)              vPhi(0,0,bi,bj)=uPhi(0,1,bi,bj)
138           ENDIF           ENDIF
139    
140           IF ( exch2_isWedge(myTile) .EQ. 1 .AND.           IF ( exch2_isWedge(myTile) .EQ. 1 .AND.
141       &        exch2_isNedge(myTile) .EQ. 1 ) THEN       &        exch2_isNedge(myTile) .EQ. 1 ) THEN
142  C         Zero NW corner points  C         Zero NW corner points
143    #ifdef W2_FILL_NULL_REGIONS
144            DO J=sNy+1,sNy+OLy            DO J=sNy+1,sNy+OLy
145             DO I=1-OLx,0             DO I=1-OLx,0
146              uPhi(I,J,bi,bj)=0.              uPhi(I,J,bi,bj)=e2FillValue_RX
147             ENDDO             ENDDO
148            ENDDO            ENDDO
149            DO J=sNy+2,sNy+OLy            DO J=sNy+2,sNy+OLy
150             DO I=1-OLx,0             DO I=1-OLx,0
151              vPhi(I,J,bi,bj)=0.              vPhi(I,J,bi,bj)=e2FillValue_RX
152             ENDDO             ENDDO
153            ENDDO            ENDDO
154    #endif
155            IF ( withSigns ) THEN            IF ( withSigns ) THEN
156              uPhi(0,sNy+1,bi,bj)=-vPhi(1,sNy+2,bi,bj)              uPhi(0,sNy+1,bi,bj)=-vPhi(1,sNy+2,bi,bj)
157              vPhi(0,sNy+2,bi,bj)=-uPhi(0,sNy,bi,bj)              vPhi(0,sNy+2,bi,bj)=-uPhi(0,sNy,bi,bj)
# Line 146  C         Zero NW corner points Line 160  C         Zero NW corner points
160              vPhi(0,sNy+2,bi,bj)= uPhi(0,sNy,bi,bj)              vPhi(0,sNy+2,bi,bj)= uPhi(0,sNy,bi,bj)
161            ENDIF            ENDIF
162           ENDIF           ENDIF
163    
164           IF ( exch2_isEedge(myTile) .EQ. 1 .AND.           IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
165       &        exch2_isSedge(myTile) .EQ. 1 ) THEN       &        exch2_isSedge(myTile) .EQ. 1 ) THEN
166  C         Zero SE corner points  C         Zero SE corner points
167    #ifdef W2_FILL_NULL_REGIONS
168            DO J=1-OLx,0            DO J=1-OLx,0
169             DO I=sNx+2,sNx+OLx             DO I=sNx+2,sNx+OLx
170              uPhi(I,J,bi,bj)=0.              uPhi(I,J,bi,bj)=e2FillValue_RX
171             ENDDO             ENDDO
172            ENDDO            ENDDO
173            DO J=1-OLx,0            DO J=1-OLx,0
174             DO I=sNx+1,sNx+OLx             DO I=sNx+1,sNx+OLx
175              vPhi(I,J,bi,bj)=0.              vPhi(I,J,bi,bj)=e2FillValue_RX
176             ENDDO             ENDDO
177            ENDDO            ENDDO
178    #endif
179            IF ( withSigns ) THEN            IF ( withSigns ) THEN
180              uPhi(sNx+2,0,bi,bj)=-vPhi(sNx,0,bi,bj)              uPhi(sNx+2,0,bi,bj)=-vPhi(sNx,0,bi,bj)
181              vPhi(sNx+1,0,bi,bj)=-uPhi(sNx+2,1,bi,bj)              vPhi(sNx+1,0,bi,bj)=-uPhi(sNx+2,1,bi,bj)
# Line 167  C         Zero SE corner points Line 184  C         Zero SE corner points
184              vPhi(sNx+1,0,bi,bj)= uPhi(sNx+2,1,bi,bj)              vPhi(sNx+1,0,bi,bj)= uPhi(sNx+2,1,bi,bj)
185            ENDIF            ENDIF
186           ENDIF           ENDIF
187    
188           IF ( exch2_isEedge(myTile) .EQ. 1 .AND.           IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
189       &        exch2_isNedge(myTile) .EQ. 1 ) THEN       &        exch2_isNedge(myTile) .EQ. 1 ) THEN
190  C         Zero NE corner points  C         Zero NE corner points
191    #ifdef W2_FILL_NULL_REGIONS
192            DO J=sNy+1,sNy+OLy            DO J=sNy+1,sNy+OLy
193             DO I=sNx+2,sNx+OLx             DO I=sNx+2,sNx+OLx
194              uPhi(I,J,bi,bj)=0.              uPhi(I,J,bi,bj)=e2FillValue_RX
195             ENDDO             ENDDO
196            ENDDO            ENDDO
197            DO J=sNy+2,sNy+OLy            DO J=sNy+2,sNy+OLy
198             DO I=sNx+1,sNx+OLx             DO I=sNx+1,sNx+OLx
199              vPhi(I,J,bi,bj)=0.              vPhi(I,J,bi,bj)=e2FillValue_RX
200             ENDDO             ENDDO
201            ENDDO            ENDDO
202    #endif
203              uPhi(sNx+2,sNy+1,bi,bj)=vPhi(sNx,sNy+2,bi,bj)              uPhi(sNx+2,sNy+1,bi,bj)=vPhi(sNx,sNy+2,bi,bj)
204              vPhi(sNx+1,sNy+2,bi,bj)=uPhi(sNx+2,sNy,bi,bj)              vPhi(sNx+1,sNy+2,bi,bj)=uPhi(sNx+2,sNy,bi,bj)
205           ENDIF           ENDIF
206    
207    C-      end bi,bj loops.
208          ENDDO          ENDDO
209         ENDDO         ENDDO
210    
211        ELSE        ELSE
212    
213  c      CALL EXCH_RX( Uphi,  c      CALL EXCH_RX( Uphi,
214  c    I            OLw, OLe, OLs, OLn, myNz,  c    I            OLw, OLe, OLs, OLn, myNz,
215  c    I            exchWidthX, exchWidthY,  c    I            exchWidthX, exchWidthY,
# Line 198  c    I            FORWARD_SIMULATION, EX Line 221  c    I            FORWARD_SIMULATION, EX
221  c_jmc: for JAM compatibility, replace the 2 CALLs above by the 2 CPP_MACROs:  c_jmc: for JAM compatibility, replace the 2 CALLs above by the 2 CPP_MACROs:
222         _EXCH_XY_RX( Uphi, myThid )         _EXCH_XY_RX( Uphi, myThid )
223         _EXCH_XY_RX( Vphi, myThid )         _EXCH_XY_RX( Vphi, myThid )
224    
225        ENDIF        ENDIF
226    
227        RETURN        RETURN

Legend:
Removed from v.1.5  
changed lines
  Added in v.1.7

  ViewVC Help
Powered by ViewVC 1.1.22