/[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.49 - (show annotations) (download)
Sun Feb 9 18:51:46 2014 UTC (11 years, 9 months ago) by jmc
Branch: MAIN
Changes since 1.48: +59 -43 lines
fix sideDrag option for thin-walls with Non-Lin Free-Surf
using 2nd hFacZ that is computed from initial (fix domain) hFac

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

  ViewVC Help
Powered by ViewVC 1.1.22