/[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.8 - (show annotations) (download)
Thu Dec 16 22:28:43 2004 UTC (19 years, 5 months ago) by jmc
Branch: MAIN
Changes since 1.7: +42 -1 lines
add diagnostics of advective & diffusive fluxes

1 C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_implicit_r.F,v 1.7 2004/12/04 18:50:34 jmc 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 kappaRX, wVel, tracer,
12 U gTracer,
13 I bi, bj, myTime, myIter, myThid )
14 C !DESCRIPTION:
15 C Solve implicitly vertical advection and diffusion for one tracer.
16
17 C !USES:
18 IMPLICIT NONE
19 C == Global data ==
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22 #include "PARAMS.h"
23 #include "GRID.h"
24 #include "GAD.h"
25
26 C !INPUT/OUTPUT PARAMETERS:
27 C == Routine Arguments ==
28 C implicitAdvection :: if True, treat vertical advection implicitly
29 C advectionScheme :: advection scheme to use
30 C tracerIdentity :: Identifier for the tracer
31 C kappaRX :: 3-D array for vertical diffusion coefficient
32 C wVel :: vertical component of the velcity field
33 C tracer :: tracer field at current time step
34 C gTracer :: future tracer field
35 C bi,bj :: tile indices
36 C myTime :: current time
37 C myIter :: current iteration number
38 C myThid :: thread number
39 LOGICAL implicitAdvection
40 INTEGER advectionScheme
41 INTEGER tracerIdentity
42 _RL kappaRX(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
43 _RL wVel (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
44 _RL tracer (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
45 _RL gTracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
46 INTEGER bi, bj
47 _RL myTime
48 INTEGER myIter, myThid
49
50 C !LOCAL VARIABLES:
51 C == Local variables ==
52 C iMin,iMax,jMin,jMax :: computational domain
53 C i,j,k :: loop indices
54 C a5d :: 2nd lower diagonal of the pentadiagonal matrix
55 C b5d :: 1rst lower diagonal of the pentadiagonal matrix
56 C c5d :: main diagonal of the pentadiagonal matrix
57 C d5d :: 1rst upper diagonal of the pentadiagonal matrix
58 C e5d :: 2nd upper diagonal of the pentadiagonal matrix
59 C rTrans :: vertical volume transport at inteface k
60 C rTransKp1 :: vertical volume transport at inteface k+1
61 C localTijk :: local copy of tracer (for Non-Lin Adv.Scheme)
62 C diagonalNumber :: number of non-zero diagonals in the matrix
63 C errCode :: > 0 if singular matrix
64 INTEGER iMin,iMax,jMin,jMax
65 INTEGER i,j,k
66 INTEGER diagonalNumber, errCode
67 _RL a5d(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
68 _RL b5d(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
69 _RL c5d(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
70 _RL d5d(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
71 _RL e5d(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
72 _RL rTrans(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
73 _RL rTransKp1(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
74 _RL localTijk(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
75 #ifdef ALLOW_DIAGNOSTICS
76 INTEGER kk
77 CHARACTER*8 diagName
78 CHARACTER*4 GAD_DIAG_SUFX, diagSufx
79 EXTERNAL GAD_DIAG_SUFX
80 LOGICAL DIAGNOSTICS_IS_ON
81 EXTERNAL DIAGNOSTICS_IS_ON
82 _RL df (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
83 #endif
84 CEOP
85
86 C-- no need to solve anything with only 1 level:
87 IF (Nr.GT.1) THEN
88
89 C-- Initialise
90 iMin = 1
91 jMin = 1
92 iMax = sNx
93 jMax = sNy
94 DO k=1,Nr
95 DO j=1-Oly,sNy+Oly
96 DO i=1-Olx,sNx+Olx
97 a5d(i,j,k) = 0. _d 0
98 b5d(i,j,k) = 0. _d 0
99 c5d(i,j,k) = 1. _d 0
100 d5d(i,j,k) = 0. _d 0
101 e5d(i,j,k) = 0. _d 0
102 ENDDO
103 ENDDO
104 ENDDO
105 diagonalNumber = 1
106
107 C-- Non-Linear Advection scheme: keep a local copy of tracer field
108 IF ( advectionScheme.EQ.ENUM_FLUX_LIMIT .OR.
109 & advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
110 IF ( multiDimAdvection ) THEN
111 DO k=1,Nr
112 DO j=1-Oly,sNy+Oly
113 DO i=1-Olx,sNx+Olx
114 localTijk(i,j,k) = gTracer(i,j,k,bi,bj)
115 ENDDO
116 ENDDO
117 ENDDO
118 ELSE
119 DO k=1,Nr
120 DO j=1-Oly,sNy+Oly
121 DO i=1-Olx,sNx+Olx
122 localTijk(i,j,k) = tracer(i,j,k,bi,bj)
123 ENDDO
124 ENDDO
125 ENDDO
126 ENDIF
127 ENDIF
128
129 IF (implicitDiffusion) THEN
130 C-- set the tri-diagonal matrix to solve the implicit diffusion problem
131 diagonalNumber = 3
132 C- 1rst lower diagonal :
133 DO k=2,Nr
134 DO j=jMin,jMax
135 DO i=iMin,iMax
136 b5d(i,j,k) = -dTtracerLev(k)*maskC(i,j,k-1,bi,bj)
137 & *recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
138 & *kappaRX(i,j, k )*recip_drC( k )
139 ENDDO
140 ENDDO
141 ENDDO
142 C- 1rst upper diagonal :
143 DO k=1,Nr-1
144 DO j=jMin,jMax
145 DO i=iMin,iMax
146 d5d(i,j,k) = -dTtracerLev(k)*maskC(i,j,k+1,bi,bj)
147 & *recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
148 & *KappaRX(i,j,k+1)*recip_drC(k+1)
149 ENDDO
150 ENDDO
151 ENDDO
152 C- Main diagonal :
153 DO k=1,Nr
154 DO j=jMin,jMax
155 DO i=iMin,iMax
156 c5d(i,j,k) = 1. _d 0 - b5d(i,j,k) - d5d(i,j,k)
157 ENDDO
158 ENDDO
159 ENDDO
160
161 C-- end if implicitDiffusion
162 ENDIF
163
164 IF (implicitAdvection) THEN
165
166 DO k=Nr,1,-1
167
168 C-- Compute transport
169 IF (k.EQ.Nr) THEN
170 DO j=1-Oly,sNy+Oly
171 DO i=1-Olx,sNx+Olx
172 rTransKp1(i,j) = 0.
173 ENDDO
174 ENDDO
175 ELSE
176 DO j=1-Oly,sNy+Oly
177 DO i=1-Olx,sNx+Olx
178 rTransKp1(i,j) = rTrans(i,j)
179 ENDDO
180 ENDDO
181 ENDIF
182
183 IF (k.EQ.1) THEN
184 DO j=1-Oly,sNy+Oly
185 DO i=1-Olx,sNx+Olx
186 rTrans(i,j) = 0.
187 ENDDO
188 ENDDO
189 ELSE
190 DO j=1-Oly,sNy+Oly
191 DO i=1-Olx,sNx+Olx
192 rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
193 & *maskC(i,j,k-1,bi,bj)
194 ENDDO
195 ENDDO
196 #ifdef ALLOW_GMREDI
197 C-- Residual transp = Bolus transp + Eulerian transp
198 IF (useGMRedi)
199 & CALL GMREDI_CALC_WFLOW(
200 & rTrans, bi, bj, k, myThid)
201 #endif /* ALLOW_GMREDI */
202 ENDIF
203 DO j=jMin,jMax
204 DO i=iMin,iMax
205 c localTijk(i,j,k) = gTracer(i,j,k,bi,bj)
206 gTracer(i,j,k,bi,bj) = gTracer(i,j,k,bi,bj)
207 & + dTtracerLev(1)*recip_rA(i,j,bi,bj)
208 & *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
209 & *tracer(i,j,k,bi,bj)*(rTrans(i,j)-rTransKp1(i,j))*rkFac
210 ENDDO
211 ENDDO
212
213 #ifdef ALLOW_AIM
214 C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr
215 IF ( K.GE.2 .AND.
216 & (.NOT.useAIM .OR.tracerIdentity.NE.GAD_SALINITY .OR.K.LT.Nr)
217 & ) THEN
218 #else
219 IF ( K.GE.2 ) THEN
220 #endif
221
222 IF ( advectionScheme.EQ.ENUM_CENTERED_2ND ) THEN
223 diagonalNumber = 3
224 CALL GAD_C2_IMPL_R( bi,bj,k, iMin,iMax,jMin,jMax,
225 I dTtracerLev, rTrans,
226 U b5d, c5d, d5d,
227 I myThid)
228 ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
229 diagonalNumber = 3
230 CALL GAD_FLUXLIMIT_IMPL_R( bi,bj,k, iMin,iMax,jMin,jMax,
231 I dTtracerLev, rTrans, localTijk,
232 U b5d, c5d, d5d,
233 I myThid)
234 ELSEIF (advectionScheme.EQ.ENUM_UPWIND_3RD .OR.
235 & advectionScheme.EQ.ENUM_CENTERED_4TH) THEN
236 diagonalNumber = 5
237 CALL GAD_U3C4_IMPL_R( bi,bj,k, iMin,iMax,jMin,jMax,
238 I advectionScheme, dTtracerLev, rTrans,
239 U a5d, b5d, c5d, d5d, e5d,
240 I myThid)
241 ELSE
242 STOP 'GAD_IMPLICIT_R: Adv.Scheme in Impl form not yet coded'
243 ENDIF
244
245 ENDIF
246
247 C-- end k loop
248 ENDDO
249
250 C-- end if implicitAdvection
251 ENDIF
252
253 IF ( diagonalNumber .EQ. 3 ) THEN
254 C-- Solve tri-diagonal system :
255 CALL SOLVE_TRIDIAGONAL( iMin,iMax, jMin,jMax,
256 I b5d, c5d, d5d,
257 U gTracer,
258 O errCode,
259 I bi, bj, myThid )
260 IF (errCode.GE.1) THEN
261 STOP 'GAD_IMPLICIT_R: error when solving 3-Diag problem'
262 ENDIF
263 ELSEIF ( diagonalNumber .EQ. 5 ) THEN
264 C-- Solve penta-diagonal system :
265 CALL SOLVE_PENTADIAGONAL( iMin,iMax, jMin,jMax,
266 I a5d, b5d, c5d, d5d, e5d,
267 U gTracer,
268 O errCode,
269 I bi, bj, myThid )
270 IF (errCode.GE.1) THEN
271 STOP 'GAD_IMPLICIT_R: error when solving 5-Diag problem'
272 ENDIF
273 ELSEIF ( diagonalNumber .NE. 1 ) THEN
274 STOP 'GAD_IMPLICIT_R: no solver available'
275 ENDIF
276
277 #ifdef ALLOW_DIAGNOSTICS
278 C-- Set diagnostic suffix for the current tracer
279 IF ( useDiagnostics .AND. implicitDiffusion ) THEN
280 diagSufx = GAD_DIAG_SUFX( tracerIdentity, myThid )
281 diagName = 'DFrI'//diagSufx
282 IF ( DIAGNOSTICS_IS_ON(diagName,myThid) ) THEN
283 DO k= 1,Nr
284 IF ( k.EQ.1 ) THEN
285 C- Note: Needs to call DIAGNOSTICS_FILL at level k=1 even if array == 0
286 C otherwise counter is not incremented !!
287 DO j=1-OLy,sNy+OLy
288 DO i=1-OLx,sNx+OLx
289 df(i,j) = 0. _d 0
290 ENDDO
291 ENDDO
292 ELSE
293 DO j=1,sNy
294 DO i=1,sNx
295 df(i,j) =
296 & rA(i,j,bi,bj)
297 & * KappaRX(i,j,k)*recip_drC(k)
298 & * (gTracer(i,j,k,bi,bj) - gTracer(i,j,k-1,bi,bj))
299 ENDDO
300 ENDDO
301 ENDIF
302 kk = -k
303 CALL DIAGNOSTICS_FILL(df,diagName, kk,1, 2,bi,bj, myThid)
304 ENDDO
305 ENDIF
306 ENDIF
307 #endif /* ALLOW_DIAGNOSTICS */
308
309 C-- end if Nr > 1
310 ENDIF
311
312 RETURN
313 END

  ViewVC Help
Powered by ViewVC 1.1.22