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

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

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


Revision 1.7 - (hide annotations) (download)
Thu May 6 23:28:45 2010 UTC (14 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62g, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.6: +10 -11 lines
- S/R EXCH2_RX1,2_CUBE: remove argument "simulationMode" ;
- add argument "signOption" to EXCH2_RX1_CUBE (will be needed for SM exch)

1 jmc 1.7 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_uv_agrid_3d_rx.template,v 1.6 2009/06/28 00:57:51 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_AGRID_3D_RX
9    
10     C !INTERFACE:
11     SUBROUTINE EXCH2_UV_AGRID_3D_RX(
12 jmc 1.3 U uPhi, vPhi,
13 jmc 1.1 I withSigns, myNz, myThid )
14    
15     C !DESCRIPTION:
16     C*=====================================================================*
17     C Purpose: SUBROUTINE EXCH2_UV_AGRID_3D_RX
18     C handle exchanges for a 3D vector field on an A-grid.
19     C
20 jmc 1.3 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 jmc 1.1 C withSigns (logical) :: true to use sign of components
24 jmc 1.3 C myNz :: 3rd dimension of input arrays uPhi,vPhi
25 jmc 1.1 C myThid :: my Thread Id number
26     C
27 jmc 1.3 C Output: uPhi and vPhi are updated (halo regions filled)
28 jmc 1.1 C
29     C Calls: exch_RX (exch2_RX1_cube) - for each component
30     C
31     C*=====================================================================*
32    
33     C !USES:
34     IMPLICIT NONE
35    
36     #include "SIZE.h"
37     #include "EEPARAMS.h"
38 jmc 1.5 #include "W2_EXCH2_SIZE.h"
39 jmc 1.1 #include "W2_EXCH2_TOPOLOGY.h"
40    
41     C !INPUT/OUTPUT PARAMETERS:
42     C == Argument list variables ==
43     INTEGER myNz
44 jmc 1.3 _RX uPhi(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNz,nSx,nSy)
45     _RX vPhi(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNz,nSx,nSy)
46 jmc 1.1 LOGICAL withSigns
47     INTEGER myThid
48    
49     C !LOCAL VARIABLES:
50     C == Local variables ==
51     C i,j,k,bi,bj :: loop indices.
52     C OL[wens] :: Overlap extents in west, east, north, south.
53 jmc 1.3 C exchWidth[XY] :: Extent of regions that will be exchanged.
54     C uLoc,vLoc :: copies of the vector components with haloes filled.
55 jmc 1.1
56     INTEGER i,j,k,bi,bj
57     INTEGER OLw, OLe, OLn, OLs, exchWidthX, exchWidthY
58 jmc 1.3 _RX uLoc(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
59     _RX vLoc(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
60 jmc 1.1 _RX negOne
61 jmc 1.3 INTEGER myTile, myFace
62 jmc 1.1 CEOP
63    
64     OLw = OLx
65     OLe = OLx
66     OLn = OLy
67     OLs = OLy
68     exchWidthX = OLx
69     exchWidthY = OLy
70     negOne = 1.
71     IF (withSigns) negOne = -1.
72    
73 jmc 1.3 C-- First call the exchanges for the two components
74 jmc 1.1
75 jmc 1.7 CALL EXCH2_RX1_CUBE( uPhi, .FALSE., 'T ',
76 jmc 1.1 I OLw, OLe, OLs, OLn, myNz,
77     I exchWidthX, exchWidthY,
78 jmc 1.7 I EXCH_UPDATE_CORNERS, myThid )
79     CALL EXCH2_RX1_CUBE( uPhi, .FALSE., 'T ',
80 jmc 1.1 I OLw, OLe, OLs, OLn, myNz,
81     I exchWidthX, exchWidthY,
82 jmc 1.7 I EXCH_UPDATE_CORNERS, myThid )
83 jmc 1.1
84 jmc 1.7 CALL EXCH2_RX1_CUBE( vPhi, .FALSE., 'T ',
85 jmc 1.1 I OLw, OLe, OLs, OLn, myNz,
86     I exchWidthX, exchWidthY,
87 jmc 1.7 I EXCH_UPDATE_CORNERS, myThid )
88     CALL EXCH2_RX1_CUBE( vPhi, .FALSE., 'T ',
89 jmc 1.1 I OLw, OLe, OLs, OLn, myNz,
90     I exchWidthX, exchWidthY,
91 jmc 1.7 I EXCH_UPDATE_CORNERS, myThid )
92 jmc 1.1
93     C- note: can substitute the low-level S/R calls above with:
94 jmc 1.3 c CALL EXCH2_3D_RX( uPhi, myNz, myThid )
95     c CALL EXCH2_3D_RX( vPhi, myNz, myThid )
96 jmc 1.1
97 jmc 1.6 IF ( useCubedSphereExchange ) THEN
98    
99 jmc 1.3 C-- Then we may need to switch u and v components
100     C and/or the signs depending on which cube face we are located.
101 jmc 1.1
102 jmc 1.3 C-- Loops on tile indices:
103 jmc 1.1 DO bj = myByLo(myThid), myByHi(myThid)
104     DO bi = myBxLo(myThid), myBxHi(myThid)
105 jmc 1.3
106 jmc 1.7 C- Choose what to do at each edge of the halo based on which face we are
107 jmc 1.6 myTile = W2_myTileList(bi,bj)
108 jmc 1.3 myFace = exch2_myFace(myTile)
109    
110     C-- Loops on level index:
111 jmc 1.1 DO k = 1,myNz
112    
113 jmc 1.3 C- First we copy the component info into local dummy arrays
114 jmc 1.1 DO j = 1-OLy,sNy+OLy
115     DO i = 1-OLx,sNx+OLx
116 jmc 1.3 uLoc(i,j) = uPhi(i,j,k,bi,bj)
117     vLoc(i,j) = vPhi(i,j,k,bi,bj)
118 jmc 1.1 ENDDO
119     ENDDO
120    
121 jmc 1.3 C- odd faces share disposition of all sections of the halo
122     IF ( MOD(myFace,2).EQ.1 ) THEN
123     C- North:
124     IF (exch2_isNedge(myTile).EQ.1) THEN
125     DO j = 1,exchWidthY
126     DO i = 1-OLx,sNx+OLx
127     uPhi(i,sNy+j,k,bi,bj) = vLoc(i,sNy+j)*negOne
128     vPhi(i,sNy+j,k,bi,bj) = uLoc(i,sNy+j)
129     ENDDO
130     ENDDO
131     ENDIF
132     C- South: (nothing to change)
133     c IF (exch2_isSedge(myTile).EQ.1) THEN
134     c DO j = 1,exchWidthY
135     c DO i = 1-OLx,sNx+OLx
136     c uPhi(i,1-j,k,bi,bj) = uLoc(i,1-j)
137     c vPhi(i,1-j,k,bi,bj) = vLoc(i,1-j)
138     c ENDDO
139     c ENDDO
140     c ENDIF
141     C- East: (nothing to change)
142     c IF (exch2_isEedge(myTile).EQ.1) THEN
143 jmc 1.1 c DO j = 1-OLy,sNy+OLy
144     c DO i = 1,exchWidthX
145 jmc 1.3 c uPhi(sNx+i,j,k,bi,bj) = uLoc(sNx+i,j)
146     c vPhi(sNx+i,j,k,bi,bj) = vLoc(sNx+i,j)
147 jmc 1.1 c ENDDO
148     c ENDDO
149     c ENDIF
150 jmc 1.3 C- West:
151     IF (exch2_isWedge(myTile).EQ.1) THEN
152 jmc 1.1 DO j = 1-OLy,sNy+OLy
153     DO i = 1,exchWidthX
154 jmc 1.3 uPhi(1-i,j,k,bi,bj) = vLoc(1-i,j)
155     vPhi(1-i,j,k,bi,bj) = uLoc(1-i,j)*negOne
156 jmc 1.1 ENDDO
157     ENDDO
158     ENDIF
159    
160     ELSE
161 jmc 1.3 C- Now the even faces (share disposition of all sections of the halo)
162 jmc 1.1
163 jmc 1.3 C- East:
164     IF (exch2_isEedge(myTile).EQ.1) THEN
165 jmc 1.1 DO j = 1-OLy,sNy+OLy
166     DO i = 1,exchWidthX
167 jmc 1.3 uPhi(sNx+i,j,k,bi,bj) = vLoc(sNx+i,j)
168     vPhi(sNx+i,j,k,bi,bj) = uLoc(sNx+i,j)*negOne
169 jmc 1.1 ENDDO
170     ENDDO
171     ENDIF
172 jmc 1.3 C- West: (nothing to change)
173     c IF (exch2_isWedge(myTile).EQ.1) THEN
174 jmc 1.1 c DO j = 1-OLy,sNy+OLy
175     c DO i = 1,exchWidthX
176 jmc 1.3 c uPhi(1-i,j,k,bi,bj) = uLoc(1-i,j)
177     c vPhi(1-i,j,k,bi,bj) = vLoc(1-i,j)
178 jmc 1.1 c ENDDO
179     c ENDDO
180     c ENDIF
181 jmc 1.3 C- North: (nothing to change)
182     c IF (exch2_isNedge(myTile).EQ.1) THEN
183 jmc 1.1 c DO j = 1,exchWidthY
184     c DO i = 1-OLx,sNx+OLx
185 jmc 1.3 c uPhi(i,sNy+j,k,bi,bj) = uLoc(i,sNy+j)
186     c vPhi(i,sNy+j,k,bi,bj) = vLoc(i,sNy+j)
187 jmc 1.1 c ENDDO
188     c ENDDO
189     c ENDIF
190 jmc 1.3 C- South:
191     IF (exch2_isSedge(myTile).EQ.1) THEN
192 jmc 1.1 DO j = 1,exchWidthY
193     DO i = 1-OLx,sNx+OLx
194 jmc 1.3 uPhi(i,1-j,k,bi,bj) = vLoc(i,1-j)*negOne
195     vPhi(i,1-j,k,bi,bj) = uLoc(i,1-j)
196 jmc 1.1 ENDDO
197     ENDDO
198     ENDIF
199    
200     C end odd / even faces
201     ENDIF
202    
203     C-- end of Loops on tile and level indices (k,bi,bj).
204     ENDDO
205     ENDDO
206     ENDDO
207    
208     C--- using or not using CubedSphereExchange: end
209     ENDIF
210    
211     RETURN
212     END
213    
214     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
215    
216     CEH3 ;;; Local Variables: ***
217     CEH3 ;;; mode:fortran ***
218     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22