/[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.42 - (show annotations) (download)
Tue Mar 16 00:16:50 2010 UTC (14 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62w, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint63g, checkpoint63, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c
Changes since 1.41: +2 -2 lines
avoid unbalanced quote (single or double) in commented line

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

  ViewVC Help
Powered by ViewVC 1.1.22