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

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

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


Revision 1.21 - (show annotations) (download)
Wed Sep 24 04:52:38 2003 UTC (20 years, 8 months ago) by dimitri
Branch: MAIN
Changes since 1.20: +2 -2 lines
o Mods and bug fixes to pkg/cal, pkg/exf, etc. needed for computation
  of tracer Green's fucntions for ocean inversion project.

1 C $Header: /usr/local/gcmpack/MITgcm/pkg/generic_advdiff/gad_calc_rhs.F,v 1.20 2003/09/22 22:13:11 jmc Exp $
2 C $Name: $
3
4 #include "GAD_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: GAD_CALC_RHS
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE GAD_CALC_RHS(
11 I bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
12 I xA,yA,uTrans,vTrans,rTrans,maskUp,
13 I diffKh, diffK4, KappaRT, Tracer,
14 I tracerIdentity, advectionScheme, calcAdvection,
15 U fVerT, gTracer,
16 I myThid )
17
18 C !DESCRIPTION:
19 C Calculates the tendancy of a tracer due to advection and diffusion.
20 C It calculates the fluxes in each direction indepentently and then
21 C sets the tendancy to the divergence of these fluxes. The advective
22 C fluxes are only calculated here when using the linear advection schemes
23 C otherwise only the diffusive and parameterized fluxes are calculated.
24 C
25 C Contributions to the flux are calculated and added:
26 C \begin{equation*}
27 C {\bf F} = {\bf F}_{adv} + {\bf F}_{diff} +{\bf F}_{GM} + {\bf F}_{KPP}
28 C \end{equation*}
29 C
30 C The tendancy is the divergence of the fluxes:
31 C \begin{equation*}
32 C G_\theta = G_\theta + \nabla \cdot {\bf F}
33 C \end{equation*}
34 C
35 C The tendancy is assumed to contain data on entry.
36
37 C !USES: ===============================================================
38 IMPLICIT NONE
39 #include "SIZE.h"
40 #include "EEPARAMS.h"
41 #include "PARAMS.h"
42 #include "GRID.h"
43 #include "DYNVARS.h"
44 #include "SURFACE.h"
45 #include "GAD.h"
46 #ifdef ALLOW_PTRACERS
47 #include "PTRACERS_OPTIONS.h"
48 #include "PTRACERS.h"
49 #endif
50
51 #ifdef ALLOW_AUTODIFF_TAMC
52 #include "tamc.h"
53 #include "tamc_keys.h"
54 #endif /* ALLOW_AUTODIFF_TAMC */
55
56 C !INPUT PARAMETERS: ===================================================
57 C bi,bj :: tile indices
58 C iMin,iMax,jMin,jMax :: loop range for called routines
59 C kup :: index into 2 1/2D array, toggles between 1 and 2
60 C kdown :: index into 2 1/2D array, toggles between 2 and 1
61 C kp1 :: =k+1 for k<Nr, =Nr for k=Nr
62 C xA,yA :: areas of X and Y face of tracer cells
63 C uTrans,vTrans,rTrans :: 2-D arrays of volume transports at U,V and W points
64 C maskUp :: 2-D array for mask at W points
65 C diffKh :: horizontal diffusion coefficient
66 C diffK4 :: bi-harmonic diffusion coefficient
67 C KappaRT :: 3-D array for vertical diffusion coefficient
68 C Tracer :: tracer field
69 C tracerIdentity :: identifier for the tracer (required for KPP and GM)
70 C advectionScheme :: advection scheme to use
71 C calcAdvection :: =False if Advec terms computed with multiDim scheme
72 C myThid :: thread number
73 INTEGER bi,bj,iMin,iMax,jMin,jMax
74 INTEGER k,kUp,kDown,kM1
75 _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76 _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77 _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78 _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79 _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80 _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
81 _RL diffKh, diffK4
82 _RL KappaRT(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
83 _RL Tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
84 INTEGER tracerIdentity
85 INTEGER advectionScheme
86 LOGICAL calcAdvection
87 INTEGER myThid
88
89 C !OUTPUT PARAMETERS: ==================================================
90 C gTracer :: tendancy array
91 C fVerT :: 2 1/2D arrays for vertical advective flux
92 _RL gTracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
93 _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
94
95 C !LOCAL VARIABLES: ====================================================
96 C i,j :: loop indices
97 C df4 :: used for storing del^2 T for bi-harmonic term
98 C fZon :: zonal flux
99 C fmer :: meridional flux
100 C af :: advective flux
101 C df :: diffusive flux
102 C localT :: local copy of tracer field
103 INTEGER i,j
104 _RL df4 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
105 _RL fZon (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
106 _RL fMer (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
107 _RL af (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
108 _RL df (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
109 _RL localT(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
110 CEOP
111
112 #ifdef ALLOW_AUTODIFF_TAMC
113 C-- only the kUp part of fverT is set in this subroutine
114 C-- the kDown is still required
115 fVerT(1,1,kDown) = fVerT(1,1,kDown)
116 #endif
117
118 DO j=1-OLy,sNy+OLy
119 DO i=1-OLx,sNx+OLx
120 fZon(i,j) = 0. _d 0
121 fMer(i,j) = 0. _d 0
122 fVerT(i,j,kUp) = 0. _d 0
123 df(i,j) = 0. _d 0
124 df4(i,j) = 0. _d 0
125 localT(i,j) = 0. _d 0
126 ENDDO
127 ENDDO
128
129 C-- Make local copy of tracer array
130 DO j=1-OLy,sNy+OLy
131 DO i=1-OLx,sNx+OLx
132 localT(i,j)=tracer(i,j,k,bi,bj)
133 ENDDO
134 ENDDO
135
136 C-- Unless we have already calculated the advection terms we initialize
137 C the tendency to zero.
138 C <== now done earlier at the beginning of thermodynamics.
139 c IF (calcAdvection) THEN
140 c DO j=1-Oly,sNy+Oly
141 c DO i=1-Olx,sNx+Olx
142 c gTracer(i,j,k,bi,bj)=0. _d 0
143 c ENDDO
144 c ENDDO
145 c ENDIF
146
147 C-- Pre-calculate del^2 T if bi-harmonic coefficient is non-zero
148 IF (diffK4 .NE. 0.) THEN
149 CALL GAD_GRAD_X(bi,bj,k,xA,localT,fZon,myThid)
150 CALL GAD_GRAD_Y(bi,bj,k,yA,localT,fMer,myThid)
151 CALL GAD_DEL2(bi,bj,k,fZon,fMer,df4,myThid)
152 ENDIF
153
154 C-- Initialize net flux in X direction
155 DO j=1-Oly,sNy+Oly
156 DO i=1-Olx,sNx+Olx
157 fZon(i,j) = 0. _d 0
158 ENDDO
159 ENDDO
160
161 C- Advective flux in X
162 IF (calcAdvection) THEN
163 IF (advectionScheme.EQ.ENUM_CENTERED_2ND) THEN
164 CALL GAD_C2_ADV_X(bi,bj,k,uTrans,localT,af,myThid)
165 ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
166 CALL GAD_FLUXLIMIT_ADV_X(
167 & bi,bj,k,deltaTtracer,uTrans,uVel,localT,af,myThid)
168 ELSEIF (advectionScheme.EQ.ENUM_UPWIND_3RD ) THEN
169 CALL GAD_U3_ADV_X(bi,bj,k,uTrans,localT,af,myThid)
170 ELSEIF (advectionScheme.EQ.ENUM_CENTERED_4TH) THEN
171 CALL GAD_C4_ADV_X(bi,bj,k,uTrans,localT,af,myThid)
172 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
173 CALL GAD_DST3_ADV_X(
174 & bi,bj,k,deltaTtracer,uTrans,uVel,localT,af,myThid)
175 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
176 CALL GAD_DST3FL_ADV_X(
177 & bi,bj,k,deltaTtracer,uTrans,uVel,localT,af,myThid)
178 ELSE
179 STOP 'GAD_CALC_RHS: Bad advectionScheme (X)'
180 ENDIF
181 DO j=1-Oly,sNy+Oly
182 DO i=1-Olx,sNx+Olx
183 fZon(i,j) = fZon(i,j) + af(i,j)
184 ENDDO
185 ENDDO
186 ENDIF
187
188 C- Diffusive flux in X
189 IF (diffKh.NE.0.) THEN
190 CALL GAD_DIFF_X(bi,bj,k,xA,diffKh,localT,df,myThid)
191 ELSE
192 DO j=1-Oly,sNy+Oly
193 DO i=1-Olx,sNx+Olx
194 df(i,j) = 0. _d 0
195 ENDDO
196 ENDDO
197 ENDIF
198
199 #ifdef ALLOW_GMREDI
200 C- GM/Redi flux in X
201 IF (useGMRedi) THEN
202 C *note* should update GMREDI_XTRANSPORT to use localT and set df *aja*
203 CALL GMREDI_XTRANSPORT(
204 I iMin,iMax,jMin,jMax,bi,bj,K,
205 I xA,Tracer,tracerIdentity,
206 U df,
207 I myThid)
208 ENDIF
209 #endif
210 DO j=1-Oly,sNy+Oly
211 DO i=1-Olx,sNx+Olx
212 fZon(i,j) = fZon(i,j) + df(i,j)
213 ENDDO
214 ENDDO
215
216 C- Bi-harmonic duffusive flux in X
217 IF (diffK4 .NE. 0.) THEN
218 CALL GAD_BIHARM_X(bi,bj,k,xA,df4,diffK4,df,myThid)
219 DO j=1-Oly,sNy+Oly
220 DO i=1-Olx,sNx+Olx
221 fZon(i,j) = fZon(i,j) + df(i,j)
222 ENDDO
223 ENDDO
224 ENDIF
225
226 C-- Initialize net flux in Y direction
227 DO j=1-Oly,sNy+Oly
228 DO i=1-Olx,sNx+Olx
229 fMer(i,j) = 0. _d 0
230 ENDDO
231 ENDDO
232
233 C- Advective flux in Y
234 IF (calcAdvection) THEN
235 IF (advectionScheme.EQ.ENUM_CENTERED_2ND) THEN
236 CALL GAD_C2_ADV_Y(bi,bj,k,vTrans,localT,af,myThid)
237 ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
238 CALL GAD_FLUXLIMIT_ADV_Y(
239 & bi,bj,k,deltaTtracer,vTrans,vVel,localT,af,myThid)
240 ELSEIF (advectionScheme.EQ.ENUM_UPWIND_3RD ) THEN
241 CALL GAD_U3_ADV_Y(bi,bj,k,vTrans,localT,af,myThid)
242 ELSEIF (advectionScheme.EQ.ENUM_CENTERED_4TH) THEN
243 CALL GAD_C4_ADV_Y(bi,bj,k,vTrans,localT,af,myThid)
244 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
245 CALL GAD_DST3_ADV_Y(
246 & bi,bj,k,deltaTtracer,vTrans,vVel,localT,af,myThid)
247 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
248 CALL GAD_DST3FL_ADV_Y(
249 & bi,bj,k,deltaTtracer,vTrans,vVel,localT,af,myThid)
250 ELSE
251 STOP 'GAD_CALC_RHS: Bad advectionScheme (Y)'
252 ENDIF
253 DO j=1-Oly,sNy+Oly
254 DO i=1-Olx,sNx+Olx
255 fMer(i,j) = fMer(i,j) + af(i,j)
256 ENDDO
257 ENDDO
258 ENDIF
259
260 C- Diffusive flux in Y
261 IF (diffKh.NE.0.) THEN
262 CALL GAD_DIFF_Y(bi,bj,k,yA,diffKh,localT,df,myThid)
263 ELSE
264 DO j=1-Oly,sNy+Oly
265 DO i=1-Olx,sNx+Olx
266 df(i,j) = 0. _d 0
267 ENDDO
268 ENDDO
269 ENDIF
270
271 #ifdef ALLOW_GMREDI
272 C- GM/Redi flux in Y
273 IF (useGMRedi) THEN
274 C *note* should update GMREDI_YTRANSPORT to use localT and set df *aja*
275 CALL GMREDI_YTRANSPORT(
276 I iMin,iMax,jMin,jMax,bi,bj,K,
277 I yA,Tracer,tracerIdentity,
278 U df,
279 I myThid)
280 ENDIF
281 #endif
282 DO j=1-Oly,sNy+Oly
283 DO i=1-Olx,sNx+Olx
284 fMer(i,j) = fMer(i,j) + df(i,j)
285 ENDDO
286 ENDDO
287
288 C- Bi-harmonic flux in Y
289 IF (diffK4 .NE. 0.) THEN
290 CALL GAD_BIHARM_Y(bi,bj,k,yA,df4,diffK4,df,myThid)
291 DO j=1-Oly,sNy+Oly
292 DO i=1-Olx,sNx+Olx
293 fMer(i,j) = fMer(i,j) + df(i,j)
294 ENDDO
295 ENDDO
296 ENDIF
297
298 #ifdef NONLIN_FRSURF
299 C-- Compute vertical flux fVerT(kDown) at interface k+1 (between k & k+1):
300 IF ( calcAdvection .AND. K.EQ.Nr .AND.
301 & useRealFreshWaterFlux .AND.
302 & buoyancyRelation .EQ. 'OCEANICP' ) THEN
303 DO j=1-Oly,sNy+Oly
304 DO i=1-Olx,sNx+Olx
305 fVerT(i,j,kDown) = convertEmP2rUnit*PmEpR(i,j,bi,bj)
306 & *rA(i,j,bi,bj)*maskC(i,j,k,bi,bj)*Tracer(i,j,k,bi,bj)
307 ENDDO
308 ENDDO
309 ENDIF
310 #endif /* NONLIN_FRSURF */
311
312 C-- Compute vertical flux fVerT(kUp) at interface k (between k-1 & k):
313 C- Advective flux in R
314 IF (calcAdvection) THEN
315 C Note: wVel needs to be masked
316 IF (K.GE.2) THEN
317 C- Compute vertical advective flux in the interior:
318 IF (advectionScheme.EQ.ENUM_CENTERED_2ND) THEN
319 CALL GAD_C2_ADV_R(bi,bj,k,rTrans,tracer,af,myThid)
320 ELSEIF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
321 CALL GAD_FLUXLIMIT_ADV_R(
322 & bi,bj,k,deltaTtracer,rTrans,wVel,tracer,af,myThid)
323 ELSEIF (advectionScheme.EQ.ENUM_UPWIND_3RD ) THEN
324 CALL GAD_U3_ADV_R(bi,bj,k,rTrans,tracer,af,myThid)
325 ELSEIF (advectionScheme.EQ.ENUM_CENTERED_4TH) THEN
326 CALL GAD_C4_ADV_R(bi,bj,k,rTrans,tracer,af,myThid)
327 ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
328 CALL GAD_DST3_ADV_R(
329 & bi,bj,k,deltaTtracer,rTrans,wVel,tracer,af,myThid)
330 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
331 CALL GAD_DST3FL_ADV_R(
332 & bi,bj,k,deltaTtracer,rTrans,wVel,tracer,af,myThid)
333 ELSE
334 STOP 'GAD_CALC_RHS: Bad advectionScheme (R)'
335 ENDIF
336 C- Surface "correction" term at k>1 :
337 DO j=1-Oly,sNy+Oly
338 DO i=1-Olx,sNx+Olx
339 af(i,j) = af(i,j)
340 & + (maskC(i,j,k,bi,bj)-maskC(i,j,k-1,bi,bj))*
341 & rTrans(i,j)*Tracer(i,j,k,bi,bj)
342 ENDDO
343 ENDDO
344 ELSE
345 C- Surface "correction" term at k=1 :
346 DO j=1-Oly,sNy+Oly
347 DO i=1-Olx,sNx+Olx
348 af(i,j) = rTrans(i,j)*Tracer(i,j,k,bi,bj)
349 ENDDO
350 ENDDO
351 ENDIF
352 C- add the advective flux to fVerT
353 DO j=1-Oly,sNy+Oly
354 DO i=1-Olx,sNx+Olx
355 fVerT(i,j,kUp) = fVerT(i,j,kUp) + af(i,j)
356 ENDDO
357 ENDDO
358 ENDIF
359
360 C- Diffusive flux in R
361 C Note: For K=1 then KM1=1 and this gives a dT/dr = 0 upper
362 C boundary condition.
363 IF (implicitDiffusion) THEN
364 DO j=1-Oly,sNy+Oly
365 DO i=1-Olx,sNx+Olx
366 df(i,j) = 0. _d 0
367 ENDDO
368 ENDDO
369 ELSE
370 CALL GAD_DIFF_R(bi,bj,k,KappaRT,tracer,df,myThid)
371 ENDIF
372
373 #ifdef ALLOW_GMREDI
374 C- GM/Redi flux in R
375 IF (useGMRedi) THEN
376 C *note* should update GMREDI_RTRANSPORT to set df *aja*
377 CALL GMREDI_RTRANSPORT(
378 I iMin,iMax,jMin,jMax,bi,bj,K,
379 I Tracer,tracerIdentity,
380 U df,
381 I myThid)
382 ENDIF
383 #endif
384
385 DO j=1-Oly,sNy+Oly
386 DO i=1-Olx,sNx+Olx
387 fVerT(i,j,kUp) = fVerT(i,j,kUp) + df(i,j)*maskUp(i,j)
388 ENDDO
389 ENDDO
390
391 #ifdef ALLOW_KPP
392 C- Add non local KPP transport term (ghat) to diffusive T flux.
393 IF (useKPP) THEN
394 DO j=1-Oly,sNy+Oly
395 DO i=1-Olx,sNx+Olx
396 df(i,j) = 0. _d 0
397 ENDDO
398 ENDDO
399 IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
400 C *note* should update KPP_TRANSPORT_T to set df *aja*
401 CALL KPP_TRANSPORT_T(
402 I iMin,iMax,jMin,jMax,bi,bj,k,km1,
403 I KappaRT,
404 U df )
405 ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
406 CALL KPP_TRANSPORT_S(
407 I iMin,iMax,jMin,jMax,bi,bj,k,km1,
408 I KappaRT,
409 U df )
410 #ifdef ALLOW_PTRACERS
411 ELSEIF (tracerIdentity .GE. GAD_TR1 .AND.
412 & tracerIdentity .LE. (GAD_TR1+PTRACERS_numInUse-1)) THEN
413 CALL KPP_TRANSPORT_PTR(
414 I iMin,iMax,jMin,jMax,bi,bj,k,km1,
415 I tracerIdentity-GAD_TR1+1,KappaRT,
416 U df )
417 #endif
418 ELSE
419 PRINT*,'invalid tracer indentity: ', tracerIdentity
420 STOP 'GAD_CALC_RHS: Ooops'
421 ENDIF
422 DO j=1-Oly,sNy+Oly
423 DO i=1-Olx,sNx+Olx
424 fVerT(i,j,kUp) = fVerT(i,j,kUp) + df(i,j)*maskUp(i,j)
425 ENDDO
426 ENDDO
427 ENDIF
428 #endif
429
430 C-- Divergence of fluxes
431 DO j=1-Oly,sNy+Oly-1
432 DO i=1-Olx,sNx+Olx-1
433 gTracer(i,j,k,bi,bj)=gTracer(i,j,k,bi,bj)
434 & -_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
435 & *recip_rA(i,j,bi,bj)
436 & *(
437 & +( fZon(i+1,j)-fZon(i,j) )
438 & +( fMer(i,j+1)-fMer(i,j) )
439 & +( fVerT(i,j,kUp)-fVerT(i,j,kDown) )*rkFac
440 & )
441 ENDDO
442 ENDDO
443
444 #ifdef NONLIN_FRSURF
445 C-- account for 3.D divergence of the flow in rStar coordinate:
446 IF (calcAdvection .AND. select_rStar.GT.0) THEN
447 DO j=1-Oly,sNy+Oly-1
448 DO i=1-Olx,sNx+Olx-1
449 gTracer(i,j,k,bi,bj) = gTracer(i,j,k,bi,bj)
450 & - (rStarExpC(i,j,bi,bj) - 1. _d 0)/deltaTfreesurf
451 & *tracer(i,j,k,bi,bj)*maskC(i,j,k,bi,bj)
452 ENDDO
453 ENDDO
454 ENDIF
455 IF (calcAdvection .AND. select_rStar.LT.0) THEN
456 DO j=1-Oly,sNy+Oly-1
457 DO i=1-Olx,sNx+Olx-1
458 gTracer(i,j,k,bi,bj) = gTracer(i,j,k,bi,bj)
459 & - rStarDhCDt(i,j,bi,bj)
460 & *tracer(i,j,k,bi,bj)*maskC(i,j,k,bi,bj)
461 ENDDO
462 ENDDO
463 ENDIF
464 #endif /* NONLIN_FRSURF */
465
466
467 RETURN
468 END

  ViewVC Help
Powered by ViewVC 1.1.22