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

Annotation of /MITgcm/pkg/mom_vecinv/mom_vecinv.F

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


Revision 1.20 - (hide annotations) (download)
Wed Jun 2 13:23:55 2004 UTC (19 years, 11 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint54, checkpoint53d_post, checkpoint54b_post, checkpoint54a_pre, checkpoint54a_post, checkpoint53g_post, checkpoint53f_post, checkpoint54c_post
Changes since 1.19: +21 -11 lines
Added Sadourny discretization of Coriolis in V.I. mode
 - moved some PARAMETERS from mom_*_coriolis.F to PARAMS.h
 - re-enabled use of omega3 in mom_vecinv.F

1 adcroft 1.20 C $Header: /u/gcmpack/MITgcm/pkg/mom_vecinv/mom_vecinv.F,v 1.19 2004/05/26 14:50:10 adcroft Exp $
2 adcroft 1.2 C $Name: $
3 adcroft 1.1
4 edhill 1.10 #include "PACKAGES_CONFIG.h"
5 adcroft 1.1 #include "CPP_OPTIONS.h"
6    
7     SUBROUTINE MOM_VECINV(
8     I bi,bj,iMin,iMax,jMin,jMax,k,kUp,kDown,
9 jmc 1.4 I dPhiHydX,dPhiHydY,KappaRU,KappaRV,
10 adcroft 1.1 U fVerU, fVerV,
11 jmc 1.15 I myTime, myIter, myThid)
12 adcroft 1.1 C /==========================================================\
13     C | S/R MOM_VECINV |
14     C | o Form the right hand-side of the momentum equation. |
15     C |==========================================================|
16     C | Terms are evaluated one layer at a time working from |
17     C | the bottom to the top. The vertically integrated |
18     C | barotropic flow tendency term is evluated by summing the |
19     C | tendencies. |
20     C | Notes: |
21     C | We have not sorted out an entirely satisfactory formula |
22     C | for the diffusion equation bc with lopping. The present |
23     C | form produces a diffusive flux that does not scale with |
24     C | open-area. Need to do something to solidfy this and to |
25     C | deal "properly" with thin walls. |
26     C \==========================================================/
27     IMPLICIT NONE
28    
29     C == Global variables ==
30     #include "SIZE.h"
31     #include "DYNVARS.h"
32     #include "EEPARAMS.h"
33     #include "PARAMS.h"
34     #include "GRID.h"
35 jmc 1.7 #ifdef ALLOW_TIMEAVE
36     #include "TIMEAVE_STATV.h"
37     #endif
38 adcroft 1.1
39     C == Routine arguments ==
40     C fVerU - Flux of momentum in the vertical
41     C fVerV direction out of the upper face of a cell K
42     C ( flux into the cell above ).
43 jmc 1.4 C dPhiHydX,Y :: Gradient (X & Y dir.) of Hydrostatic Potential
44 adcroft 1.1 C bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation
45     C results will be set.
46     C kUp, kDown - Index for upper and lower layers.
47     C myThid - Instance number for this innvocation of CALC_MOM_RHS
48 jmc 1.4 _RL dPhiHydX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
49     _RL dPhiHydY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
50 adcroft 1.1 _RL KappaRU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
51     _RL KappaRV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
52     _RL fVerU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
53     _RL fVerV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
54     INTEGER kUp,kDown
55 jmc 1.15 _RL myTime
56 adcroft 1.2 INTEGER myIter
57 adcroft 1.1 INTEGER myThid
58     INTEGER bi,bj,iMin,iMax,jMin,jMax
59    
60 edhill 1.11 #ifdef ALLOW_MOM_VECINV
61 jmc 1.7
62 adcroft 1.2 C == Functions ==
63     LOGICAL DIFFERENT_MULTIPLE
64     EXTERNAL DIFFERENT_MULTIPLE
65    
66 adcroft 1.1 C == Local variables ==
67     _RL aF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
68     _RL vF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
69     _RL vrF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
70     _RL uCf (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71     _RL vCf (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72     _RL mT (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
73     _RL pF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
74     _RL del2u(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
75     _RL del2v(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76 adcroft 1.3 _RL tension(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77     _RL strain(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78 adcroft 1.1 _RS hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79     _RS r_hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80     _RS xA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
81     _RS yA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
82     _RL uFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
83     _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
84     _RL dStar(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
85     _RL zStar(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
86     _RL uDiss(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
87     _RL vDiss(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
88     C I,J,K - Loop counters
89     INTEGER i,j,k
90     C rVelMaskOverride - Factor for imposing special surface boundary conditions
91     C ( set according to free-surface condition ).
92     C hFacROpen - Lopped cell factos used tohold fraction of open
93     C hFacRClosed and closed cell wall.
94     _RL rVelMaskOverride
95     C xxxFac - On-off tracer parameters used for switching terms off.
96     _RL uDudxFac
97     _RL AhDudxFac
98     _RL A4DuxxdxFac
99     _RL vDudyFac
100     _RL AhDudyFac
101     _RL A4DuyydyFac
102     _RL rVelDudrFac
103     _RL ArDudrFac
104     _RL fuFac
105     _RL phxFac
106     _RL mtFacU
107     _RL uDvdxFac
108     _RL AhDvdxFac
109     _RL A4DvxxdxFac
110     _RL vDvdyFac
111     _RL AhDvdyFac
112     _RL A4DvyydyFac
113     _RL rVelDvdrFac
114     _RL ArDvdrFac
115     _RL fvFac
116     _RL phyFac
117     _RL vForcFac
118     _RL mtFacV
119     _RL wVelBottomOverride
120     LOGICAL bottomDragTerms
121 jmc 1.15 LOGICAL writeDiag
122 adcroft 1.1 _RL KE(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
123     _RL omega3(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
124     _RL vort3(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
125     _RL hDiv(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
126    
127 heimbach 1.9 #ifdef ALLOW_AUTODIFF_TAMC
128     C-- only the kDown part of fverU/V is set in this subroutine
129     C-- the kUp is still required
130     C-- In the case of mom_fluxform Kup is set as well
131     C-- (at least in part)
132     fVerU(1,1,kUp) = fVerU(1,1,kUp)
133     fVerV(1,1,kUp) = fVerV(1,1,kUp)
134     #endif
135    
136 adcroft 1.1 rVelMaskOverride=1.
137     IF ( k .EQ. 1 ) rVelMaskOverride=freeSurfFac
138     wVelBottomOverride=1.
139     IF (k.EQ.Nr) wVelBottomOverride=0.
140 jmc 1.15 writeDiag = DIFFERENT_MULTIPLE(diagFreq, myTime,
141     & myTime-deltaTClock)
142 adcroft 1.1
143     C Initialise intermediate terms
144     DO J=1-OLy,sNy+OLy
145     DO I=1-OLx,sNx+OLx
146     aF(i,j) = 0.
147     vF(i,j) = 0.
148     vrF(i,j) = 0.
149     uCf(i,j) = 0.
150     vCf(i,j) = 0.
151     mT(i,j) = 0.
152     pF(i,j) = 0.
153     del2u(i,j) = 0.
154     del2v(i,j) = 0.
155     dStar(i,j) = 0.
156     zStar(i,j) = 0.
157     uDiss(i,j) = 0.
158     vDiss(i,j) = 0.
159     vort3(i,j) = 0.
160     omega3(i,j) = 0.
161     ke(i,j) = 0.
162 heimbach 1.8 #ifdef ALLOW_AUTODIFF_TAMC
163     strain(i,j) = 0. _d 0
164     tension(i,j) = 0. _d 0
165     #endif
166 adcroft 1.1 ENDDO
167     ENDDO
168    
169     C-- Term by term tracer parmeters
170     C o U momentum equation
171     uDudxFac = afFacMom*1.
172     AhDudxFac = vfFacMom*1.
173     A4DuxxdxFac = vfFacMom*1.
174     vDudyFac = afFacMom*1.
175     AhDudyFac = vfFacMom*1.
176     A4DuyydyFac = vfFacMom*1.
177     rVelDudrFac = afFacMom*1.
178     ArDudrFac = vfFacMom*1.
179     mTFacU = mtFacMom*1.
180     fuFac = cfFacMom*1.
181     phxFac = pfFacMom*1.
182     C o V momentum equation
183     uDvdxFac = afFacMom*1.
184     AhDvdxFac = vfFacMom*1.
185     A4DvxxdxFac = vfFacMom*1.
186     vDvdyFac = afFacMom*1.
187     AhDvdyFac = vfFacMom*1.
188     A4DvyydyFac = vfFacMom*1.
189     rVelDvdrFac = afFacMom*1.
190     ArDvdrFac = vfFacMom*1.
191     mTFacV = mtFacMom*1.
192     fvFac = cfFacMom*1.
193     phyFac = pfFacMom*1.
194     vForcFac = foFacMom*1.
195    
196     IF ( no_slip_bottom
197     & .OR. bottomDragQuadratic.NE.0.
198     & .OR. bottomDragLinear.NE.0.) THEN
199     bottomDragTerms=.TRUE.
200     ELSE
201     bottomDragTerms=.FALSE.
202     ENDIF
203    
204     C-- with stagger time stepping, grad Phi_Hyp is directly incoporated in TIMESTEP
205     IF (staggerTimeStep) THEN
206     phxFac = 0.
207     phyFac = 0.
208     ENDIF
209    
210     C-- Calculate open water fraction at vorticity points
211     CALL MOM_CALC_HFACZ(bi,bj,k,hFacZ,r_hFacZ,myThid)
212    
213     C---- Calculate common quantities used in both U and V equations
214     C Calculate tracer cell face open areas
215     DO j=1-OLy,sNy+OLy
216     DO i=1-OLx,sNx+OLx
217     xA(i,j) = _dyG(i,j,bi,bj)
218     & *drF(k)*_hFacW(i,j,k,bi,bj)
219     yA(i,j) = _dxG(i,j,bi,bj)
220     & *drF(k)*_hFacS(i,j,k,bi,bj)
221     ENDDO
222     ENDDO
223    
224     C Make local copies of horizontal flow field
225     DO j=1-OLy,sNy+OLy
226     DO i=1-OLx,sNx+OLx
227     uFld(i,j) = uVel(i,j,k,bi,bj)
228     vFld(i,j) = vVel(i,j,k,bi,bj)
229     ENDDO
230     ENDDO
231    
232 jmc 1.7 C note (jmc) : Dissipation and Vort3 advection do not necesary
233     C use the same maskZ (and hFacZ) => needs 2 call(s)
234     c CALL MOM_VI_HFACZ_DISS(bi,bj,k,hFacZ,r_hFacZ,myThid)
235    
236 adcroft 1.16 CALL MOM_CALC_KE(bi,bj,k,2,uFld,vFld,KE,myThid)
237 adcroft 1.1
238 adcroft 1.17 CALL MOM_CALC_HDIV(bi,bj,k,2,uFld,vFld,hDiv,myThid)
239 adcroft 1.1
240 adcroft 1.18 CALL MOM_CALC_RELVORT3(bi,bj,k,uFld,vFld,hFacZ,vort3,myThid)
241 adcroft 1.1
242 adcroft 1.20 IF (useAbsVorticity)
243     & CALL MOM_CALC_ABSVORT3(bi,bj,k,vort3,omega3,myThid)
244 adcroft 1.1
245     IF (momViscosity) THEN
246     C Calculate del^2 u and del^2 v for bi-harmonic term
247 adcroft 1.19 IF (viscA4.NE.0.
248     & .OR. viscA4Grid.NE.0.
249     & .OR. viscC4leith.NE.0.
250     & ) THEN
251 adcroft 1.2 CALL MOM_VI_DEL2UV(bi,bj,k,hDiv,vort3,hFacZ,
252     O del2u,del2v,
253     & myThid)
254 adcroft 1.17 CALL MOM_CALC_HDIV(bi,bj,k,2,del2u,del2v,dStar,myThid)
255 adcroft 1.18 CALL MOM_CALC_RELVORT3(
256 adcroft 1.2 & bi,bj,k,del2u,del2v,hFacZ,zStar,myThid)
257     ENDIF
258 adcroft 1.1 C Calculate dissipation terms for U and V equations
259 adcroft 1.2 C in terms of vorticity and divergence
260 adcroft 1.19 IF (viscAh.NE.0. .OR. viscA4.NE.0.
261     & .OR. viscAhGrid.NE.0. .OR. viscA4Grid.NE.0.
262     & .OR. viscC2leith.NE.0. .OR. viscC4leith.NE.0.
263     & ) THEN
264 adcroft 1.2 CALL MOM_VI_HDISSIP(bi,bj,k,hDiv,vort3,hFacZ,dStar,zStar,
265     O uDiss,vDiss,
266     & myThid)
267     ENDIF
268 adcroft 1.3 C or in terms of tension and strain
269     IF (viscAstrain.NE.0. .OR. viscAtension.NE.0.) THEN
270     CALL MOM_CALC_TENSION(bi,bj,k,uFld,vFld,
271     O tension,
272     I myThid)
273     CALL MOM_CALC_STRAIN(bi,bj,k,uFld,vFld,hFacZ,
274     O strain,
275     I myThid)
276     CALL MOM_HDISSIP(bi,bj,k,
277     I tension,strain,hFacZ,viscAtension,viscAstrain,
278     O uDiss,vDiss,
279     I myThid)
280     ENDIF
281 adcroft 1.1 ENDIF
282    
283 jmc 1.7 C- Return to standard hfacZ (min-4) and mask vort3 accordingly:
284     c CALL MOM_VI_MASK_VORT3(bi,bj,k,hFacZ,r_hFacZ,vort3,myThid)
285    
286 adcroft 1.1 C---- Zonal momentum equation starts here
287    
288     C-- Vertical flux (fVer is at upper face of "u" cell)
289    
290     C Eddy component of vertical flux (interior component only) -> vrF
291     IF (momViscosity.AND..NOT.implicitViscosity)
292     & CALL MOM_U_RVISCFLUX(bi,bj,k,uVel,KappaRU,vrF,myThid)
293    
294     C Combine fluxes
295     DO j=jMin,jMax
296     DO i=iMin,iMax
297     fVerU(i,j,kDown) = ArDudrFac*vrF(i,j)
298     ENDDO
299     ENDDO
300    
301     C-- Tendency is minus divergence of the fluxes + coriolis + pressure term
302     DO j=2-Oly,sNy+Oly-1
303     DO i=2-Olx,sNx+Olx-1
304     gU(i,j,k,bi,bj) = uDiss(i,j)
305     & -_recip_hFacW(i,j,k,bi,bj)*recip_drF(k)
306     & *recip_rAw(i,j,bi,bj)
307     & *(
308     & +fVerU(i,j,kUp)*rkFac - fVerU(i,j,kDown)*rkFac
309     & )
310 jmc 1.4 & - phxFac*dPhiHydX(i,j)
311 adcroft 1.1 ENDDO
312     ENDDO
313    
314     C-- No-slip and drag BCs appear as body forces in cell abutting topography
315     IF (momViscosity.AND.no_slip_sides) THEN
316     C- No-slip BCs impose a drag at walls...
317     CALL MOM_U_SIDEDRAG(bi,bj,k,uFld,del2u,hFacZ,vF,myThid)
318     DO j=jMin,jMax
319     DO i=iMin,iMax
320     gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+vF(i,j)
321     ENDDO
322     ENDDO
323     ENDIF
324 heimbach 1.8
325 adcroft 1.1 C- No-slip BCs impose a drag at bottom
326     IF (momViscosity.AND.bottomDragTerms) THEN
327     CALL MOM_U_BOTTOMDRAG(bi,bj,k,uFld,KE,KappaRU,vF,myThid)
328     DO j=jMin,jMax
329     DO i=iMin,iMax
330     gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+vF(i,j)
331     ENDDO
332     ENDDO
333     ENDIF
334    
335     C-- Metric terms for curvilinear grid systems
336     c IF (usingSphericalPolarMTerms) THEN
337     C o Spherical polar grid metric terms
338     c CALL MOM_U_METRIC_NH(bi,bj,k,uFld,wVel,mT,myThid)
339     c DO j=jMin,jMax
340     c DO i=iMin,iMax
341     c gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+mTFacU*mT(i,j)
342     c ENDDO
343     c ENDDO
344     c ENDIF
345    
346     C---- Meridional momentum equation starts here
347    
348     C-- Vertical flux (fVer is at upper face of "v" cell)
349    
350     C Eddy component of vertical flux (interior component only) -> vrF
351     IF (momViscosity.AND..NOT.implicitViscosity)
352     & CALL MOM_V_RVISCFLUX(bi,bj,k,vVel,KappaRV,vrf,myThid)
353    
354     C Combine fluxes -> fVerV
355     DO j=jMin,jMax
356     DO i=iMin,iMax
357     fVerV(i,j,kDown) = ArDvdrFac*vrF(i,j)
358     ENDDO
359     ENDDO
360    
361     C-- Tendency is minus divergence of the fluxes + coriolis + pressure term
362     DO j=jMin,jMax
363     DO i=iMin,iMax
364     gV(i,j,k,bi,bj) = vDiss(i,j)
365     & -_recip_hFacS(i,j,k,bi,bj)*recip_drF(k)
366     & *recip_rAs(i,j,bi,bj)
367     & *(
368     & +fVerV(i,j,kUp)*rkFac - fVerV(i,j,kDown)*rkFac
369     & )
370 jmc 1.4 & - phyFac*dPhiHydY(i,j)
371 adcroft 1.1 ENDDO
372     ENDDO
373    
374     C-- No-slip and drag BCs appear as body forces in cell abutting topography
375     IF (momViscosity.AND.no_slip_sides) THEN
376     C- No-slip BCs impose a drag at walls...
377     CALL MOM_V_SIDEDRAG(bi,bj,k,vFld,del2v,hFacZ,vF,myThid)
378     DO j=jMin,jMax
379     DO i=iMin,iMax
380     gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vF(i,j)
381     ENDDO
382     ENDDO
383     ENDIF
384     C- No-slip BCs impose a drag at bottom
385     IF (momViscosity.AND.bottomDragTerms) THEN
386     CALL MOM_V_BOTTOMDRAG(bi,bj,k,vFld,KE,KappaRV,vF,myThid)
387     DO j=jMin,jMax
388     DO i=iMin,iMax
389     gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vF(i,j)
390     ENDDO
391     ENDDO
392     ENDIF
393    
394     C-- Metric terms for curvilinear grid systems
395     c IF (usingSphericalPolarMTerms) THEN
396     C o Spherical polar grid metric terms
397     c CALL MOM_V_METRIC_NH(bi,bj,k,vFld,wVel,mT,myThid)
398     c DO j=jMin,jMax
399     c DO i=iMin,iMax
400     c gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+mTFacV*mT(i,j)
401     c ENDDO
402     c ENDDO
403     c ENDIF
404    
405 jmc 1.5 C-- Horizontal Coriolis terms
406 adcroft 1.20 IF (useCoriolis .AND. .NOT.useCDscheme
407     & .AND. .NOT. useAbsVorticity) THEN
408     CALL MOM_VI_CORIOLIS(bi,bj,k,uFld,vFld,hFacZ,r_hFacZ,
409 jmc 1.5 & uCf,vCf,myThid)
410     DO j=jMin,jMax
411     DO i=iMin,iMax
412     gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+uCf(i,j)
413     gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vCf(i,j)
414     ENDDO
415 adcroft 1.1 ENDDO
416 jmc 1.15 IF ( writeDiag ) THEN
417     CALL WRITE_LOCAL_RL('fV','I10',1,uCf,bi,bj,k,myIter,myThid)
418     CALL WRITE_LOCAL_RL('fU','I10',1,vCf,bi,bj,k,myIter,myThid)
419     ENDIF
420 jmc 1.5 ENDIF
421 adcroft 1.1
422 jmc 1.5 IF (momAdvection) THEN
423     C-- Horizontal advection of relative vorticity
424 adcroft 1.20 IF (useAbsVorticity) THEN
425     CALL MOM_VI_U_CORIOLIS(bi,bj,K,vFld,omega3,hFacZ,r_hFacZ,
426     & uCf,myThid)
427     ELSE
428     CALL MOM_VI_U_CORIOLIS(bi,bj,k,vFld,vort3,hFacZ,r_hFacZ,
429     & uCf,myThid)
430     ENDIF
431 jmc 1.5 c CALL MOM_VI_U_CORIOLIS_C4(bi,bj,K,vFld,vort3,r_hFacZ,uCf,myThid)
432     DO j=jMin,jMax
433     DO i=iMin,iMax
434     gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+uCf(i,j)
435     ENDDO
436 adcroft 1.1 ENDDO
437 adcroft 1.20 IF (useAbsVorticity) THEN
438     CALL MOM_VI_V_CORIOLIS(bi,bj,K,uFld,omega3,hFacZ,r_hFacZ,
439     & vCf,myThid)
440     ELSE
441     CALL MOM_VI_V_CORIOLIS(bi,bj,k,uFld,vort3,hFacZ,r_hFacZ,
442     & vCf,myThid)
443     ENDIF
444 jmc 1.5 c CALL MOM_VI_V_CORIOLIS_C4(bi,bj,K,uFld,vort3,r_hFacZ,vCf,myThid)
445     DO j=jMin,jMax
446     DO i=iMin,iMax
447     gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vCf(i,j)
448     ENDDO
449 adcroft 1.1 ENDDO
450    
451 jmc 1.15 IF ( writeDiag ) THEN
452     CALL WRITE_LOCAL_RL('zV','I10',1,uCf,bi,bj,k,myIter,myThid)
453     CALL WRITE_LOCAL_RL('zU','I10',1,vCf,bi,bj,k,myIter,myThid)
454     ENDIF
455 jmc 1.7 #ifdef ALLOW_TIMEAVE
456 dimitri 1.13 #ifndef HRCUBE
457 jmc 1.7 IF (taveFreq.GT.0.) THEN
458     CALL TIMEAVE_CUMUL_1K1T(uZetatave,vCf,deltaTClock,
459     & Nr, k, bi, bj, myThid)
460     CALL TIMEAVE_CUMUL_1K1T(vZetatave,uCf,deltaTClock,
461     & Nr, k, bi, bj, myThid)
462     ENDIF
463 dimitri 1.13 #endif /* ALLOW_TIMEAVE */
464     #endif /* ndef HRCUBE */
465 jmc 1.7
466 jmc 1.5 C-- Vertical shear terms (-w*du/dr & -w*dv/dr)
467 jmc 1.12 IF ( .NOT. momImplVertAdv ) THEN
468     CALL MOM_VI_U_VERTSHEAR(bi,bj,K,uVel,wVel,uCf,myThid)
469     DO j=jMin,jMax
470     DO i=iMin,iMax
471     gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+uCf(i,j)
472     ENDDO
473 jmc 1.5 ENDDO
474 jmc 1.12 CALL MOM_VI_V_VERTSHEAR(bi,bj,K,vVel,wVel,vCf,myThid)
475     DO j=jMin,jMax
476     DO i=iMin,iMax
477     gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vCf(i,j)
478     ENDDO
479 jmc 1.5 ENDDO
480 jmc 1.12 ENDIF
481 adcroft 1.1
482     C-- Bernoulli term
483 jmc 1.5 CALL MOM_VI_U_GRAD_KE(bi,bj,K,KE,uCf,myThid)
484     DO j=jMin,jMax
485     DO i=iMin,iMax
486     gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+uCf(i,j)
487     ENDDO
488     ENDDO
489     CALL MOM_VI_V_GRAD_KE(bi,bj,K,KE,vCf,myThid)
490     DO j=jMin,jMax
491     DO i=iMin,iMax
492     gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vCf(i,j)
493     ENDDO
494 adcroft 1.1 ENDDO
495 jmc 1.15 IF ( writeDiag ) THEN
496     CALL WRITE_LOCAL_RL('KEx','I10',1,uCf,bi,bj,k,myIter,myThid)
497     CALL WRITE_LOCAL_RL('KEy','I10',1,vCf,bi,bj,k,myIter,myThid)
498     ENDIF
499    
500 jmc 1.5 C-- end if momAdvection
501     ENDIF
502    
503     C-- Set du/dt & dv/dt on boundaries to zero
504 adcroft 1.1 DO j=jMin,jMax
505     DO i=iMin,iMax
506 jmc 1.5 gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)*_maskW(i,j,k,bi,bj)
507     gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)*_maskS(i,j,k,bi,bj)
508 adcroft 1.1 ENDDO
509     ENDDO
510 jmc 1.5
511 adcroft 1.2
512 jmc 1.15 IF ( writeDiag ) THEN
513 adcroft 1.3 CALL WRITE_LOCAL_RL('Ds','I10',1,strain,bi,bj,k,myIter,myThid)
514     CALL WRITE_LOCAL_RL('Dt','I10',1,tension,bi,bj,k,myIter,myThid)
515 adcroft 1.2 CALL WRITE_LOCAL_RL('Du','I10',1,uDiss,bi,bj,k,myIter,myThid)
516     CALL WRITE_LOCAL_RL('Dv','I10',1,vDiss,bi,bj,k,myIter,myThid)
517 adcroft 1.3 CALL WRITE_LOCAL_RL('Z3','I10',1,vort3,bi,bj,k,myIter,myThid)
518 adcroft 1.20 CALL WRITE_LOCAL_RL('W3','I10',1,omega3,bi,bj,k,myIter,myThid)
519 adcroft 1.3 CALL WRITE_LOCAL_RL('KE','I10',1,KE,bi,bj,k,myIter,myThid)
520     CALL WRITE_LOCAL_RL('D','I10',1,hdiv,bi,bj,k,myIter,myThid)
521 adcroft 1.1 ENDIF
522 jmc 1.7
523 edhill 1.11 #endif /* ALLOW_MOM_VECINV */
524 adcroft 1.1
525     RETURN
526     END

  ViewVC Help
Powered by ViewVC 1.1.22