/[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.3 - (hide annotations) (download)
Thu Sep 6 14:23:58 2001 UTC (22 years, 8 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint46n_post, checkpoint47e_post, checkpoint44e_post, checkpoint46l_post, checkpoint46g_pre, checkpoint47c_post, release1_p13_pre, checkpoint46f_post, checkpoint44f_post, checkpoint46b_post, checkpoint43a-release1mods, release1_p13, checkpoint40pre9, checkpoint46l_pre, chkpt44d_post, release1_p8, release1_p9, release1_p1, release1_p2, release1_p3, release1_p4, release1_p5, release1_p6, release1_p7, checkpoint44e_pre, release1_b1, checkpoint48b_post, checkpoint43, checkpoint48c_pre, checkpoint47d_pre, release1_chkpt44d_post, checkpoint47a_post, checkpoint47i_post, release1_p11, checkpoint47d_post, icebear5, icebear4, icebear3, icebear2, checkpoint46d_pre, release1-branch_tutorials, checkpoint45d_post, checkpoint46j_pre, chkpt44a_post, checkpoint44h_pre, checkpoint46a_post, checkpoint47g_post, checkpoint46j_post, checkpoint46k_post, chkpt44c_pre, checkpoint48a_post, checkpoint45a_post, ecco_c44_e19, ecco_c44_e18, ecco_c44_e17, ecco_c44_e16, release1_p12, release1_p10, release1_p16, release1_p17, release1_p14, release1_p15, checkpoint47j_post, branch-exfmods-tag, checkpoint44g_post, checkpoint46e_pre, checkpoint48c_post, checkpoint45b_post, checkpoint46b_pre, release1-branch-end, release1_final_v1, checkpoint46c_pre, checkpoint46, checkpoint47b_post, checkpoint44b_post, checkpoint46h_pre, checkpoint46m_post, checkpoint46a_pre, checkpoint45c_post, ecco_ice2, ecco_ice1, checkpoint44h_post, checkpoint46g_post, release1_p12_pre, ecco_c44_e22, ecco_c44_e25, checkpoint47f_post, chkpt44a_pre, checkpoint46i_post, ecco_c44_e23, ecco_c44_e20, ecco_c44_e21, ecco_c44_e26, ecco_c44_e27, ecco_c44_e24, checkpoint46c_post, ecco-branch-mod1, ecco-branch-mod2, ecco-branch-mod3, ecco-branch-mod4, ecco-branch-mod5, checkpoint46e_post, release1_beta1, checkpoint44b_pre, checkpoint42, checkpoint40, checkpoint41, checkpoint47, checkpoint44, checkpoint45, checkpoint48, checkpoint46h_post, chkpt44c_post, checkpoint47h_post, checkpoint44f_pre, checkpoint46d_post, release1-branch_branchpoint
Branch point for: c24_e25_ice, branch-exfmods-curt, release1_final, release1-branch, release1, ecco-branch, release1_50yr, icebear, release1_coupled
Changes since 1.2: +22 -1 lines
Added tension/strain form of dissipation.
 * NOT working on cubed sphere.

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

  ViewVC Help
Powered by ViewVC 1.1.22