/[MITgcm]/MITgcm/pkg/generic_advdiff/gad_som_prep_cs_corner.F
ViewVC logotype

Annotation of /MITgcm/pkg/generic_advdiff/gad_som_prep_cs_corner.F

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


Revision 1.1 - (hide annotations) (download)
Tue Feb 12 20:32:34 2008 UTC (16 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint59q, checkpoint59p, checkpoint59o
prather advection scheme (SOM) coded for Cubed-Sphere grid

1 jmc 1.1 C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_exch_som.F,v 1.2 2008/02/08 17:16:15 jmc Exp $
2     C $Name: $
3    
4     #include "GAD_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: GAD_SOM_PREP_CS_CORNER
8     C !INTERFACE:
9     SUBROUTINE GAD_SOM_PREP_CS_CORNER(
10     U smVol, smTr0, smTr, smCorners,
11     I prep4dirX, overlapOnly, interiorOnly,
12     I N_edge, S_edge, E_edge, W_edge,
13     I iPass, k, myNz, bi, bj, myThid )
14    
15    
16     C !DESCRIPTION: \bv
17     C *==========================================================*
18     C | SUBROUTINE GAD_SOM_PREP_CS_CORNER
19     C | o Prepare for Horizontal SOM Advection :
20     C | when using Cubed-Sphere Grid, fill corner-halo regions
21     C | of all Tracer-moments with proper values
22     C *==========================================================*
23     C \ev
24     C !USES:
25     IMPLICIT NONE
26    
27     C === Global variables ===
28     #include "SIZE.h"
29     #include "EEPARAMS.h"
30     #include "GAD.h"
31    
32     C !INPUT/OUTPUT PARAMETERS:
33     C === Routine arguments ===
34     C smVol :: grid-cell volume
35     C smTr0 :: tracer Zero Order moment
36     C smTr :: tracer 1rst & 2nd Order moments
37     C smCorners :: Temporary storage of Corner-halo-regions values
38     C ( 3rd dim = Number of corners = 4 : SW, SE, NE, NW )
39     C prep4dirX :: True = prepare for X direction advection
40     C otherwise, prepare for Y direction advection.
41     C overlapOnly :: only update the edges of myTile, but not the interior
42     C interiorOnly :: only update the interior of myTile, but not the edges
43     C [N,S,E,W]_edge :: true if N,S,E,W edge of myTile is an Edge of the cube
44     C iPass :: current passage index in SOM_ADVECT
45     C k :: current level index
46     C myNz :: 3rd dimension of array to exchange
47     C bi,bj :: current tile indices
48     C myThid :: my Thread Id number
49     INTEGER myNz
50     _RL smVol(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNz)
51     _RL smTr0(1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNz)
52     _RL smTr (1-OLx:sNx+OLx,1-OLy:sNy+OLy,myNz,nSx,nSy,nSOM)
53     _RL smCorners(OLx,OLy,4,-1:nSOM)
54     LOGICAL prep4dirX, overlapOnly, interiorOnly
55     LOGICAL N_edge, S_edge, E_edge, W_edge
56     INTEGER iPass, k, bi, bj
57     INTEGER myThid
58     CEOP
59    
60     #ifdef GAD_ALLOW_SOM_ADVECT
61     C !LOCAL VARIABLES:
62     C === Local variables ===
63     INTEGER i,j, jPass, n
64     LOGICAL southWestCorner
65     LOGICAL southEastCorner
66     LOGICAL northEastCorner
67     LOGICAL northWestCorner
68    
69     southWestCorner = S_edge .AND. W_edge
70     southEastCorner = S_edge .AND. E_edge
71     northEastCorner = N_edge .AND. E_edge
72     northWestCorner = N_edge .AND. W_edge
73    
74     IF ( overlapOnly ) THEN
75     C-- to avoid repeating 2 times the full sequence of FILL_CS_CORNER calls,
76     C add a loop on jPass (from iPass to 2) to reproduce the following logic:
77     C 1 ) overlapOnly & iPass = 1 (face 3 & 6)
78     C - fill corners for the other direction
79     C - then store the corner values
80     C 2 ) IF overlapOnly :: fill corners for the current direction
81     C ELSEIF .NOT.interiorOnly :: get the corner values back from storage
82     C ENDIF
83     DO jPass = iPass,2
84    
85     IF ( ( jPass.EQ.2 .AND. prep4dirX ) .OR.
86     & ( jPass.EQ.1 .AND. .NOT.prep4dirX ) ) THEN
87     C-- Fill corners to prepare for calculations in X
88     CALL GAD_SOM_FILL_CS_CORNER( .TRUE.,
89     U smVol(1-OLx,1-OLy,k),
90     U smTr0(1-OLx,1-OLy,k),
91     U smTr(1-OLx,1-OLy,k,bi,bj,1),
92     U smTr(1-OLx,1-OLy,k,bi,bj,2),
93     U smTr(1-OLx,1-OLy,k,bi,bj,3),
94     U smTr(1-OLx,1-OLy,k,bi,bj,4),
95     U smTr(1-OLx,1-OLy,k,bi,bj,5),
96     U smTr(1-OLx,1-OLy,k,bi,bj,6),
97     U smTr(1-OLx,1-OLy,k,bi,bj,7),
98     U smTr(1-OLx,1-OLy,k,bi,bj,8),
99     U smTr(1-OLx,1-OLy,k,bi,bj,9),
100     I bi, bj, myThid )
101     C-- End of filling for X dir
102     c ENDIF
103    
104     ELSE
105     C Note: the 2 IF tests are equivalent to just 1 if/else test;
106     C use this later option and leave the former commented.
107    
108     c IF ( ( jPass.EQ.1 .AND. prep4dirX ) .OR.
109     c & ( jPass.EQ.2 .AND. .NOT.prep4dirX ) ) THEN
110     C-- Fill corners to prepare for calculations in Y
111     CALL GAD_SOM_FILL_CS_CORNER( .FALSE.,
112     U smVol(1-OLx,1-OLy,k),
113     U smTr0(1-OLx,1-OLy,k),
114     U smTr(1-OLx,1-OLy,k,bi,bj,1),
115     U smTr(1-OLx,1-OLy,k,bi,bj,2),
116     U smTr(1-OLx,1-OLy,k,bi,bj,3),
117     U smTr(1-OLx,1-OLy,k,bi,bj,4),
118     U smTr(1-OLx,1-OLy,k,bi,bj,5),
119     U smTr(1-OLx,1-OLy,k,bi,bj,6),
120     U smTr(1-OLx,1-OLy,k,bi,bj,7),
121     U smTr(1-OLx,1-OLy,k,bi,bj,8),
122     U smTr(1-OLx,1-OLy,k,bi,bj,9),
123     I bi, bj, myThid )
124     C-- End of filling for Y dir
125     ENDIF
126    
127     IF ( jPass.EQ.1 ) THEN
128     C-- Store corner values (to be used on the next iPass)
129     IF ( southWestCorner ) THEN
130     DO j=1,OLy
131     DO i=1,OLx
132     smCorners(i,j,1,-1) = smVol(i-OLx,j-OLy,k)
133     smCorners(i,j,1, 0) = smTr0(i-OLx,j-OLy,k)
134     DO n=1,nSOM
135     smCorners(i,j,1,n) = smTr (i-OLx,j-OLy,k,bi,bj,n)
136     ENDDO
137     ENDDO
138     ENDDO
139     ENDIF
140     IF ( southEastCorner ) THEN
141     DO j=1,OLy
142     DO i=1,OLx
143     smCorners(i,j,2,-1) = smVol(sNx+i,j-OLy,k)
144     smCorners(i,j,2, 0) = smTr0(sNx+i,j-OLy,k)
145     DO n=1,nSOM
146     smCorners(i,j,2,n) = smTr (sNx+i,j-OLy,k,bi,bj,n)
147     ENDDO
148     ENDDO
149     ENDDO
150     ENDIF
151     IF ( northEastCorner ) THEN
152     DO j=1,OLy
153     DO i=1,OLx
154     smCorners(i,j,3,-1) = smVol(sNx+i,sNy+j,k)
155     smCorners(i,j,3, 0) = smTr0(sNx+i,sNy+j,k)
156     DO n=1,nSOM
157     smCorners(i,j,3,n) = smTr (sNx+i,sNy+j,k,bi,bj,n)
158     ENDDO
159     ENDDO
160     ENDDO
161     ENDIF
162     IF ( northWestCorner ) THEN
163     DO j=1,OLy
164     DO i=1,OLx
165     smCorners(i,j,4,-1) = smVol(i-OLx,sNy+j,k)
166     smCorners(i,j,4, 0) = smTr0(i-OLx,sNy+j,k)
167     DO n=1,nSOM
168     smCorners(i,j,4,n) = smTr (i-OLx,sNy+j,k,bi,bj,n)
169     ENDDO
170     ENDDO
171     ENDDO
172     ENDIF
173     C-- End storing block
174     ENDIF
175    
176     C-- End of loop on jPass
177     ENDDO
178    
179     ELSEIF ( .NOT.interiorOnly ) THEN
180    
181     C-- Get back corner values from storage
182     IF ( southWestCorner ) THEN
183     DO j=1,OLy
184     DO i=1,OLx
185     smVol(i-OLx,j-OLy,k ) = smCorners(i,j,1,-1)
186     smTr0(i-OLx,j-OLy,k ) = smCorners(i,j,1, 0)
187     DO n=1,nSOM
188     smTr(i-OLx,j-OLy,k,bi,bj,n) = smCorners(i,j,1, n)
189     ENDDO
190     ENDDO
191     ENDDO
192     ENDIF
193     IF ( southEastCorner ) THEN
194     DO j=1,OLy
195     DO i=1,OLx
196     smVol(sNx+i,j-OLy,k ) = smCorners(i,j,2,-1)
197     smTr0(sNx+i,j-OLy,k ) = smCorners(i,j,2, 0)
198     DO n=1,nSOM
199     smTr(sNx+i,j-OLy,k,bi,bj,n) = smCorners(i,j,2, n)
200     ENDDO
201     ENDDO
202     ENDDO
203     ENDIF
204     IF ( northEastCorner ) THEN
205     DO j=1,OLy
206     DO i=1,OLx
207     smVol(sNx+i,sNy+j,k ) = smCorners(i,j,3,-1)
208     smTr0(sNx+i,sNy+j,k ) = smCorners(i,j,3, 0)
209     DO n=1,nSOM
210     smTr(sNx+i,sNy+j,k,bi,bj,n) = smCorners(i,j,3, n)
211     ENDDO
212     ENDDO
213     ENDDO
214     ENDIF
215     IF ( northWestCorner ) THEN
216     DO j=1,OLy
217     DO i=1,OLx
218     smVol(i-OLx,sNy+j,k ) = smCorners(i,j,4,-1)
219     smTr0(i-OLx,sNy+j,k ) = smCorners(i,j,4, 0)
220     DO n=1,nSOM
221     smTr(i-OLx,sNy+j,k,bi,bj,n) = smCorners(i,j,4, n)
222     ENDDO
223     ENDDO
224     ENDDO
225     ENDIF
226     C-- End getting back corner values from storage
227    
228     C--- End if/else - overlapOnly - block
229     ENDIF
230    
231     #endif /* GAD_ALLOW_SOM_ADVECT */
232    
233     RETURN
234     END

  ViewVC Help
Powered by ViewVC 1.1.22