/[MITgcm]/MITgcm/pkg/mom_fluxform/mom_fluxform.F
ViewVC logotype

Contents of /MITgcm/pkg/mom_fluxform/mom_fluxform.F

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


Revision 1.46 - (show annotations) (download)
Sun Jul 28 21:04:25 2013 UTC (10 years, 9 months ago) by jmc
Branch: MAIN
Changes since 1.45: +23 -21 lines
store in common block (in MOM_VISC.h): useHarmonicVisc, useBiharmonicVisc
 & useVariableVisc, (previously local flag harmonic, biharmonic
 & useVariableViscosity, were set for each k in mom_common/mom_calc_visc.F
and pass as argument back to S/R MOM_FLUXFORM & MOM_VECINV)

1 C $Header: /u/gcmpack/MITgcm/pkg/mom_fluxform/mom_fluxform.F,v 1.45 2012/10/01 15:46:33 heimbach Exp $
2 C $Name: $
3
4 CBOI
5 C !TITLE: pkg/mom\_advdiff
6 C !AUTHORS: adcroft@mit.edu
7 C !INTRODUCTION: Flux-form Momentum Equations Package
8 C
9 C Package "mom\_fluxform" provides methods for calculating explicit terms
10 C in the momentum equation cast in flux-form:
11 C \begin{eqnarray*}
12 C G^u & = & -\frac{1}{\rho} \partial_x \phi_h
13 C -\nabla \cdot {\bf v} u
14 C -fv
15 C +\frac{1}{\rho} \nabla \cdot {\bf \tau}^x
16 C + \mbox{metrics}
17 C \\
18 C G^v & = & -\frac{1}{\rho} \partial_y \phi_h
19 C -\nabla \cdot {\bf v} v
20 C +fu
21 C +\frac{1}{\rho} \nabla \cdot {\bf \tau}^y
22 C + \mbox{metrics}
23 C \end{eqnarray*}
24 C where ${\bf v}=(u,v,w)$ and $\tau$, the stress tensor, includes surface
25 C stresses as well as internal viscous stresses.
26 CEOI
27
28 #include "MOM_FLUXFORM_OPTIONS.h"
29 #ifdef ALLOW_MOM_COMMON
30 # include "MOM_COMMON_OPTIONS.h"
31 #endif
32
33 CBOP
34 C !ROUTINE: MOM_FLUXFORM
35
36 C !INTERFACE: ==========================================================
37 SUBROUTINE MOM_FLUXFORM(
38 I bi,bj,k,iMin,iMax,jMin,jMax,
39 I KappaRU, KappaRV,
40 U fVerUkm, fVerVkm,
41 O fVerUkp, fVerVkp,
42 O guDiss, gvDiss,
43 I myTime, myIter, myThid )
44
45 C !DESCRIPTION:
46 C Calculates all the horizontal accelerations except for the implicit surface
47 C pressure gradient and implicit vertical viscosity.
48
49 C !USES: ===============================================================
50 C == Global variables ==
51 IMPLICIT NONE
52 #include "SIZE.h"
53 #include "EEPARAMS.h"
54 #include "PARAMS.h"
55 #include "GRID.h"
56 #include "DYNVARS.h"
57 #include "FFIELDS.h"
58 #include "SURFACE.h"
59 #ifdef ALLOW_MOM_COMMON
60 # include "MOM_VISC.h"
61 #endif
62 #ifdef ALLOW_AUTODIFF_TAMC
63 # include "tamc.h"
64 # include "tamc_keys.h"
65 # include "MOM_FLUXFORM.h"
66 #endif
67
68 C !INPUT PARAMETERS: ===================================================
69 C bi,bj :: current tile indices
70 C k :: current vertical level
71 C iMin,iMax,jMin,jMax :: loop ranges
72 C KappaRU :: vertical viscosity
73 C KappaRV :: vertical viscosity
74 C fVerUkm :: vertical advective flux of U, interface above (k-1/2)
75 C fVerVkm :: vertical advective flux of V, interface above (k-1/2)
76 C fVerUkp :: vertical advective flux of U, interface below (k+1/2)
77 C fVerVkp :: vertical advective flux of V, interface below (k+1/2)
78 C guDiss :: dissipation tendency (all explicit terms), u component
79 C gvDiss :: dissipation tendency (all explicit terms), v component
80 C myTime :: current time
81 C myIter :: current time-step number
82 C myThid :: my Thread Id number
83 INTEGER bi,bj,k
84 INTEGER iMin,iMax,jMin,jMax
85 _RL KappaRU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
86 _RL KappaRV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
87 _RL fVerUkm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
88 _RL fVerVkm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
89 _RL fVerUkp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
90 _RL fVerVkp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
91 _RL guDiss(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
92 _RL gvDiss(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
93 _RL myTime
94 INTEGER myIter
95 INTEGER myThid
96
97 C !OUTPUT PARAMETERS: ==================================================
98 C None - updates gU() and gV() in common blocks
99
100 C !LOCAL VARIABLES: ====================================================
101 C i,j :: loop indices
102 C vF :: viscous flux
103 C v4F :: bi-harmonic viscous flux
104 C cF :: Coriolis acceleration
105 C mT :: Metric terms
106 C fZon :: zonal fluxes
107 C fMer :: meridional fluxes
108 C fVrUp,fVrDw :: vertical viscous fluxes at interface k & k+1
109 INTEGER i,j
110 #ifdef ALLOW_AUTODIFF_TAMC
111 INTEGER imomkey
112 #endif
113 _RL vF(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
114 _RL v4F(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
115 _RL cF(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
116 _RL mT(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
117 _RL fZon(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
118 _RL fMer(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
119 _RL fVrUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
120 _RL fVrDw(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
121 C afFacMom :: Tracer parameters for turning terms on and off.
122 C vfFacMom
123 C pfFacMom afFacMom - Advective terms
124 C cfFacMom vfFacMom - Eddy viscosity terms
125 C mtFacMom pfFacMom - Pressure terms
126 C cfFacMom - Coriolis terms
127 C foFacMom - Forcing
128 C mtFacMom - Metric term
129 C uDudxFac, AhDudxFac, etc ... individual term parameters for switching terms off
130 _RS hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
131 _RS r_hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
132 _RS xA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
133 _RS yA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
134 _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
135 _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
136 _RL uFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
137 _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
138 _RL rTransU(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
139 _RL rTransV(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
140 _RL KE(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
141 _RL viscAh_D(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
142 _RL viscAh_Z(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
143 _RL viscA4_D(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
144 _RL viscA4_Z(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
145 _RL vort3(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
146 _RL hDiv(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
147 _RL strain(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
148 _RL tension(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
149 _RL uDudxFac
150 _RL AhDudxFac
151 _RL vDudyFac
152 _RL AhDudyFac
153 _RL rVelDudrFac
154 _RL ArDudrFac
155 _RL fuFac
156 _RL mtFacU
157 _RL mtNHFacU
158 _RL uDvdxFac
159 _RL AhDvdxFac
160 _RL vDvdyFac
161 _RL AhDvdyFac
162 _RL rVelDvdrFac
163 _RL ArDvdrFac
164 _RL fvFac
165 _RL mtFacV
166 _RL mtNHFacV
167 _RL sideMaskFac
168 LOGICAL bottomDragTerms
169 CEOP
170 #ifdef MOM_BOUNDARY_CONSERVE
171 COMMON / MOM_FLUXFORM_LOCAL / uBnd, vBnd
172 _RL uBnd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
173 _RL vBnd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
174 #endif /* MOM_BOUNDARY_CONSERVE */
175
176 #ifdef ALLOW_AUTODIFF_TAMC
177 act0 = k - 1
178 max0 = Nr
179 act1 = bi - myBxLo(myThid)
180 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
181 act2 = bj - myByLo(myThid)
182 max2 = myByHi(myThid) - myByLo(myThid) + 1
183 act3 = myThid - 1
184 max3 = nTx*nTy
185 act4 = ikey_dynamics - 1
186 imomkey = (act0 + 1)
187 & + act1*max0
188 & + act2*max0*max1
189 & + act3*max0*max1*max2
190 & + act4*max0*max1*max2*max3
191 #endif /* ALLOW_AUTODIFF_TAMC */
192
193 C Initialise intermediate terms
194 DO j=1-OLy,sNy+OLy
195 DO i=1-OLx,sNx+OLx
196 vF(i,j) = 0.
197 v4F(i,j) = 0.
198 cF(i,j) = 0.
199 mT(i,j) = 0.
200 fZon(i,j) = 0.
201 fMer(i,j) = 0.
202 fVrUp(i,j)= 0.
203 fVrDw(i,j)= 0.
204 rTransU(i,j)= 0.
205 rTransV(i,j)= 0.
206 c KE(i,j) = 0.
207 hDiv(i,j) = 0.
208 vort3(i,j) = 0.
209 strain(i,j) = 0.
210 tension(i,j)= 0.
211 guDiss(i,j) = 0.
212 gvDiss(i,j) = 0.
213 ENDDO
214 ENDDO
215
216 C-- Term by term tracer parmeters
217 C o U momentum equation
218 uDudxFac = afFacMom*1.
219 AhDudxFac = vfFacMom*1.
220 vDudyFac = afFacMom*1.
221 AhDudyFac = vfFacMom*1.
222 rVelDudrFac = afFacMom*1.
223 ArDudrFac = vfFacMom*1.
224 mtFacU = mtFacMom*1.
225 mtNHFacU = 1.
226 fuFac = cfFacMom*1.
227 C o V momentum equation
228 uDvdxFac = afFacMom*1.
229 AhDvdxFac = vfFacMom*1.
230 vDvdyFac = afFacMom*1.
231 AhDvdyFac = vfFacMom*1.
232 rVelDvdrFac = afFacMom*1.
233 ArDvdrFac = vfFacMom*1.
234 mtFacV = mtFacMom*1.
235 mtNHFacV = 1.
236 fvFac = cfFacMom*1.
237
238 IF (implicitViscosity) THEN
239 ArDudrFac = 0.
240 ArDvdrFac = 0.
241 ENDIF
242
243 C note: using standard stencil (no mask) results in under-estimating
244 C vorticity at a no-slip boundary by a factor of 2 = sideDragFactor
245 IF ( no_slip_sides ) THEN
246 sideMaskFac = sideDragFactor
247 ELSE
248 sideMaskFac = 0. _d 0
249 ENDIF
250
251 IF ( no_slip_bottom
252 & .OR. bottomDragQuadratic.NE.0.
253 & .OR. bottomDragLinear.NE.0.) THEN
254 bottomDragTerms=.TRUE.
255 ELSE
256 bottomDragTerms=.FALSE.
257 ENDIF
258
259 C-- Calculate open water fraction at vorticity points
260 CALL MOM_CALC_HFACZ(bi,bj,k,hFacZ,r_hFacZ,myThid)
261
262 C---- Calculate common quantities used in both U and V equations
263 C Calculate tracer cell face open areas
264 DO j=1-OLy,sNy+OLy
265 DO i=1-OLx,sNx+OLx
266 xA(i,j) = _dyG(i,j,bi,bj)*deepFacC(k)
267 & *drF(k)*_hFacW(i,j,k,bi,bj)
268 yA(i,j) = _dxG(i,j,bi,bj)*deepFacC(k)
269 & *drF(k)*_hFacS(i,j,k,bi,bj)
270 ENDDO
271 ENDDO
272
273 C Make local copies of horizontal flow field
274 DO j=1-OLy,sNy+OLy
275 DO i=1-OLx,sNx+OLx
276 uFld(i,j) = uVel(i,j,k,bi,bj)
277 vFld(i,j) = vVel(i,j,k,bi,bj)
278 ENDDO
279 ENDDO
280
281 C Calculate velocity field "volume transports" through tracer cell faces.
282 C anelastic: transports are scaled by rhoFacC (~ mass transport)
283 DO j=1-OLy,sNy+OLy
284 DO i=1-OLx,sNx+OLx
285 uTrans(i,j) = uFld(i,j)*xA(i,j)*rhoFacC(k)
286 vTrans(i,j) = vFld(i,j)*yA(i,j)*rhoFacC(k)
287 ENDDO
288 ENDDO
289
290 CALL MOM_CALC_KE(bi,bj,k,2,uFld,vFld,KE,myThid)
291 IF ( momViscosity) THEN
292 CALL MOM_CALC_HDIV(bi,bj,k,2,uFld,vFld,hDiv,myThid)
293 CALL MOM_CALC_RELVORT3(bi,bj,k,uFld,vFld,hFacZ,vort3,myThid)
294 CALL MOM_CALC_TENSION(bi,bj,k,uFld,vFld,tension,myThid)
295 CALL MOM_CALC_STRAIN(bi,bj,k,uFld,vFld,hFacZ,strain,myThid)
296 DO j=1-OLy,sNy+OLy
297 DO i=1-OLx,sNx+OLx
298 IF ( hFacZ(i,j).EQ.0. ) THEN
299 vort3(i,j) = sideMaskFac*vort3(i,j)
300 strain(i,j) = sideMaskFac*strain(i,j)
301 ENDIF
302 ENDDO
303 ENDDO
304 #ifdef ALLOW_DIAGNOSTICS
305 IF ( useDiagnostics ) THEN
306 CALL DIAGNOSTICS_FILL(hDiv, 'momHDiv ',k,1,2,bi,bj,myThid)
307 CALL DIAGNOSTICS_FILL(vort3, 'momVort3',k,1,2,bi,bj,myThid)
308 CALL DIAGNOSTICS_FILL(tension,'Tension ',k,1,2,bi,bj,myThid)
309 CALL DIAGNOSTICS_FILL(strain, 'Strain ',k,1,2,bi,bj,myThid)
310 ENDIF
311 #endif
312 ENDIF
313
314 C--- First call (k=1): compute vertical adv. flux fVerUkm & fVerVkm
315 IF (momAdvection.AND.k.EQ.1) THEN
316
317 #ifdef MOM_BOUNDARY_CONSERVE
318 CALL MOM_UV_BOUNDARY( bi, bj, k,
319 I uVel, vVel,
320 O uBnd(1-OLx,1-OLy,k,bi,bj),
321 O vBnd(1-OLx,1-OLy,k,bi,bj),
322 I myTime, myIter, myThid )
323 #endif /* MOM_BOUNDARY_CONSERVE */
324
325 C- Calculate vertical transports above U & V points (West & South face):
326
327 #ifdef ALLOW_AUTODIFF_TAMC
328 # ifdef NONLIN_FRSURF
329 # ifndef DISABLE_RSTAR_CODE
330 CADJ STORE dwtransc(:,:,bi,bj) =
331 CADJ & comlev1_bibj_k, key = imomkey, byte = isbyte
332 CADJ STORE dwtransu(:,:,bi,bj) =
333 CADJ & comlev1_bibj_k, key = imomkey, byte = isbyte
334 CADJ STORE dwtransv(:,:,bi,bj) =
335 CADJ & comlev1_bibj_k, key = imomkey, byte = isbyte
336 # endif
337 # endif /* NONLIN_FRSURF */
338 #endif /* ALLOW_AUTODIFF_TAMC */
339 CALL MOM_CALC_RTRANS( k, bi, bj,
340 O rTransU, rTransV,
341 I myTime, myIter, myThid)
342
343 C- Free surface correction term (flux at k=1)
344 CALL MOM_U_ADV_WU( bi,bj,k,uVel,wVel,rTransU,
345 O fVerUkm, myThid )
346
347 CALL MOM_V_ADV_WV( bi,bj,k,vVel,wVel,rTransV,
348 O fVerVkm, myThid )
349
350 C--- endif momAdvection & k=1
351 ENDIF
352
353
354 C--- Calculate vertical transports (at k+1) below U & V points :
355 IF (momAdvection) THEN
356 CALL MOM_CALC_RTRANS( k+1, bi, bj,
357 O rTransU, rTransV,
358 I myTime, myIter, myThid)
359 ENDIF
360
361 #ifdef MOM_BOUNDARY_CONSERVE
362 IF ( momAdvection .AND. k.LT.Nr ) THEN
363 CALL MOM_UV_BOUNDARY( bi, bj, k+1,
364 I uVel, vVel,
365 O uBnd(1-OLx,1-OLy,k+1,bi,bj),
366 O vBnd(1-OLx,1-OLy,k+1,bi,bj),
367 I myTime, myIter, myThid )
368 ENDIF
369 #endif /* MOM_BOUNDARY_CONSERVE */
370
371 IF (momViscosity) THEN
372 CALL MOM_CALC_VISC( bi, bj, k,
373 O viscAh_Z, viscAh_D, viscA4_Z, viscA4_D,
374 I hDiv, vort3, tension, strain, KE, hFacZ,
375 I myThid )
376 ENDIF
377
378 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
379
380 C---- Zonal momentum equation starts here
381
382 IF (momAdvection) THEN
383 C--- Calculate mean fluxes (advection) between cells for zonal flow.
384
385 #ifdef MOM_BOUNDARY_CONSERVE
386 CALL MOM_U_ADV_UU( bi,bj,k,uTrans,uBnd(1-OLx,1-OLy,k,bi,bj),
387 O fZon,myThid )
388 CALL MOM_U_ADV_VU( bi,bj,k,vTrans,uBnd(1-OLx,1-OLy,k,bi,bj),
389 O fMer,myThid )
390 CALL MOM_U_ADV_WU(
391 I bi,bj,k+1,uBnd,wVel,rTransU,
392 O fVerUkp, myThid )
393 #else /* MOM_BOUNDARY_CONSERVE */
394 C-- Zonal flux (fZon is at east face of "u" cell)
395 C Mean flow component of zonal flux -> fZon
396 CALL MOM_U_ADV_UU(bi,bj,k,uTrans,uFld,fZon,myThid)
397
398 C-- Meridional flux (fMer is at south face of "u" cell)
399 C Mean flow component of meridional flux -> fMer
400 CALL MOM_U_ADV_VU(bi,bj,k,vTrans,uFld,fMer,myThid)
401
402 C-- Vertical flux (fVer is at upper face of "u" cell)
403 C Mean flow component of vertical flux (at k+1) -> fVer
404 CALL MOM_U_ADV_WU(
405 I bi,bj,k+1,uVel,wVel,rTransU,
406 O fVerUkp, myThid )
407 #endif /* MOM_BOUNDARY_CONSERVE */
408
409 C-- Tendency is minus divergence of the fluxes + coriolis + pressure term
410 DO j=jMin,jMax
411 DO i=iMin,iMax
412 gU(i,j,k,bi,bj) =
413 #ifdef OLD_UV_GEOM
414 & -_recip_hFacW(i,j,k,bi,bj)*recip_drF(k)/
415 & ( 0.5 _d 0*(rA(i,j,bi,bj)+rA(i-1,j,bi,bj)) )
416 #else
417 & -_recip_hFacW(i,j,k,bi,bj)*recip_drF(k)
418 & *recip_rAw(i,j,bi,bj)*recip_deepFac2C(k)*recip_rhoFacC(k)
419 #endif
420 & *( ( fZon(i,j ) - fZon(i-1,j) )*uDudxFac
421 & +( fMer(i,j+1) - fMer(i, j) )*vDudyFac
422 & +( fVerUkp(i,j) - fVerUkm(i,j) )*rkSign*rVelDudrFac
423 & )
424 ENDDO
425 ENDDO
426
427 #ifdef ALLOW_DIAGNOSTICS
428 IF ( useDiagnostics ) THEN
429 CALL DIAGNOSTICS_FILL( fZon, 'ADVx_Um ',k,1,2,bi,bj,myThid)
430 CALL DIAGNOSTICS_FILL( fMer, 'ADVy_Um ',k,1,2,bi,bj,myThid)
431 CALL DIAGNOSTICS_FILL(fVerUkm,'ADVrE_Um',k,1,2,bi,bj,myThid)
432 ENDIF
433 #endif
434
435 #ifdef NONLIN_FRSURF
436 C-- account for 3.D divergence of the flow in rStar coordinate:
437 # ifndef DISABLE_RSTAR_CODE
438 IF ( select_rStar.GT.0 ) THEN
439 DO j=jMin,jMax
440 DO i=iMin,iMax
441 gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)
442 & - (rStarExpW(i,j,bi,bj) - 1. _d 0)/deltaTfreesurf
443 & *uVel(i,j,k,bi,bj)
444 ENDDO
445 ENDDO
446 ENDIF
447 IF ( select_rStar.LT.0 ) THEN
448 DO j=jMin,jMax
449 DO i=iMin,iMax
450 gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)
451 & - rStarDhWDt(i,j,bi,bj)*uVel(i,j,k,bi,bj)
452 ENDDO
453 ENDDO
454 ENDIF
455 # endif /* DISABLE_RSTAR_CODE */
456 #endif /* NONLIN_FRSURF */
457
458 #ifdef ALLOW_ADDFLUID
459 IF ( selectAddFluid.GE.1 ) THEN
460 DO j=jMin,jMax
461 DO i=iMin,iMax
462 gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)
463 & + uVel(i,j,k,bi,bj)*mass2rUnit*0.5 _d 0
464 & *( addMass(i-1,j,k,bi,bj) + addMass(i,j,k,bi,bj) )
465 & *_recip_hFacW(i,j,k,bi,bj)*recip_drF(k)*recip_rhoFacC(k)
466 & * recip_rAw(i,j,bi,bj)*recip_deepFac2C(k)
467 ENDDO
468 ENDDO
469 ENDIF
470 #endif /* ALLOW_ADDFLUID */
471
472 ELSE
473 C- if momAdvection / else
474 DO j=1-OLy,sNy+OLy
475 DO i=1-OLx,sNx+OLx
476 gU(i,j,k,bi,bj) = 0. _d 0
477 ENDDO
478 ENDDO
479
480 C- endif momAdvection.
481 ENDIF
482
483 IF (momViscosity) THEN
484 C--- Calculate eddy fluxes (dissipation) between cells for zonal flow.
485
486 C Bi-harmonic term del^2 U -> v4F
487 IF ( useBiharmonicVisc )
488 & CALL MOM_U_DEL2U(bi,bj,k,uFld,hFacZ,v4f,myThid)
489
490 C Laplacian and bi-harmonic terms, Zonal Fluxes -> fZon
491 CALL MOM_U_XVISCFLUX(bi,bj,k,uFld,v4F,fZon,
492 I viscAh_D,viscA4_D,myThid)
493
494 C Laplacian and bi-harmonic termis, Merid Fluxes -> fMer
495 CALL MOM_U_YVISCFLUX(bi,bj,k,uFld,v4F,hFacZ,fMer,
496 I viscAh_Z,viscA4_Z,myThid)
497
498 C Eddy component of vertical flux (interior component only) -> fVrUp & fVrDw
499 IF (.NOT.implicitViscosity) THEN
500 CALL MOM_U_RVISCFLUX(bi,bj, k, uVel,KappaRU,fVrUp,myThid)
501 CALL MOM_U_RVISCFLUX(bi,bj,k+1,uVel,KappaRU,fVrDw,myThid)
502 ENDIF
503
504 C-- Tendency is minus divergence of the fluxes
505 C anelastic: hor.visc.fluxes are not scaled by rhoFac (by vert.visc.flx is)
506 DO j=jMin,jMax
507 DO i=iMin,iMax
508 guDiss(i,j) =
509 #ifdef OLD_UV_GEOM
510 & -_recip_hFacW(i,j,k,bi,bj)*recip_drF(k)/
511 & ( 0.5 _d 0*(rA(i,j,bi,bj)+rA(i-1,j,bi,bj)) )
512 #else
513 & -_recip_hFacW(i,j,k,bi,bj)*recip_drF(k)
514 & *recip_rAw(i,j,bi,bj)*recip_deepFac2C(k)
515 #endif
516 & *( ( fZon(i,j ) - fZon(i-1,j) )*AhDudxFac
517 & +( fMer(i,j+1) - fMer(i, j) )*AhDudyFac
518 & +( fVrDw(i,j) - fVrUp(i,j) )*rkSign*ArDudrFac
519 & *recip_rhoFacC(k)
520 & )
521 ENDDO
522 ENDDO
523
524 #ifdef ALLOW_DIAGNOSTICS
525 IF ( useDiagnostics ) THEN
526 CALL DIAGNOSTICS_FILL(fZon, 'VISCx_Um',k,1,2,bi,bj,myThid)
527 CALL DIAGNOSTICS_FILL(fMer, 'VISCy_Um',k,1,2,bi,bj,myThid)
528 IF (.NOT.implicitViscosity)
529 & CALL DIAGNOSTICS_FILL(fVrUp,'VISrE_Um',k,1,2,bi,bj,myThid)
530 ENDIF
531 #endif
532
533 C-- No-slip and drag BCs appear as body forces in cell abutting topography
534 IF (no_slip_sides) THEN
535 C- No-slip BCs impose a drag at walls...
536 CALL MOM_U_SIDEDRAG( bi, bj, k,
537 I uFld, v4f, hFacZ,
538 I viscAh_Z, viscA4_Z,
539 I useHarmonicVisc, useBiharmonicVisc, useVariableVisc,
540 O vF,
541 I myThid )
542 DO j=jMin,jMax
543 DO i=iMin,iMax
544 gUdiss(i,j) = gUdiss(i,j) + vF(i,j)
545 ENDDO
546 ENDDO
547 ENDIF
548 C- No-slip BCs impose a drag at bottom
549 IF (bottomDragTerms) THEN
550 CALL MOM_U_BOTTOMDRAG(bi,bj,k,uFld,KE,KappaRU,vF,myThid)
551 DO j=jMin,jMax
552 DO i=iMin,iMax
553 gUdiss(i,j) = gUdiss(i,j) + vF(i,j)
554 ENDDO
555 ENDDO
556 ENDIF
557
558 #ifdef ALLOW_SHELFICE
559 IF (useShelfIce) THEN
560 CALL SHELFICE_U_DRAG(bi,bj,k,uFld,KE,KappaRU,vF,myThid)
561 DO j=jMin,jMax
562 DO i=iMin,iMax
563 gUdiss(i,j) = gUdiss(i,j) + vF(i,j)
564 ENDDO
565 ENDDO
566 ENDIF
567 #endif /* ALLOW_SHELFICE */
568
569 C- endif momViscosity
570 ENDIF
571
572 C-- Forcing term (moved to timestep.F)
573 c IF (momForcing)
574 c & CALL EXTERNAL_FORCING_U(
575 c I iMin,iMax,jMin,jMax,bi,bj,k,
576 c I myTime,myThid)
577
578 C-- Metric terms for curvilinear grid systems
579 IF (useNHMTerms) THEN
580 C o Non-Hydrostatic (spherical) metric terms
581 CALL MOM_U_METRIC_NH(bi,bj,k,uFld,wVel,mT,myThid)
582 DO j=jMin,jMax
583 DO i=iMin,iMax
584 gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+mtNHFacU*mT(i,j)
585 ENDDO
586 ENDDO
587 ENDIF
588 IF ( usingSphericalPolarGrid .AND. metricTerms ) THEN
589 C o Spherical polar grid metric terms
590 CALL MOM_U_METRIC_SPHERE(bi,bj,k,uFld,vFld,mT,myThid)
591 DO j=jMin,jMax
592 DO i=iMin,iMax
593 gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+mtFacU*mT(i,j)
594 ENDDO
595 ENDDO
596 ENDIF
597 IF ( usingCylindricalGrid .AND. metricTerms ) THEN
598 C o Cylindrical grid metric terms
599 CALL MOM_U_METRIC_CYLINDER(bi,bj,k,uFld,vFld,mT,myThid)
600 DO j=jMin,jMax
601 DO i=iMin,iMax
602 gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+mtFacU*mT(i,j)
603 ENDDO
604 ENDDO
605 ENDIF
606
607 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
608
609 C---- Meridional momentum equation starts here
610
611 IF (momAdvection) THEN
612
613 #ifdef MOM_BOUNDARY_CONSERVE
614 CALL MOM_V_ADV_UV( bi,bj,k,uTrans,vBnd(1-OLx,1-OLy,k,bi,bj),
615 O fZon,myThid )
616 CALL MOM_V_ADV_VV( bi,bj,k,vTrans,vBnd(1-OLx,1-OLy,k,bi,bj),
617 O fMer,myThid )
618 CALL MOM_V_ADV_WV( bi,bj,k+1,vBnd,wVel,rTransV,
619 O fVerVkp, myThid )
620 #else /* MOM_BOUNDARY_CONSERVE */
621 C--- Calculate mean fluxes (advection) between cells for meridional flow.
622 C Mean flow component of zonal flux -> fZon
623 CALL MOM_V_ADV_UV( bi,bj,k,uTrans,vFld,fZon,myThid )
624
625 C-- Meridional flux (fMer is at north face of "v" cell)
626 C Mean flow component of meridional flux -> fMer
627 CALL MOM_V_ADV_VV( bi,bj,k,vTrans,vFld,fMer,myThid )
628
629 C-- Vertical flux (fVer is at upper face of "v" cell)
630 C Mean flow component of vertical flux (at k+1) -> fVerV
631 CALL MOM_V_ADV_WV( bi,bj,k+1,vVel,wVel,rTransV,
632 O fVerVkp, myThid )
633 #endif /* MOM_BOUNDARY_CONSERVE */
634
635 C-- Tendency is minus divergence of the fluxes + coriolis + pressure term
636 DO j=jMin,jMax
637 DO i=iMin,iMax
638 gV(i,j,k,bi,bj) =
639 #ifdef OLD_UV_GEOM
640 & -_recip_hFacS(i,j,k,bi,bj)*recip_drF(k)/
641 & ( 0.5 _d 0*(_rA(i,j,bi,bj)+_rA(i,j-1,bi,bj)) )
642 #else
643 & -_recip_hFacS(i,j,k,bi,bj)*recip_drF(k)
644 & *recip_rAs(i,j,bi,bj)*recip_deepFac2C(k)*recip_rhoFacC(k)
645 #endif
646 & *( ( fZon(i+1,j) - fZon(i,j ) )*uDvdxFac
647 & +( fMer(i, j) - fMer(i,j-1) )*vDvdyFac
648 & +( fVerVkp(i,j) - fVerVkm(i,j) )*rkSign*rVelDvdrFac
649 & )
650 ENDDO
651 ENDDO
652
653 #ifdef ALLOW_DIAGNOSTICS
654 IF ( useDiagnostics ) THEN
655 CALL DIAGNOSTICS_FILL( fZon, 'ADVx_Vm ',k,1,2,bi,bj,myThid)
656 CALL DIAGNOSTICS_FILL( fMer, 'ADVy_Vm ',k,1,2,bi,bj,myThid)
657 CALL DIAGNOSTICS_FILL(fVerVkm,'ADVrE_Vm',k,1,2,bi,bj,myThid)
658 ENDIF
659 #endif
660
661 #ifdef NONLIN_FRSURF
662 C-- account for 3.D divergence of the flow in rStar coordinate:
663 # ifndef DISABLE_RSTAR_CODE
664 IF ( select_rStar.GT.0 ) THEN
665 DO j=jMin,jMax
666 DO i=iMin,iMax
667 gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)
668 & - (rStarExpS(i,j,bi,bj) - 1. _d 0)/deltaTfreesurf
669 & *vVel(i,j,k,bi,bj)
670 ENDDO
671 ENDDO
672 ENDIF
673 IF ( select_rStar.LT.0 ) THEN
674 DO j=jMin,jMax
675 DO i=iMin,iMax
676 gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)
677 & - rStarDhSDt(i,j,bi,bj)*vVel(i,j,k,bi,bj)
678 ENDDO
679 ENDDO
680 ENDIF
681 # endif /* DISABLE_RSTAR_CODE */
682 #endif /* NONLIN_FRSURF */
683
684 #ifdef ALLOW_ADDFLUID
685 IF ( selectAddFluid.GE.1 ) THEN
686 DO j=jMin,jMax
687 DO i=iMin,iMax
688 gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)
689 & + vVel(i,j,k,bi,bj)*mass2rUnit*0.5 _d 0
690 & *( addMass(i,j-1,k,bi,bj) + addMass(i,j,k,bi,bj) )
691 & *_recip_hFacS(i,j,k,bi,bj)*recip_drF(k)*recip_rhoFacC(k)
692 & * recip_rAs(i,j,bi,bj)*recip_deepFac2C(k)
693 ENDDO
694 ENDDO
695 ENDIF
696 #endif /* ALLOW_ADDFLUID */
697
698 ELSE
699 C- if momAdvection / else
700 DO j=1-OLy,sNy+OLy
701 DO i=1-OLx,sNx+OLx
702 gV(i,j,k,bi,bj) = 0. _d 0
703 ENDDO
704 ENDDO
705
706 C- endif momAdvection.
707 ENDIF
708
709 IF (momViscosity) THEN
710 C--- Calculate eddy fluxes (dissipation) between cells for meridional flow.
711 C Bi-harmonic term del^2 V -> v4F
712 IF ( useBiharmonicVisc )
713 & CALL MOM_V_DEL2V(bi,bj,k,vFld,hFacZ,v4f,myThid)
714
715 C Laplacian and bi-harmonic terms, Zonal Fluxes -> fZon
716 CALL MOM_V_XVISCFLUX(bi,bj,k,vFld,v4f,hFacZ,fZon,
717 I viscAh_Z,viscA4_Z,myThid)
718
719 C Laplacian and bi-harmonic termis, Merid Fluxes -> fMer
720 CALL MOM_V_YVISCFLUX(bi,bj,k,vFld,v4f,fMer,
721 I viscAh_D,viscA4_D,myThid)
722
723 C Eddy component of vertical flux (interior component only) -> fVrUp & fVrDw
724 IF (.NOT.implicitViscosity) THEN
725 CALL MOM_V_RVISCFLUX(bi,bj, k, vVel,KappaRV,fVrUp,myThid)
726 CALL MOM_V_RVISCFLUX(bi,bj,k+1,vVel,KappaRV,fVrDw,myThid)
727 ENDIF
728
729 C-- Tendency is minus divergence of the fluxes + coriolis + pressure term
730 C anelastic: hor.visc.fluxes are not scaled by rhoFac (by vert.visc.flx is)
731 DO j=jMin,jMax
732 DO i=iMin,iMax
733 gvDiss(i,j) =
734 #ifdef OLD_UV_GEOM
735 & -_recip_hFacS(i,j,k,bi,bj)*recip_drF(k)/
736 & ( 0.5 _d 0*(_rA(i,j,bi,bj)+_rA(i,j-1,bi,bj)) )
737 #else
738 & -_recip_hFacS(i,j,k,bi,bj)*recip_drF(k)
739 & *recip_rAs(i,j,bi,bj)*recip_deepFac2C(k)
740 #endif
741 & *( ( fZon(i+1,j) - fZon(i,j ) )*AhDvdxFac
742 & +( fMer(i, j) - fMer(i,j-1) )*AhDvdyFac
743 & +( fVrDw(i,j) - fVrUp(i,j) )*rkSign*ArDvdrFac
744 & *recip_rhoFacC(k)
745 & )
746 ENDDO
747 ENDDO
748
749 #ifdef ALLOW_DIAGNOSTICS
750 IF ( useDiagnostics ) THEN
751 CALL DIAGNOSTICS_FILL(fZon, 'VISCx_Vm',k,1,2,bi,bj,myThid)
752 CALL DIAGNOSTICS_FILL(fMer, 'VISCy_Vm',k,1,2,bi,bj,myThid)
753 IF (.NOT.implicitViscosity)
754 & CALL DIAGNOSTICS_FILL(fVrUp,'VISrE_Vm',k,1,2,bi,bj,myThid)
755 ENDIF
756 #endif
757
758 C-- No-slip and drag BCs appear as body forces in cell abutting topography
759 IF (no_slip_sides) THEN
760 C- No-slip BCs impose a drag at walls...
761 CALL MOM_V_SIDEDRAG( bi, bj, k,
762 I vFld, v4f, hFacZ,
763 I viscAh_Z,viscA4_Z,
764 I useHarmonicVisc, useBiharmonicVisc, useVariableVisc,
765 O vF,
766 I myThid )
767 DO j=jMin,jMax
768 DO i=iMin,iMax
769 gvDiss(i,j) = gvDiss(i,j) + vF(i,j)
770 ENDDO
771 ENDDO
772 ENDIF
773 C- No-slip BCs impose a drag at bottom
774 IF (bottomDragTerms) THEN
775 CALL MOM_V_BOTTOMDRAG(bi,bj,k,vFld,KE,KappaRV,vF,myThid)
776 DO j=jMin,jMax
777 DO i=iMin,iMax
778 gvDiss(i,j) = gvDiss(i,j) + vF(i,j)
779 ENDDO
780 ENDDO
781 ENDIF
782
783 #ifdef ALLOW_SHELFICE
784 IF (useShelfIce) THEN
785 CALL SHELFICE_V_DRAG(bi,bj,k,vFld,KE,KappaRV,vF,myThid)
786 DO j=jMin,jMax
787 DO i=iMin,iMax
788 gvDiss(i,j) = gvDiss(i,j) + vF(i,j)
789 ENDDO
790 ENDDO
791 ENDIF
792 #endif /* ALLOW_SHELFICE */
793
794 C- endif momViscosity
795 ENDIF
796
797 C-- Forcing term (moved to timestep.F)
798 c IF (momForcing)
799 c & CALL EXTERNAL_FORCING_V(
800 c I iMin,iMax,jMin,jMax,bi,bj,k,
801 c I myTime,myThid)
802
803 C-- Metric terms for curvilinear grid systems
804 IF (useNHMTerms) THEN
805 C o Non-Hydrostatic (spherical) metric terms
806 CALL MOM_V_METRIC_NH(bi,bj,k,vFld,wVel,mT,myThid)
807 DO j=jMin,jMax
808 DO i=iMin,iMax
809 gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+mtNHFacV*mT(i,j)
810 ENDDO
811 ENDDO
812 ENDIF
813 IF ( usingSphericalPolarGrid .AND. metricTerms ) THEN
814 C o Spherical polar grid metric terms
815 CALL MOM_V_METRIC_SPHERE(bi,bj,k,uFld,mT,myThid)
816 DO j=jMin,jMax
817 DO i=iMin,iMax
818 gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+mtFacV*mT(i,j)
819 ENDDO
820 ENDDO
821 ENDIF
822 IF ( usingCylindricalGrid .AND. metricTerms ) THEN
823 C o Cylindrical grid metric terms
824 CALL MOM_V_METRIC_CYLINDER(bi,bj,k,uFld,vFld,mT,myThid)
825 DO j=jMin,jMax
826 DO i=iMin,iMax
827 gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+mtFacV*mT(i,j)
828 ENDDO
829 ENDDO
830 ENDIF
831
832 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
833
834 C-- Coriolis term
835 C Note. As coded here, coriolis will not work with "thin walls"
836 c IF (useCDscheme) THEN
837 c CALL MOM_CDSCHEME(bi,bj,k,dPhiHydX,dPhiHydY,myThid)
838 c ELSE
839 IF (.NOT.useCDscheme) THEN
840 CALL MOM_U_CORIOLIS(bi,bj,k,vFld,cf,myThid)
841 DO j=jMin,jMax
842 DO i=iMin,iMax
843 gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+fuFac*cf(i,j)
844 ENDDO
845 ENDDO
846 #ifdef ALLOW_DIAGNOSTICS
847 IF ( useDiagnostics )
848 & CALL DIAGNOSTICS_FILL(cf,'Um_Cori ',k,1,2,bi,bj,myThid)
849 #endif
850 CALL MOM_V_CORIOLIS(bi,bj,k,uFld,cf,myThid)
851 DO j=jMin,jMax
852 DO i=iMin,iMax
853 gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+fvFac*cf(i,j)
854 ENDDO
855 ENDDO
856 #ifdef ALLOW_DIAGNOSTICS
857 IF ( useDiagnostics )
858 & CALL DIAGNOSTICS_FILL(cf,'Vm_Cori ',k,1,2,bi,bj,myThid)
859 #endif
860 ENDIF
861
862 C-- 3.D Coriolis term (horizontal momentum, Eastward component: -fprime*w)
863 IF ( use3dCoriolis ) THEN
864 CALL MOM_U_CORIOLIS_NH(bi,bj,k,wVel,cf,myThid)
865 DO j=jMin,jMax
866 DO i=iMin,iMax
867 gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+fuFac*cf(i,j)
868 ENDDO
869 ENDDO
870 IF ( usingCurvilinearGrid ) THEN
871 C- presently, non zero angleSinC array only supported with Curvilinear-Grid
872 CALL MOM_V_CORIOLIS_NH(bi,bj,k,wVel,cf,myThid)
873 DO j=jMin,jMax
874 DO i=iMin,iMax
875 gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+fvFac*cf(i,j)
876 ENDDO
877 ENDDO
878 ENDIF
879 ENDIF
880
881 C-- Set du/dt & dv/dt on boundaries to zero
882 DO j=jMin,jMax
883 DO i=iMin,iMax
884 gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)*_maskW(i,j,k,bi,bj)
885 guDiss(i,j) = guDiss(i,j) *_maskW(i,j,k,bi,bj)
886 gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)*_maskS(i,j,k,bi,bj)
887 gvDiss(i,j) = gvDiss(i,j) *_maskS(i,j,k,bi,bj)
888 ENDDO
889 ENDDO
890
891 #ifdef ALLOW_DIAGNOSTICS
892 IF ( useDiagnostics ) THEN
893 CALL DIAGNOSTICS_FILL(KE, 'momKE ',k,1,2,bi,bj,myThid)
894 CALL DIAGNOSTICS_FILL(gU(1-OLx,1-OLy,k,bi,bj),
895 & 'Um_Advec',k,1,2,bi,bj,myThid)
896 CALL DIAGNOSTICS_FILL(gV(1-OLx,1-OLy,k,bi,bj),
897 & 'Vm_Advec',k,1,2,bi,bj,myThid)
898 IF (momViscosity) THEN
899 CALL DIAGNOSTICS_FILL(guDiss,'Um_Diss ',k,1,2,bi,bj,myThid)
900 CALL DIAGNOSTICS_FILL(gvDiss,'Vm_Diss ',k,1,2,bi,bj,myThid)
901 ENDIF
902 ENDIF
903 #endif /* ALLOW_DIAGNOSTICS */
904
905 RETURN
906 END

  ViewVC Help
Powered by ViewVC 1.1.22