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

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

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


Revision 1.15 - (show annotations) (download)
Thu Dec 1 14:20:25 2011 UTC (12 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63g
Changes since 1.14: +146 -68 lines
- fix implicit vertical advection conservation with AB and/or NonLin-FreeSurf
  (remove Tr*d/dz(w) in gad_implicit_r.F and add it in gad_calc_rhs.F)
- add argument recip_hFac (+ also to all GAD_*_IMPL_R S/R) and use it
  in place of recip_hFacC (to fix NonLin FreeSurf implicit vertical scheme)
- fill diagnostics of vertical advective fluxes (computed from tendency)
  when using implicit vert. advection.

1 C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_implicit_r.F,v 1.14 2009/06/26 23:10:09 jahn Exp $
2 C $Name: $
3
4 #include "GAD_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: GAD_IMPLICIT_R
8 C !INTERFACE:
9 SUBROUTINE GAD_IMPLICIT_R(
10 I implicitAdvection, advectionScheme, tracerIdentity,
11 I deltaTLev,
12 I kappaRX, recip_hFac, wVel, tracer,
13 U gTracer,
14 I bi, bj, myTime, myIter, myThid )
15 C !DESCRIPTION:
16 C Solve implicitly vertical advection and diffusion for one tracer.
17
18 C !USES:
19 IMPLICIT NONE
20 C == Global data ==
21 #include "SIZE.h"
22 #include "EEPARAMS.h"
23 #include "PARAMS.h"
24 #include "GRID.h"
25 #include "SURFACE.h"
26 #include "GAD.h"
27
28 C !INPUT/OUTPUT PARAMETERS:
29 C == Routine Arguments ==
30 C implicitAdvection :: if True, treat vertical advection implicitly
31 C advectionScheme :: advection scheme to use
32 C tracerIdentity :: Identifier for the tracer
33 C kappaRX :: 3-D array for vertical diffusion coefficient
34 C recip_hFac :: inverse of cell open-depth factor
35 C wVel :: vertical component of the velcity field
36 C tracer :: tracer field at current time step
37 C gTracer :: future tracer field
38 C bi,bj :: tile indices
39 C myTime :: current time
40 C myIter :: current iteration number
41 C myThid :: thread number
42 LOGICAL implicitAdvection
43 INTEGER advectionScheme
44 INTEGER tracerIdentity
45 _RL deltaTLev(Nr)
46 _RL kappaRX (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
47 _RS recip_hFac(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
48 _RL wVel (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
49 _RL tracer (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
50 _RL gTracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
51 INTEGER bi, bj
52 _RL myTime
53 INTEGER myIter, myThid
54
55 #ifdef ALLOW_DIAGNOSTICS
56 C !FUNCTIONS:
57 CHARACTER*4 GAD_DIAG_SUFX
58 EXTERNAL GAD_DIAG_SUFX
59 LOGICAL DIAGNOSTICS_IS_ON
60 EXTERNAL DIAGNOSTICS_IS_ON
61 #endif
62
63 C !LOCAL VARIABLES:
64 C == Local variables ==
65 C iMin,iMax,jMin,jMax :: computational domain
66 C i,j,k :: loop indices
67 C a5d :: 2nd lower diagonal of the pentadiagonal matrix
68 C b5d :: 1rst lower diagonal of the pentadiagonal matrix
69 C c5d :: main diagonal of the pentadiagonal matrix
70 C d5d :: 1rst upper diagonal of the pentadiagonal matrix
71 C e5d :: 2nd upper diagonal of the pentadiagonal matrix
72 C rTrans :: vertical volume transport at interface k
73 C localTijk :: local copy of tracer (for Non-Lin Adv.Scheme)
74 C diagonalNumber :: number of non-zero diagonals in the matrix
75 C errCode :: > 0 if singular matrix
76 INTEGER iMin,iMax,jMin,jMax
77 PARAMETER( iMin = 1, iMax = sNx )
78 PARAMETER( jMin = 1, jMax = sNy )
79 INTEGER i,j,k
80 INTEGER diagonalNumber, errCode
81 _RL a5d(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
82 _RL b5d(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
83 _RL c5d(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
84 _RL d5d(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
85 _RL e5d(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
86 _RL wFld (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
87 _RL rTrans (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
88 _RL localTijk(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
89 #ifdef ALLOW_DIAGNOSTICS
90 CHARACTER*8 diagName
91 CHARACTER*4 diagSufx
92 LOGICAL diagDif, diagAdv
93 INTEGER km1, km2, kp1, kp2
94 _RL df (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
95 _RL af (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
96 _RL div(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
97 #endif
98 CEOP
99
100 C-- no need to solve anything with only 1 level:
101 IF (Nr.GT.1) THEN
102
103 C-- Initialise
104 DO k=1,Nr
105 DO j=1-Oly,sNy+Oly
106 DO i=1-Olx,sNx+Olx
107 a5d(i,j,k) = 0. _d 0
108 b5d(i,j,k) = 0. _d 0
109 c5d(i,j,k) = 1. _d 0
110 d5d(i,j,k) = 0. _d 0
111 e5d(i,j,k) = 0. _d 0
112 ENDDO
113 ENDDO
114 ENDDO
115 diagonalNumber = 1
116
117 C-- Non-Linear Advection scheme: keep a local copy of tracer field
118 IF ( advectionScheme.EQ.ENUM_FLUX_LIMIT .OR.
119 & advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
120 IF ( multiDimAdvection ) THEN
121 DO k=1,Nr
122 DO j=1-Oly,sNy+Oly
123 DO i=1-Olx,sNx+Olx
124 localTijk(i,j,k) = gTracer(i,j,k,bi,bj)
125 ENDDO
126 ENDDO
127 ENDDO
128 ELSE
129 DO k=1,Nr
130 DO j=1-Oly,sNy+Oly
131 DO i=1-Olx,sNx+Olx
132 localTijk(i,j,k) = tracer(i,j,k,bi,bj)
133 ENDDO
134 ENDDO
135 ENDDO
136 ENDIF
137 ENDIF
138
139 IF (implicitDiffusion) THEN
140 C-- set the tri-diagonal matrix to solve the implicit diffusion problem
141 diagonalNumber = 3
142 C- 1rst lower diagonal :
143 DO k=2,Nr
144 DO j=jMin,jMax
145 DO i=iMin,iMax
146 b5d(i,j,k) = -deltaTLev(k)*maskC(i,j,k-1,bi,bj)
147 & *recip_hFac(i,j,k)*recip_drF(k)
148 & *kappaRX(i,j, k )*recip_drC( k )
149 ENDDO
150 ENDDO
151 ENDDO
152 C- 1rst upper diagonal :
153 DO k=1,Nr-1
154 DO j=jMin,jMax
155 DO i=iMin,iMax
156 d5d(i,j,k) = -deltaTLev(k)*maskC(i,j,k+1,bi,bj)
157 & *recip_hFac(i,j,k)*recip_drF(k)
158 & *KappaRX(i,j,k+1)*recip_drC(k+1)
159 ENDDO
160 ENDDO
161 ENDDO
162 C- Main diagonal :
163 DO k=1,Nr
164 DO j=jMin,jMax
165 DO i=iMin,iMax
166 c5d(i,j,k) = 1. _d 0 - b5d(i,j,k) - d5d(i,j,k)
167 ENDDO
168 ENDDO
169 ENDDO
170
171 C-- end if implicitDiffusion
172 ENDIF
173
174 IF (implicitAdvection) THEN
175
176 DO k=Nr,1,-1
177
178 C-- Compute transport
179 IF (k.EQ.1) THEN
180 DO j=1-Oly,sNy+Oly
181 DO i=1-Olx,sNx+Olx
182 wFld(i,j) = 0. _d 0
183 rTrans(i,j) = 0. _d 0
184 ENDDO
185 ENDDO
186 ELSE
187 DO j=1-Oly,sNy+Oly
188 DO i=1-Olx,sNx+Olx
189 wFld(i,j) = wVel(i,j,k,bi,bj)
190 rTrans(i,j) = wFld(i,j)*rA(i,j,bi,bj)*maskC(i,j,k-1,bi,bj)
191 ENDDO
192 ENDDO
193 #ifdef ALLOW_GMREDI
194 C-- Residual transp = Bolus transp + Eulerian transp
195 IF (useGMRedi)
196 & CALL GMREDI_CALC_WFLOW(
197 U wFld, rTrans,
198 I k, bi, bj, myThid )
199 #endif /* ALLOW_GMREDI */
200 ENDIF
201
202 #ifdef ALLOW_AIM
203 C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr
204 IF ( k.GE.2 .AND.
205 & (.NOT.useAIM .OR.tracerIdentity.NE.GAD_SALINITY .OR.k.LT.Nr)
206 & ) THEN
207 #else
208 IF ( k.GE.2 ) THEN
209 #endif
210
211 IF ( advectionScheme.EQ.ENUM_CENTERED_2ND ) THEN
212 diagonalNumber = 3
213 CALL GAD_C2_IMPL_R( bi,bj,k, iMin,iMax,jMin,jMax,
214 I deltaTLev, rTrans, recip_hFac,
215 U b5d, c5d, d5d,
216 I myThid )
217 ELSEIF ( advectionScheme.EQ.ENUM_UPWIND_1RST
218 & .OR. advectionScheme.EQ.ENUM_DST2 ) THEN
219 diagonalNumber = 3
220 CALL GAD_DST2U1_IMPL_R( bi,bj,k, iMin,iMax,jMin,jMax,
221 I advectionScheme, deltaTLev,
222 I rTrans, recip_hFac,
223 U b5d, c5d, d5d,
224 I myThid )
225 ELSEIF ( advectionScheme.EQ.ENUM_FLUX_LIMIT ) THEN
226 diagonalNumber = 3
227 CALL GAD_FLUXLIMIT_IMPL_R( bi,bj,k, iMin,iMax,jMin,jMax,
228 I deltaTLev, rTrans, recip_hFac, localTijk,
229 U b5d, c5d, d5d,
230 I myThid )
231 ELSEIF ( advectionScheme.EQ.ENUM_UPWIND_3RD
232 & .OR. advectionScheme.EQ.ENUM_CENTERED_4TH
233 & .OR. advectionScheme.EQ.ENUM_DST3 ) THEN
234 diagonalNumber = 5
235 CALL GAD_U3C4_IMPL_R( bi,bj,k, iMin,iMax,jMin,jMax,
236 I advectionScheme, deltaTLev,
237 I rTrans, recip_hFac,
238 U a5d, b5d, c5d, d5d, e5d,
239 I myThid )
240 ELSEIF ( advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
241 diagonalNumber = 5
242 CALL GAD_DST3FL_IMPL_R( bi,bj,k, iMin,iMax,jMin,jMax,
243 I deltaTLev, rTrans, recip_hFac, localTijk,
244 U a5d, b5d, c5d, d5d, e5d,
245 I myThid )
246 ELSE
247 STOP 'GAD_IMPLICIT_R: Adv.Scheme in Impl form not yet coded'
248 ENDIF
249
250 ENDIF
251
252 C-- end k loop
253 ENDDO
254
255 C-- end if implicitAdvection
256 ENDIF
257
258 IF ( diagonalNumber .EQ. 3 ) THEN
259 C-- Solve tri-diagonal system :
260 CALL SOLVE_TRIDIAGONAL( iMin,iMax, jMin,jMax,
261 I b5d, c5d, d5d,
262 U gTracer,
263 O errCode,
264 I bi, bj, myThid )
265 IF (errCode.GE.1) THEN
266 STOP 'GAD_IMPLICIT_R: error when solving 3-Diag problem'
267 ENDIF
268 ELSEIF ( diagonalNumber .EQ. 5 ) THEN
269 C-- Solve penta-diagonal system :
270 CALL SOLVE_PENTADIAGONAL( iMin,iMax, jMin,jMax,
271 I a5d, b5d, c5d, d5d, e5d,
272 U gTracer,
273 O errCode,
274 I bi, bj, myThid )
275 IF (errCode.GE.1) THEN
276 STOP 'GAD_IMPLICIT_R: error when solving 5-Diag problem'
277 ENDIF
278 ELSEIF ( diagonalNumber .NE. 1 ) THEN
279 STOP 'GAD_IMPLICIT_R: no solver available'
280 ENDIF
281
282 #ifdef ALLOW_DIAGNOSTICS
283 C-- Set diagnostic suffix for the current tracer
284 IF ( useDiagnostics ) THEN
285 diagSufx = GAD_DIAG_SUFX( tracerIdentity, myThid )
286 diagName = 'DFrI'//diagSufx
287 diagDif = implicitDiffusion
288 IF ( diagDif ) diagDif = DIAGNOSTICS_IS_ON(diagName,myThid)
289 diagName = 'ADVr'//diagSufx
290 diagAdv = implicitAdvection
291 IF ( diagAdv ) diagAdv = DIAGNOSTICS_IS_ON(diagName,myThid)
292
293 IF ( diagDif .OR. diagAdv ) THEN
294 DO j=1-OLy,sNy+OLy
295 DO i=1-OLx,sNx+OLx
296 af(i,j) = 0. _d 0
297 ENDDO
298 ENDDO
299 DO k= Nr,1,-1
300 IF ( implicitDiffusion .AND. k.GE.2 ) THEN
301 DO j=jMin,jMax
302 DO i=iMin,iMax
303 df(i,j) =
304 & -rA(i,j,bi,bj)
305 & * KappaRX(i,j,k)*recip_drC(k)*rkSign
306 & * (gTracer(i,j,k,bi,bj) - gTracer(i,j,k-1,bi,bj))
307 & * maskC(i,j,k,bi,bj)
308 & * maskC(i,j,k-1,bi,bj)
309 ENDDO
310 ENDDO
311 ELSE
312 DO j=1-OLy,sNy+OLy
313 DO i=1-OLx,sNx+OLx
314 df(i,j) = 0. _d 0
315 ENDDO
316 ENDDO
317 ENDIF
318 C- Note: Needs to explicitly increment counter (call DIAGNOSTICS_COUNT)
319 C since skipping k=1 DIAGNOSTICS_FILL call.
320 IF ( diagDif .AND. k.GE.2 ) THEN
321 diagName = 'DFrI'//diagSufx
322 CALL DIAGNOSTICS_FILL(df,diagName, k,1, 2,bi,bj, myThid)
323 IF ( k.EQ.2 ) CALL DIAGNOSTICS_COUNT(diagName,bi,bj,myThid)
324 ENDIF
325 IF ( diagAdv ) THEN
326 km1=MAX(1,k-1)
327 km2=MAX(1,k-2)
328 kp1=MIN(Nr,k+1)
329 kp2=MIN(Nr,k+2)
330 C-- Flux_divergence*deltaT = Tr^n - Tr^n+1 = [A-I](Tr^n+1)
331 C = deltaT*rkSign*[ Flx_k+1 - Flx_k ]/dz
332 DO j=jMin,jMax
333 DO i=iMin,iMax
334 div(i,j) = gTracer(i,j,k,bi,bj)*( c5d(i,j,k) - 1. _d 0 )
335 & + gTracer(i,j,km1,bi,bj)*b5d(i,j,k)
336 & + gTracer(i,j,kp1,bi,bj)*d5d(i,j,k)
337 ENDDO
338 ENDDO
339 IF ( diagonalNumber .EQ. 5 ) THEN
340 DO j=jMin,jMax
341 DO i=iMin,iMax
342 div(i,j) = div(i,j)
343 & + gTracer(i,j,km2,bi,bj)*a5d(i,j,k)
344 & + gTracer(i,j,kp2,bi,bj)*e5d(i,j,k)
345 ENDDO
346 ENDDO
347 ENDIF
348 #ifdef NONLIN_FRSURF
349 IF ( nonlinFreeSurf.GT.0 ) THEN
350 C-- use future hFac to stay consistent with solver matrix
351 IF ( select_rStar.GT.0 ) THEN
352 DO j=jMin,jMax
353 DO i=iMin,iMax
354 div(i,j) = div(i,j)*h0FacC(i,j,k,bi,bj)*drF(k)
355 & *rStarFacC(i,j,bi,bj)
356 ENDDO
357 ENDDO
358 ELSEIF ( selectSigmaCoord.NE.0 ) THEN
359 DO j=jMin,jMax
360 DO i=iMin,iMax
361 div(i,j) = div(i,j)*(
362 & _hFacC(i,j,k,bi,bj)*drF(k)
363 & + dBHybSigF(k)*dEtaHdt(i,j,bi,bj)*deltaTfreesurf
364 & )
365 ENDDO
366 ENDDO
367 ELSE
368 DO j=jMin,jMax
369 DO i=iMin,iMax
370 IF ( k.EQ.kSurfC(i,j,bi,bj) ) THEN
371 div(i,j) = div(i,j)*hFac_surfC(i,j,bi,bj)*drF(k)
372 ELSE
373 div(i,j) = div(i,j)*_hFacC(i,j,k,bi,bj)*drF(k)
374 ENDIF
375 ENDDO
376 ENDDO
377 ENDIF
378 ELSE
379 #else /* NONLIN_FRSURF */
380 IF ( .TRUE. ) THEN
381 #endif /* NONLIN_FRSURF */
382 C-- use current hFac (consistent with solver matrix)
383 DO j=jMin,jMax
384 DO i=iMin,iMax
385 div(i,j) = div(i,j)*_hFacC(i,j,k,bi,bj)*drF(k)
386 ENDDO
387 ENDDO
388 ENDIF
389 DO j=jMin,jMax
390 DO i=iMin,iMax
391 af(i,j) = af(i,j)
392 & - rkSign*div(i,j)*rA(i,j,bi,bj)/deltaTLev(k)
393 & - df(i,j)
394 ENDDO
395 ENDDO
396 diagName = 'ADVr'//diagSufx
397 CALL DIAGNOSTICS_FILL(af,diagName, k,1, 2,bi,bj, myThid)
398 ENDIF
399 ENDDO
400 ENDIF
401 ENDIF
402 #endif /* ALLOW_DIAGNOSTICS */
403
404 C-- end if Nr > 1
405 ENDIF
406
407 RETURN
408 END

  ViewVC Help
Powered by ViewVC 1.1.22