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

Contents of /MITgcm/pkg/generic_advdiff/gad_advection.F

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


Revision 1.1 - (show annotations) (download)
Mon Sep 10 01:22:48 2001 UTC (22 years, 8 months ago) by adcroft
Branch: MAIN
Added multi-dimensional form of advection
 o available only for single step schemes (ie. can't be used with ABII)
 o stable for max(cfl_u,cfl_v,cfl_w)<=1  (without cfl_u+cfl_v+cfl_w <=1)
 o selected using multiDimAdvection=.T.  (default)
 o had to hack some existing routines to work on local arrays

1 C $Header: $
2 C $Name: $
3
4 #include "GAD_OPTIONS.h"
5
6 SUBROUTINE GAD_ADVECTION(bi,bj,advectionScheme,tracerIdentity,
7 U Tracer,Gtracer,
8 I myTime,myIter,myThid)
9 C /==========================================================\
10 C | SUBROUTINE GAD_ADVECTION |
11 C | o Solves the pure advection tracer equation. |
12 C |==========================================================|
13 C \==========================================================/
14 IMPLICIT NONE
15
16 C == Global variables ===
17 #include "SIZE.h"
18 #include "EEPARAMS.h"
19 #include "PARAMS.h"
20 #include "DYNVARS.h"
21 #include "GRID.h"
22 #include "GAD.h"
23
24 C == Routine arguments ==
25 INTEGER bi,bj
26 INTEGER advectionScheme
27 INTEGER tracerIdentity
28 _RL Tracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
29 _RL Gtracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
30 _RL myTime
31 INTEGER myIter
32 INTEGER myThid
33
34 C == Local variables
35 _RS maskUp (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
36 INTEGER iMin,iMax,jMin,jMax
37 INTEGER i,j,k,kup,kDown,kp1
38 _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
39 _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
40 _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
41 _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
42 _RL rTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
43 _RL af (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
44 _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
45 _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
46 _RL localTijk(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
47 _RL kp1Msk
48
49 C-- Set up work arrays with valid (i.e. not NaN) values
50 C These inital values do not alter the numerical results. They
51 C just ensure that all memory references are to valid floating
52 C point numbers. This prevents spurious hardware signals due to
53 C uninitialised but inert locations.
54 DO j=1-OLy,sNy+OLy
55 DO i=1-OLx,sNx+OLx
56 xA(i,j) = 0. _d 0
57 yA(i,j) = 0. _d 0
58 uTrans(i,j) = 0. _d 0
59 vTrans(i,j) = 0. _d 0
60 rTrans(i,j) = 0. _d 0
61 fVerT(i,j,1) = 0. _d 0
62 fVerT(i,j,2) = 0. _d 0
63 ENDDO
64 ENDDO
65
66 iMin = 1-OLx
67 iMax = sNx+OLx
68 jMin = 1-OLy
69 jMax = sNy+OLy
70
71 C-- Start of k loop for horizontal fluxes
72 DO k=1,Nr
73
74 C-- Get temporary terms used by tendency routines
75 CALL CALC_COMMON_FACTORS (
76 I bi,bj,iMin,iMax,jMin,jMax,k,
77 O xA,yA,uTrans,vTrans,rTrans,maskUp,
78 I myThid)
79
80 C-- Make local copy of tracer array
81 DO j=1-OLy,sNy+OLy
82 DO i=1-OLx,sNx+OLx
83 localTij(i,j)=tracer(i,j,k,bi,bj)
84 ENDDO
85 ENDDO
86
87 C- Advective flux in X
88 DO j=1-Oly,sNy+Oly
89 DO i=1-Olx,sNx+Olx
90 af(i,j) = 0.
91 ENDDO
92 ENDDO
93 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
94 CALL GAD_FLUXLIMIT_ADV_X(
95 & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
96 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
97 CALL GAD_DST3_ADV_X(
98 & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
99 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
100 CALL GAD_DST3FL_ADV_X(
101 & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
102 ELSE
103 STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
104 ENDIF
105 DO j=1-Oly,sNy+Oly
106 DO i=1-Olx,sNx+Olx-1
107 localTij(i,j)=localTij(i,j)-deltaTtracer*
108 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
109 & *recip_rA(i,j,bi,bj)
110 & *( af(i+1,j)-af(i,j)
111 & -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
112 & )
113 ENDDO
114 ENDDO
115
116 #ifdef ALLOW_OBCS
117 C-- Apply open boundary conditions
118 IF (useOBCS) THEN
119 IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
120 CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
121 ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
122 CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
123 END IF
124 END IF
125 #endif /* ALLOW_OBCS */
126
127 C- Advective flux in Y
128 DO j=1-Oly,sNy+Oly
129 DO i=1-Olx,sNx+Olx
130 af(i,j) = 0.
131 ENDDO
132 ENDDO
133 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
134 CALL GAD_FLUXLIMIT_ADV_Y(
135 & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
136 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
137 CALL GAD_DST3_ADV_Y(
138 & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
139 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
140 CALL GAD_DST3FL_ADV_Y(
141 & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
142 ELSE
143 STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
144 ENDIF
145 DO j=1-Oly,sNy+Oly-1
146 DO i=1-Olx,sNx+Olx
147 localTij(i,j)=localTij(i,j)-deltaTtracer*
148 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
149 & *recip_rA(i,j,bi,bj)
150 & *( af(i,j+1)-af(i,j)
151 & -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
152 & )
153 ENDDO
154 ENDDO
155 #ifdef ALLOW_OBCS
156 C-- Apply open boundary conditions
157 IF (useOBCS) THEN
158 IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
159 CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
160 ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
161 CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
162 END IF
163 END IF
164 #endif /* ALLOW_OBCS */
165 DO j=1-Oly,sNy+Oly-1
166 DO i=1-Olx,sNx+Olx
167 localTijk(i,j,k)=localTij(i,j)
168 ENDDO
169 ENDDO
170
171
172 C-- End of K loop for horizontal fluxes
173 ENDDO
174
175 C-- Start of k loop for vertical flux
176 DO k=Nr,1,-1
177
178 C-- kup Cycles through 1,2 to point to w-layer above
179 C-- kDown Cycles through 2,1 to point to w-layer below
180 kup = 1+MOD(k+1,2)
181 kDown= 1+MOD(k,2)
182
183 C-- Get temporary terms used by tendency routines
184 CALL CALC_COMMON_FACTORS (
185 I bi,bj,iMin,iMax,jMin,jMax,k,
186 O xA,yA,uTrans,vTrans,rTrans,maskUp,
187 I myThid)
188
189 C- Advective flux in R
190 DO j=1-Oly,sNy+Oly
191 DO i=1-Olx,sNx+Olx
192 af(i,j) = 0.
193 ENDDO
194 ENDDO
195
196 C Note: wVel needs to be masked
197 IF (K.GE.2) THEN
198 C- Compute vertical advective flux in the interior:
199 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
200 CALL GAD_FLUXLIMIT_ADV_R(
201 & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
202 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
203 c CALL GAD_DST3_ADV_R(
204 c & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
205 STOP 'GAD_ADVECTION: adv. scheme not avail. yet'
206 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
207 c CALL GAD_DST3FL_ADV_R(
208 c & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
209 STOP 'GAD_ADVECTION: adv. scheme not avail. yet'
210 ELSE
211 STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
212 ENDIF
213 C- Surface "correction" term at k>1 :
214 DO j=1-Oly,sNy+Oly
215 DO i=1-Olx,sNx+Olx
216 af(i,j) = af(i,j)
217 & + (maskC(i,j,k,bi,bj)-maskC(i,j,k-1,bi,bj))*
218 & rTrans(i,j)*localTijk(i,j,k)
219 ENDDO
220 ENDDO
221 ELSE
222 C- Surface "correction" term at k=1 :
223 DO j=1-Oly,sNy+Oly
224 DO i=1-Olx,sNx+Olx
225 af(i,j) = rTrans(i,j)*localTijk(i,j,k)
226 ENDDO
227 ENDDO
228 ENDIF
229 C- add the advective flux to fVerT
230 DO j=1-Oly,sNy+Oly
231 DO i=1-Olx,sNx+Olx
232 fVerT(i,j,kUp) = af(i,j)
233 ENDDO
234 ENDDO
235
236 C-- Divergence of fluxes
237 kp1=min(Nr,k+1)
238 kp1Msk=1.
239 if (k.EQ.Nr) kp1Msk=0.
240 DO j=1-Oly,sNy+Oly
241 DO i=1-Olx,sNx+Olx
242 localTij(i,j)=localTijk(i,j,k)-deltaTtracer*
243 & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
244 & *recip_rA(i,j,bi,bj)
245 & *( fVerT(i,j,kUp)-fVerT(i,j,kDown)
246 & -tracer(i,j,k,bi,bj)*rA(i,j,bi,bj)*
247 & (wVel(i,j,k,bi,bj)-kp1Msk*wVel(i,j,kp1,bi,bj))
248 & )*rkFac
249 gTracer(i,j,k,bi,bj)=
250 & (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer
251 ENDDO
252 ENDDO
253
254 C-- End of K loop for vertical flux
255 ENDDO
256
257 RETURN
258 END

  ViewVC Help
Powered by ViewVC 1.1.22