/[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.55 - (show annotations) (download)
Wed Nov 30 00:11:22 2016 UTC (7 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, HEAD
Changes since 1.54: +4 -3 lines
forgot these 2 S/R: with implicit bottom friction, turn off explicit bottom i
 drag calls.

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

  ViewVC Help
Powered by ViewVC 1.1.22