/[MITgcm]/MITgcm/eesupp/src/exch_uv_agrid_3d_rx.template
ViewVC logotype

Annotation of /MITgcm/eesupp/src/exch_uv_agrid_3d_rx.template

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


Revision 1.4 - (hide annotations) (download)
Fri Aug 17 18:34:17 2007 UTC (16 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint62, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59g, checkpoint59f, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.3: +8 -9 lines
cleaning:
 - only 1 RETURN instruction per S/R (to help TAF)
 - comment out #include "EXCH.h" in wrapper EXCH S/R (not necessary)
 - comment out unnecessary #include "EESUPPORT.h" (to make TAF happy)

1 jmc 1.4 C $Header: /u/gcmpack/MITgcm/eesupp/src/exch_uv_agrid_3d_rx.template,v 1.3 2006/11/18 01:08:38 heimbach Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "PACKAGES_CONFIG.h"
5     #include "CPP_EEOPTIONS.h"
6    
7     CBOP
8     C !ROUTINE: EXCH_UV_AGRID_3D_RX
9    
10     C !INTERFACE:
11     SUBROUTINE EXCH_UV_AGRID_3D_RX(
12     U Uphi, Vphi,
13     I withSigns, myNz, myThid )
14    
15     C !DESCRIPTION:
16     C*=====================================================================*
17     C Purpose: SUBROUTINE EXCH_UV_AGRID_3D_RX
18     C handle exchanges for a 3D vector field on an A-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 signs 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 (either exch_rx_cube or exch_rx) - twice, once
30     C for the first-component, once for second.
31     C
32     C NOTES: 1) If using CubedSphereExchange, only works on ONE PROCESSOR!
33     C*=====================================================================*
34    
35     C !USES:
36     IMPLICIT NONE
37    
38     #include "SIZE.h"
39     #include "EEPARAMS.h"
40 jmc 1.4 c#include "EESUPPORT.h"
41     c#include "EXCH.h"
42 jmc 1.1
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 jmc 1.4 #ifndef ALLOW_EXCH2
53 jmc 1.1 C == Local variables ==
54     C i,j,k,bi,bj :: are DO indices.
55     C OL[wens] :: Overlap extents in west, east, north, south.
56     C exchWidth[XY] :: Extent of regions that will be exchanged.
57     C dummy[12] :: copies of the vector components with haloes filled.
58    
59     INTEGER i,j,k,bi,bj
60     INTEGER OLw, OLe, OLn, OLs, exchWidthX, exchWidthY
61     _RX dummy1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
62     _RX dummy2(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
63     _RX negOne
64 jmc 1.4 #endif
65     CEOP
66 jmc 1.1
67     #ifdef ALLOW_EXCH2
68     CALL EXCH2_UV_AGRID_3D_RX(
69     U Uphi, Vphi,
70 jmc 1.2 I withSigns, myNz, myThid )
71 jmc 1.1 RETURN
72 jmc 1.4 #else /* ALLOW_EXCH2 */
73 jmc 1.1
74     OLw = OLx
75     OLe = OLx
76     OLn = OLy
77     OLs = OLy
78     exchWidthX = OLx
79     exchWidthY = OLy
80     negOne = 1.
81     IF (withSigns) negOne = -1.
82    
83    
84     IF (useCubedSphereExchange) THEN
85     C--- using CubedSphereExchange:
86    
87     C First call the exchanges for the two components
88    
89     CALL EXCH_RX_CUBE( Uphi,
90     I OLw, OLe, OLs, OLn, myNz,
91     I exchWidthX, exchWidthY,
92     I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
93     CALL EXCH_RX_CUBE( Vphi,
94     I OLw, OLe, OLs, OLn, myNz,
95     I exchWidthX, exchWidthY,
96     I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
97    
98     C Then if we are on the sphere we may need to switch u and v components
99     C and/or the signs depending on which cube face we are located.
100    
101     C-- Loops on tile and level indices:
102     DO bj = myByLo(myThid), myByHi(myThid)
103     DO bi = myBxLo(myThid), myBxHi(myThid)
104 jmc 1.2 DO k = 1,myNz
105 jmc 1.1
106     C First we need to copy the component info into dummy arrays
107     DO j = 1-OLy,sNy+OLy
108     DO i = 1-OLx,sNx+OLx
109     dummy1(i,j) = Uphi(i,j,k,bi,bj)
110     dummy2(i,j) = Vphi(i,j,k,bi,bj)
111     ENDDO
112     ENDDO
113    
114     C Now choose what to do at each edge of the halo based on which face
115     C (we assume that bj is always=1)
116    
117     C odd faces share disposition of all sections of the halo
118     IF ( MOD(bi,2).EQ.1 ) THEN
119     DO j = 1,sNy
120     DO i = 1,exchWidthX
121     C east (nothing to change)
122     c Uphi(sNx+i,j,k,bi,bj) = dummy1(sNx+i,j)
123     c Vphi(sNx+i,j,k,bi,bj) = dummy2(sNx+i,j)
124     C west
125     Uphi(1-i,j,k,bi,bj) = dummy2(1-i,j)
126     Vphi(1-i,j,k,bi,bj) = dummy1(1-i,j)*negOne
127     ENDDO
128     ENDDO
129     DO j = 1,exchWidthY
130     DO i = 1,sNx
131     C north
132     Uphi(i,sNy+j,k,bi,bj) = dummy2(i,sNy+j)*negOne
133     Vphi(i,sNy+j,k,bi,bj) = dummy1(i,sNy+j)
134     C south (nothing to change)
135     c Uphi(i,1-j,k,bi,bj) = dummy1(i,1-j)
136     c Vphi(i,1-j,k,bi,bj) = dummy2(i,1-j)
137     ENDDO
138     ENDDO
139    
140     ELSE
141     C now the even faces (share disposition of all sections of the halo)
142    
143     DO j = 1,sNy
144     DO i = 1,exchWidthX
145     C east
146     Uphi(sNx+i,j,k,bi,bj) = dummy2(sNx+i,j)
147     Vphi(sNx+i,j,k,bi,bj) = dummy1(sNx+i,j)*negOne
148     C west (nothing to change)
149     c Uphi(1-i,j,k,bi,bj) = dummy1(1-i,j)
150     c Vphi(1-i,j,k,bi,bj) = dummy2(1-i,j)
151     ENDDO
152     ENDDO
153     DO j = 1,exchWidthY
154     DO i = 1,sNx
155     C north (nothing to change)
156     c Uphi(i,sNy+j,k,bi,bj) = dummy1(i,sNy+j)
157     c Vphi(i,sNy+j,k,bi,bj) = dummy2(i,sNy+j)
158     C south
159     Uphi(i,1-j,k,bi,bj) = dummy2(i,1-j)*negOne
160     Vphi(i,1-j,k,bi,bj) = dummy1(i,1-j)
161    
162     ENDDO
163     ENDDO
164    
165     C end odd / even faces
166     ENDIF
167    
168     C-- end of Loops on tile and level indices (k,bi,bj).
169     ENDDO
170     ENDDO
171     ENDDO
172    
173     ELSE
174     C--- not using CubedSphereExchange:
175    
176     CALL EXCH_RX( Uphi,
177     I OLw, OLe, OLs, OLn, myNz,
178     I exchWidthX, exchWidthY,
179     I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
180     CALL EXCH_RX( Vphi,
181     I OLw, OLe, OLs, OLn, myNz,
182     I exchWidthX, exchWidthY,
183     I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
184    
185     C--- using or not using CubedSphereExchange: end
186     ENDIF
187    
188     RETURN
189 jmc 1.4 #endif /* ALLOW_EXCH2 */
190 jmc 1.1 END
191    
192     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
193    
194     CEH3 ;;; Local Variables: ***
195     CEH3 ;;; mode:fortran ***
196     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22