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

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

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


Revision 1.8 - (hide annotations) (download)
Sat Jul 28 16:07:35 2007 UTC (16 years, 10 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59g, checkpoint59f, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint61a
Changes since 1.7: +2 -2 lines
Comment a bunch of EESUPPORT.h includes which are not necessary
and interfere with parallel exch2 adjoint ('cph-mpi').

1 heimbach 1.8 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_uv_xy_rx.template,v 1.7 2005/11/04 01:31:04 jmc Exp $
2 afe 1.1 C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5 jmc 1.6 #include "W2_OPTIONS.h"
6 afe 1.1
7     CBOP
8 jmc 1.6
9 afe 1.1 C !ROUTINE: EXCH_UV_XY_RX
10    
11     C !INTERFACE:
12     SUBROUTINE EXCH2_UV_XY_RX(
13     U Uphi, Vphi, withSigns,
14     I myThid )
15     IMPLICIT NONE
16     C !DESCRIPTION:
17     C *==========================================================*
18 jmc 1.6 C | SUBROUTINE EXCH_UV_XY_RX
19     C | o Handle exchanges for _RX, two-dimensional arrays.
20 afe 1.1 C *==========================================================*
21     C | Driver exchange routine which branches to cube sphere or
22     C | global, simple cartesian index grid. Exchange routine is
23     C | called with two arrays that are components of a vector.
24 jmc 1.6 C | These components are rotated and interchanged on the
25 afe 1.1 C | rotated grid during cube exchanges.
26     C *==========================================================*
27    
28     C !USES:
29     C === Global data ===
30     #include "SIZE.h"
31     #include "EEPARAMS.h"
32 heimbach 1.8 cph-mpi#include "EESUPPORT.h"
33 afe 1.1 #include "W2_EXCH2_TOPOLOGY.h"
34     #include "W2_EXCH2_PARAMS.h"
35    
36     C !INPUT/OUTPUT PARAMETERS:
37     C === Routine arguments ===
38     C Uphi :: Arrays with overlap regions are to be exchanged
39     C Vphi Note - The interface to EXCH_ assumes that
40     C the standard Fortran 77 sequence association rules
41     C apply.
42     C myThid :: My thread id.
43     C withSigns :: Flag controlling whether vector is signed.
44     _RX Uphi(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
45     _RX Vphi(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
46     LOGICAL withSigns
47     INTEGER myThid
48    
49     C !LOCAL VARIABLES:
50     C == Local variables ==
51     C OL[wens] :: Overlap extents in west, east, north, south.
52     C exchWidth[XY] :: Extent of regions that will be exchanged.
53     INTEGER OLw, OLe, OLn, OLs, exchWidthX, exchWidthY, myNz
54 jmc 1.7 INTEGER bi, bj, myTile, j
55     #ifdef W2_FILL_NULL_REGIONS
56     INTEGER i
57     #endif
58 afe 1.1 CEOP
59    
60     OLw = OLx
61     OLe = OLx
62     OLn = OLy
63     OLs = OLy
64     exchWidthX = OLx
65     exchWidthY = OLy
66     myNz = 1
67     C ** NOTE ** The exchange routine we use here does not
68     C require the preceeding and following barriers.
69     C However, the slow, simple exchange interface
70     C that is calling it here is meant to ensure
71     C that threads are synchronised before exchanges
72     C begine.
73     IF (useCubedSphereExchange) THEN
74 jmc 1.6
75 afe 1.1 CALL EXCH2_RX2_CUBE( Uphi, Vphi, withSigns, 'UV',
76     I OLw, OLe, OLs, OLn, myNz,
77     I exchWidthX, exchWidthY,
78     I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
79     CALL EXCH2_RX2_CUBE( Uphi, Vphi, withSigns, 'UV',
80     I OLw, OLe, OLs, OLn, myNz,
81     I exchWidthX, exchWidthY,
82     I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
83 jmc 1.5 CALL EXCH2_RX2_CUBE( Uphi, Vphi, withSigns, 'UV',
84     I OLw, OLe, OLs, OLn, myNz,
85     I exchWidthX, exchWidthY,
86     I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
87 jmc 1.6
88 afe 1.1 DO bj=myByLo(myThid),myByHi(myThid)
89     DO bi=myBxLo(myThid),myBxHi(myThid)
90     myTile = W2_myTileList(bi)
91 jmc 1.6
92 afe 1.1 IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
93     & exch2_isSedge(myTile) .EQ. 1 ) THEN
94 cnh 1.2 C Uphi(snx+1, 0,bi,bj)= vPhi(snx+1, 1,bi,bj)
95     DO j=1-olx,0
96     Uphi(snx+1, j,bi,bj)= vPhi(snx+(1-j), 1,bi,bj)
97     ENDDO
98 afe 1.1 ENDIF
99     IF ( withSigns ) THEN
100     IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
101     & exch2_isNedge(myTile) .EQ. 1 ) THEN
102 cnh 1.2 C Uphi(snx+1,sny+1,bi,bj)=-vPhi(snx+1,sny+1,bi,bj)
103     DO j=1,olx
104     Uphi(snx+1,sny+j,bi,bj)=-vPhi(snx+j,sny+1,bi,bj)
105     ENDDO
106 afe 1.1 ENDIF
107     ELSE
108     IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
109     & exch2_isNedge(myTile) .EQ. 1 ) THEN
110 cnh 1.2 C Uphi(snx+1,sny+1,bi,bj)= vPhi(snx+1,sny+1,bi,bj)
111     DO j=1,olx
112     Uphi(snx+1,sny+j,bi,bj)= vPhi(snx+j,sny+1,bi,bj)
113     ENDDO
114 afe 1.1 ENDIF
115 cnh 1.2 ENDIF
116    
117 jmc 1.6 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
119 jmc 1.4 C to compute vorticity on a wider stencil (e.g., vort3(0,1) & (1,0))
120 jmc 1.6
121 cnh 1.2 IF ( exch2_isWedge(myTile) .EQ. 1 .AND.
122     & exch2_isSedge(myTile) .EQ. 1 ) THEN
123     C Zero SW corner points
124 jmc 1.6 #ifdef W2_FILL_NULL_REGIONS
125 cnh 1.2 DO J=1-OLx,0
126     DO I=1-OLx,0
127 jmc 1.6 uPhi(I,J,bi,bj)=e2FillValue_RX
128 cnh 1.2 ENDDO
129     ENDDO
130     DO J=1-OLx,0
131     DO I=1-OLx,0
132 jmc 1.6 vPhi(I,J,bi,bj)=e2FillValue_RX
133 cnh 1.2 ENDDO
134     ENDDO
135 jmc 1.6 #endif
136 jmc 1.4 uPhi(0,0,bi,bj)=vPhi(1,0,bi,bj)
137     vPhi(0,0,bi,bj)=uPhi(0,1,bi,bj)
138 cnh 1.2 ENDIF
139 jmc 1.6
140 cnh 1.2 IF ( exch2_isWedge(myTile) .EQ. 1 .AND.
141     & exch2_isNedge(myTile) .EQ. 1 ) THEN
142     C Zero NW corner points
143 jmc 1.6 #ifdef W2_FILL_NULL_REGIONS
144 cnh 1.2 DO J=sNy+1,sNy+OLy
145     DO I=1-OLx,0
146 jmc 1.6 uPhi(I,J,bi,bj)=e2FillValue_RX
147 cnh 1.2 ENDDO
148     ENDDO
149     DO J=sNy+2,sNy+OLy
150     DO I=1-OLx,0
151 jmc 1.6 vPhi(I,J,bi,bj)=e2FillValue_RX
152 cnh 1.2 ENDDO
153     ENDDO
154 jmc 1.6 #endif
155 jmc 1.4 IF ( withSigns ) THEN
156     uPhi(0,sNy+1,bi,bj)=-vPhi(1,sNy+2,bi,bj)
157     vPhi(0,sNy+2,bi,bj)=-uPhi(0,sNy,bi,bj)
158     ELSE
159     uPhi(0,sNy+1,bi,bj)= vPhi(1,sNy+2,bi,bj)
160     vPhi(0,sNy+2,bi,bj)= uPhi(0,sNy,bi,bj)
161     ENDIF
162 cnh 1.2 ENDIF
163 jmc 1.6
164 cnh 1.2 IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
165     & exch2_isSedge(myTile) .EQ. 1 ) THEN
166     C Zero SE corner points
167 jmc 1.6 #ifdef W2_FILL_NULL_REGIONS
168 cnh 1.2 DO J=1-OLx,0
169     DO I=sNx+2,sNx+OLx
170 jmc 1.6 uPhi(I,J,bi,bj)=e2FillValue_RX
171 cnh 1.2 ENDDO
172     ENDDO
173     DO J=1-OLx,0
174     DO I=sNx+1,sNx+OLx
175 jmc 1.6 vPhi(I,J,bi,bj)=e2FillValue_RX
176 cnh 1.2 ENDDO
177     ENDDO
178 jmc 1.6 #endif
179 jmc 1.4 IF ( withSigns ) THEN
180     uPhi(sNx+2,0,bi,bj)=-vPhi(sNx,0,bi,bj)
181     vPhi(sNx+1,0,bi,bj)=-uPhi(sNx+2,1,bi,bj)
182     ELSE
183     uPhi(sNx+2,0,bi,bj)= vPhi(sNx,0,bi,bj)
184     vPhi(sNx+1,0,bi,bj)= uPhi(sNx+2,1,bi,bj)
185     ENDIF
186 cnh 1.2 ENDIF
187 jmc 1.6
188 cnh 1.2 IF ( exch2_isEedge(myTile) .EQ. 1 .AND.
189     & exch2_isNedge(myTile) .EQ. 1 ) THEN
190     C Zero NE corner points
191 jmc 1.6 #ifdef W2_FILL_NULL_REGIONS
192 cnh 1.2 DO J=sNy+1,sNy+OLy
193     DO I=sNx+2,sNx+OLx
194 jmc 1.6 uPhi(I,J,bi,bj)=e2FillValue_RX
195 cnh 1.2 ENDDO
196     ENDDO
197     DO J=sNy+2,sNy+OLy
198     DO I=sNx+1,sNx+OLx
199 jmc 1.6 vPhi(I,J,bi,bj)=e2FillValue_RX
200 cnh 1.2 ENDDO
201     ENDDO
202 jmc 1.6 #endif
203 jmc 1.4 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)
205 afe 1.1 ENDIF
206 jmc 1.6
207     C- end bi,bj loops.
208 afe 1.1 ENDDO
209     ENDDO
210    
211     ELSE
212 jmc 1.6
213 afe 1.1 c CALL EXCH_RX( Uphi,
214     c I OLw, OLe, OLs, OLn, myNz,
215     c I exchWidthX, exchWidthY,
216     c I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
217     c CALL EXCH_RX( Vphi,
218     c I OLw, OLe, OLs, OLn, myNz,
219     c I exchWidthX, exchWidthY,
220     c I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
221     c_jmc: for JAM compatibility, replace the 2 CALLs above by the 2 CPP_MACROs:
222     _EXCH_XY_RX( Uphi, myThid )
223     _EXCH_XY_RX( Vphi, myThid )
224 jmc 1.6
225 afe 1.1 ENDIF
226    
227     RETURN
228     END
229 edhill 1.3
230     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
231    
232     CEH3 ;;; Local Variables: ***
233     CEH3 ;;; mode:fortran ***
234     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22