/[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.6 by jmc, Sun Jul 24 01:35:06 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 66  C                that is calling it here Line 68  C                that is calling it here
68  C                that threads are synchronised before exchanges  C                that threads are synchronised before exchanges
69  C                begine.  C                begine.
70        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
71    
72         CALL EXCH2_RX2_CUBE( Uphi, Vphi, withSigns, 'UV',         CALL EXCH2_RX2_CUBE( Uphi, Vphi, withSigns, 'UV',
73       I            OLw, OLe, OLs, OLn, myNz,       I            OLw, OLe, OLs, OLn, myNz,
74       I            exchWidthX, exchWidthY,       I            exchWidthX, exchWidthY,
# Line 78  C                begine. Line 81  C                begine.
81       I            OLw, OLe, OLs, OLn, myNz,       I            OLw, OLe, OLs, OLn, myNz,
82       I            exchWidthX, exchWidthY,       I            exchWidthX, exchWidthY,
83       I            FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )       I            FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
84    
85         DO bj=myByLo(myThid),myByHi(myThid)         DO bj=myByLo(myThid),myByHi(myThid)
86          DO bi=myBxLo(myThid),myBxHi(myThid)          DO bi=myBxLo(myThid),myBxHi(myThid)
87           myTile = W2_myTileList(bi)           myTile = W2_myTileList(bi)
88    
89           IF ( exch2_isEedge(myTile) .EQ. 1 .AND.           IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
90       &        exch2_isSedge(myTile) .EQ. 1 ) THEN       &        exch2_isSedge(myTile) .EQ. 1 ) THEN
91  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 111  C          Uphi(snx+1,sny+1,bi,bj)= vPhi
111            ENDIF            ENDIF
112           ENDIF           ENDIF
113    
114  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
115  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
116  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))
117    
118           IF ( exch2_isWedge(myTile) .EQ. 1 .AND.           IF ( exch2_isWedge(myTile) .EQ. 1 .AND.
119       &        exch2_isSedge(myTile) .EQ. 1 ) THEN       &        exch2_isSedge(myTile) .EQ. 1 ) THEN
120  C         Zero SW corner points  C         Zero SW corner points
121    #ifdef W2_FILL_NULL_REGIONS
122            DO J=1-OLx,0            DO J=1-OLx,0
123             DO I=1-OLx,0             DO I=1-OLx,0
124              uPhi(I,J,bi,bj)=0.              uPhi(I,J,bi,bj)=e2FillValue_RX
125             ENDDO             ENDDO
126            ENDDO            ENDDO
127            DO J=1-OLx,0            DO J=1-OLx,0
128             DO I=1-OLx,0             DO I=1-OLx,0
129              vPhi(I,J,bi,bj)=0.              vPhi(I,J,bi,bj)=e2FillValue_RX
130             ENDDO             ENDDO
131            ENDDO            ENDDO
132    #endif
133              uPhi(0,0,bi,bj)=vPhi(1,0,bi,bj)              uPhi(0,0,bi,bj)=vPhi(1,0,bi,bj)
134              vPhi(0,0,bi,bj)=uPhi(0,1,bi,bj)              vPhi(0,0,bi,bj)=uPhi(0,1,bi,bj)
135           ENDIF           ENDIF
136    
137           IF ( exch2_isWedge(myTile) .EQ. 1 .AND.           IF ( exch2_isWedge(myTile) .EQ. 1 .AND.
138       &        exch2_isNedge(myTile) .EQ. 1 ) THEN       &        exch2_isNedge(myTile) .EQ. 1 ) THEN
139  C         Zero NW corner points  C         Zero NW corner points
140    #ifdef W2_FILL_NULL_REGIONS
141            DO J=sNy+1,sNy+OLy            DO J=sNy+1,sNy+OLy
142             DO I=1-OLx,0             DO I=1-OLx,0
143              uPhi(I,J,bi,bj)=0.              uPhi(I,J,bi,bj)=e2FillValue_RX
144             ENDDO             ENDDO
145            ENDDO            ENDDO
146            DO J=sNy+2,sNy+OLy            DO J=sNy+2,sNy+OLy
147             DO I=1-OLx,0             DO I=1-OLx,0
148              vPhi(I,J,bi,bj)=0.              vPhi(I,J,bi,bj)=e2FillValue_RX
149             ENDDO             ENDDO
150            ENDDO            ENDDO
151    #endif
152            IF ( withSigns ) THEN            IF ( withSigns ) THEN
153              uPhi(0,sNy+1,bi,bj)=-vPhi(1,sNy+2,bi,bj)              uPhi(0,sNy+1,bi,bj)=-vPhi(1,sNy+2,bi,bj)
154              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 157  C         Zero NW corner points
157              vPhi(0,sNy+2,bi,bj)= uPhi(0,sNy,bi,bj)              vPhi(0,sNy+2,bi,bj)= uPhi(0,sNy,bi,bj)
158            ENDIF            ENDIF
159           ENDIF           ENDIF
160    
161           IF ( exch2_isEedge(myTile) .EQ. 1 .AND.           IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
162       &        exch2_isSedge(myTile) .EQ. 1 ) THEN       &        exch2_isSedge(myTile) .EQ. 1 ) THEN
163  C         Zero SE corner points  C         Zero SE corner points
164    #ifdef W2_FILL_NULL_REGIONS
165            DO J=1-OLx,0            DO J=1-OLx,0
166             DO I=sNx+2,sNx+OLx             DO I=sNx+2,sNx+OLx
167              uPhi(I,J,bi,bj)=0.              uPhi(I,J,bi,bj)=e2FillValue_RX
168             ENDDO             ENDDO
169            ENDDO            ENDDO
170            DO J=1-OLx,0            DO J=1-OLx,0
171             DO I=sNx+1,sNx+OLx             DO I=sNx+1,sNx+OLx
172              vPhi(I,J,bi,bj)=0.              vPhi(I,J,bi,bj)=e2FillValue_RX
173             ENDDO             ENDDO
174            ENDDO            ENDDO
175    #endif
176            IF ( withSigns ) THEN            IF ( withSigns ) THEN
177              uPhi(sNx+2,0,bi,bj)=-vPhi(sNx,0,bi,bj)              uPhi(sNx+2,0,bi,bj)=-vPhi(sNx,0,bi,bj)
178              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 181  C         Zero SE corner points
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)
182            ENDIF            ENDIF
183           ENDIF           ENDIF
184    
185           IF ( exch2_isEedge(myTile) .EQ. 1 .AND.           IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
186       &        exch2_isNedge(myTile) .EQ. 1 ) THEN       &        exch2_isNedge(myTile) .EQ. 1 ) THEN
187  C         Zero NE corner points  C         Zero NE corner points
188    #ifdef W2_FILL_NULL_REGIONS
189            DO J=sNy+1,sNy+OLy            DO J=sNy+1,sNy+OLy
190             DO I=sNx+2,sNx+OLx             DO I=sNx+2,sNx+OLx
191              uPhi(I,J,bi,bj)=0.              uPhi(I,J,bi,bj)=e2FillValue_RX
192             ENDDO             ENDDO
193            ENDDO            ENDDO
194            DO J=sNy+2,sNy+OLy            DO J=sNy+2,sNy+OLy
195             DO I=sNx+1,sNx+OLx             DO I=sNx+1,sNx+OLx
196              vPhi(I,J,bi,bj)=0.              vPhi(I,J,bi,bj)=e2FillValue_RX
197             ENDDO             ENDDO
198            ENDDO            ENDDO
199    #endif
200              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)
201              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)
202           ENDIF           ENDIF
203    
204    C-      end bi,bj loops.
205          ENDDO          ENDDO
206         ENDDO         ENDDO
207    
208        ELSE        ELSE
209    
210  c      CALL EXCH_RX( Uphi,  c      CALL EXCH_RX( Uphi,
211  c    I            OLw, OLe, OLs, OLn, myNz,  c    I            OLw, OLe, OLs, OLn, myNz,
212  c    I            exchWidthX, exchWidthY,  c    I            exchWidthX, exchWidthY,
# Line 198  c    I            FORWARD_SIMULATION, EX Line 218  c    I            FORWARD_SIMULATION, EX
218  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:
219         _EXCH_XY_RX( Uphi, myThid )         _EXCH_XY_RX( Uphi, myThid )
220         _EXCH_XY_RX( Vphi, myThid )         _EXCH_XY_RX( Vphi, myThid )
221    
222        ENDIF        ENDIF
223    
224        RETURN        RETURN

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

  ViewVC Help
Powered by ViewVC 1.1.22