/[MITgcm]/MITgcm/verification/aim.5l_cs/code/mom_vecinv.F
ViewVC logotype

Contents of /MITgcm/verification/aim.5l_cs/code/mom_vecinv.F

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


Revision 1.1.4.1 - (show annotations) (download)
Tue Feb 26 16:05:07 2002 UTC (22 years, 2 months ago) by adcroft
Branch: release1
CVS Tags: release1_p12, release1_p13, release1_p10, release1_p16, release1_p17, release1_p14, release1_p15, release1_p13_pre, release1_p12_pre, release1_p11, release1_p8, release1_p9, release1_p2, release1_p3, release1_p4, release1_p6, release1_p7, release1_p1, release1_p5, release1_chkpt44d_post
Branch point for: release1_50yr
Changes since 1.1: +2 -2 lines
Merging changes on MAIN between checkpoint43 and checkpoint43a-release1mods
Command: cvs -q update -jcheckpoint43 -jcheckpoint43a-release1mods -d -P

These changes are most of the changes between c43 and c44 except those
that occured after "12:45 11 Jan 2002". As far as I can tell it is
checkpoint43 with the following mods:

  o fix bug in mom_vi_del2uv
  o select when filters are applied ; add options to zonal_filter (data.zonfilt)  o gmredi: fix Pb in the adiabatic form ; add options (.e.g. Bolus advection)
  o update AIM experiments (NCEP input files)
  o improve and extend diagnostics (Monitor, TimeAve with NonLin-FrSurf)
  o added some stuff for AD
  o Jamar wet-points

This update does not contain the following mods that are in checkpoint44

  o bug fix in pkg/generic_advdiff/
    - thread related bug, bi,bj arguments in vertical advection routines
  o some changes to pkg/autodiff, pkg/cost, pkg/exf, pkg/ecco,
    verification/carbon and model/src/ related to adjoint
  o some new Matlab scripts for diagnosing model density
    - utils/matlab/dens_poly3.m and ini_poly3.m

The list of exclusions is accurate based on a "cvs diff". The list of
inclusions is based on the record in doc/tag-index which may not be complete.

1 C $Header: /u/gcmpack/MITgcm/verification/aim.5l_cs/code/mom_vecinv.F,v 1.1 2002/01/09 00:28:56 jmc Exp $
2 C $Name: checkpoint43a-release1mods $
3
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 I myCurrentTime, myIter, myThid)
11 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 _RL myCurrentTime
51 INTEGER myIter
52 INTEGER myThid
53 INTEGER bi,bj,iMin,iMax,jMin,jMax
54
55 C == Functions ==
56 LOGICAL DIFFERENT_MULTIPLE
57 EXTERNAL DIFFERENT_MULTIPLE
58
59 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 _RL tension(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
70 _RL strain(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71 _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 c 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 C note (jmc) : Dissipation and Vort3 advection do not necesary
223 C use the same maskZ (and hFacZ) => needs 2 call(s)
224 CALL MOM_VI_HFACZ_DISS(bi,bj,k,hFacZ,r_hFacZ,myThid)
225
226 CALL MOM_VI_CALC_KE(bi,bj,k,uFld,vFld,KE,myThid)
227
228 CALL MOM_VI_CALC_HDIV(bi,bj,k,uFld,vFld,hDiv,myThid)
229
230 CALL MOM_VI_CALC_RELVORT3(bi,bj,k,uFld,vFld,hFacZ,vort3,myThid)
231
232 c CALL MOM_VI_CALC_ABSVORT3(bi,bj,k,vort3,omega3,myThid)
233
234 IF (momViscosity) THEN
235 C Calculate del^2 u and del^2 v for bi-harmonic term
236 IF (viscA4.NE.0.) THEN
237 CALL MOM_VI_DEL2UV(bi,bj,k,hDiv,vort3,hFacZ,
238 O del2u,del2v,
239 & myThid)
240 CALL MOM_VI_CALC_HDIV(bi,bj,k,del2u,del2v,dStar,myThid)
241 CALL MOM_VI_CALC_RELVORT3(
242 & bi,bj,k,del2u,del2v,hFacZ,zStar,myThid)
243 ENDIF
244 C Calculate dissipation terms for U and V equations
245 C in terms of vorticity and divergence
246 IF (viscAh.NE.0. .OR. viscA4.NE.0.) THEN
247 CALL MOM_VI_HDISSIP(bi,bj,k,hDiv,vort3,hFacZ,dStar,zStar,
248 O uDiss,vDiss,
249 & myThid)
250 ENDIF
251 C or in terms of tension and strain
252 IF (viscAstrain.NE.0. .OR. viscAtension.NE.0.) THEN
253 CALL MOM_CALC_TENSION(bi,bj,k,uFld,vFld,
254 O tension,
255 I myThid)
256 CALL MOM_CALC_STRAIN(bi,bj,k,uFld,vFld,hFacZ,
257 O strain,
258 I myThid)
259 CALL MOM_HDISSIP(bi,bj,k,
260 I tension,strain,hFacZ,viscAtension,viscAstrain,
261 O uDiss,vDiss,
262 I myThid)
263 ENDIF
264 ENDIF
265
266 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
267 c include 'mom_vecinv.inc'
268 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
269
270 C---- Zonal momentum equation starts here
271
272 C-- Vertical flux (fVer is at upper face of "u" cell)
273
274 C Eddy component of vertical flux (interior component only) -> vrF
275 IF (momViscosity.AND..NOT.implicitViscosity)
276 & CALL MOM_U_RVISCFLUX(bi,bj,k,uVel,KappaRU,vrF,myThid)
277
278 C Combine fluxes
279 DO j=jMin,jMax
280 DO i=iMin,iMax
281 fVerU(i,j,kDown) = ArDudrFac*vrF(i,j)
282 ENDDO
283 ENDDO
284
285 C--- Hydrostatic term ( -1/rhoConst . dphi/dx )
286 IF (momPressureForcing) THEN
287 DO j=1-Olx,sNy+Oly
288 DO i=2-Olx,sNx+Olx
289 pf(i,j) = - _recip_dxC(i,j,bi,bj)
290 & *(phi_hyd(i,j,k)-phi_hyd(i-1,j,k))
291 ENDDO
292 ENDDO
293 ENDIF
294
295 C-- Tendency is minus divergence of the fluxes + coriolis + pressure term
296 DO j=2-Oly,sNy+Oly-1
297 DO i=2-Olx,sNx+Olx-1
298 gU(i,j,k,bi,bj) = uDiss(i,j)
299 & -_recip_hFacW(i,j,k,bi,bj)*recip_drF(k)
300 & *recip_rAw(i,j,bi,bj)
301 & *(
302 & +fVerU(i,j,kUp)*rkFac - fVerU(i,j,kDown)*rkFac
303 & )
304 & _PHM( +phxFac * pf(i,j) )
305 ENDDO
306 ENDDO
307
308 C-- No-slip and drag BCs appear as body forces in cell abutting topography
309 IF (momViscosity.AND.no_slip_sides) THEN
310 C- No-slip BCs impose a drag at walls...
311 CALL MOM_U_SIDEDRAG(bi,bj,k,uFld,del2u,hFacZ,vF,myThid)
312 DO j=jMin,jMax
313 DO i=iMin,iMax
314 gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+vF(i,j)
315 ENDDO
316 ENDDO
317 ENDIF
318 C- No-slip BCs impose a drag at bottom
319 IF (momViscosity.AND.bottomDragTerms) THEN
320 CALL MOM_U_BOTTOMDRAG(bi,bj,k,uFld,KE,KappaRU,vF,myThid)
321 DO j=jMin,jMax
322 DO i=iMin,iMax
323 gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+vF(i,j)
324 ENDDO
325 ENDDO
326 ENDIF
327
328 C-- Forcing term
329 IF (momForcing)
330 & CALL EXTERNAL_FORCING_U(
331 I iMin,iMax,jMin,jMax,bi,bj,k,
332 I myCurrentTime,myThid)
333
334 C-- Metric terms for curvilinear grid systems
335 c IF (usingSphericalPolarMTerms) THEN
336 C o Spherical polar grid metric terms
337 c CALL MOM_U_METRIC_NH(bi,bj,k,uFld,wVel,mT,myThid)
338 c DO j=jMin,jMax
339 c DO i=iMin,iMax
340 c gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+mTFacU*mT(i,j)
341 c ENDDO
342 c ENDDO
343 c ENDIF
344
345 C-- Set du/dt on boundaries to zero
346 DO j=jMin,jMax
347 DO i=iMin,iMax
348 gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)*_maskW(i,j,k,bi,bj)
349 ENDDO
350 ENDDO
351
352
353 C---- Meridional momentum equation starts here
354
355 C-- Vertical flux (fVer is at upper face of "v" cell)
356
357 C Eddy component of vertical flux (interior component only) -> vrF
358 IF (momViscosity.AND..NOT.implicitViscosity)
359 & CALL MOM_V_RVISCFLUX(bi,bj,k,vVel,KappaRV,vrf,myThid)
360
361 C Combine fluxes -> fVerV
362 DO j=jMin,jMax
363 DO i=iMin,iMax
364 fVerV(i,j,kDown) = ArDvdrFac*vrF(i,j)
365 ENDDO
366 ENDDO
367
368 C--- Hydorstatic term (-1/rhoConst . dphi/dy )
369 IF (momPressureForcing) THEN
370 DO j=jMin,jMax
371 DO i=iMin,iMax
372 pF(i,j) = -_recip_dyC(i,j,bi,bj)
373 & *(phi_hyd(i,j,k)-phi_hyd(i,j-1,k))
374 ENDDO
375 ENDDO
376 ENDIF
377
378 C-- Tendency is minus divergence of the fluxes + coriolis + pressure term
379 DO j=jMin,jMax
380 DO i=iMin,iMax
381 gV(i,j,k,bi,bj) = vDiss(i,j)
382 & -_recip_hFacS(i,j,k,bi,bj)*recip_drF(k)
383 & *recip_rAs(i,j,bi,bj)
384 & *(
385 & +fVerV(i,j,kUp)*rkFac - fVerV(i,j,kDown)*rkFac
386 & )
387 & _PHM( +phyFac*pf(i,j) )
388 ENDDO
389 ENDDO
390
391 C-- No-slip and drag BCs appear as body forces in cell abutting topography
392 IF (momViscosity.AND.no_slip_sides) THEN
393 C- No-slip BCs impose a drag at walls...
394 CALL MOM_V_SIDEDRAG(bi,bj,k,vFld,del2v,hFacZ,vF,myThid)
395 DO j=jMin,jMax
396 DO i=iMin,iMax
397 gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vF(i,j)
398 ENDDO
399 ENDDO
400 ENDIF
401 C- No-slip BCs impose a drag at bottom
402 IF (momViscosity.AND.bottomDragTerms) THEN
403 CALL MOM_V_BOTTOMDRAG(bi,bj,k,vFld,KE,KappaRV,vF,myThid)
404 DO j=jMin,jMax
405 DO i=iMin,iMax
406 gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vF(i,j)
407 ENDDO
408 ENDDO
409 ENDIF
410
411 C-- Forcing term
412 IF (momForcing)
413 & CALL EXTERNAL_FORCING_V(
414 I iMin,iMax,jMin,jMax,bi,bj,k,
415 I myCurrentTime,myThid)
416
417 C-- Metric terms for curvilinear grid systems
418 c IF (usingSphericalPolarMTerms) THEN
419 C o Spherical polar grid metric terms
420 c CALL MOM_V_METRIC_NH(bi,bj,k,vFld,wVel,mT,myThid)
421 c DO j=jMin,jMax
422 c DO i=iMin,iMax
423 c gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+mTFacV*mT(i,j)
424 c ENDDO
425 c ENDDO
426 c ENDIF
427
428 C-- Set dv/dt on boundaries to zero
429 DO j=jMin,jMax
430 DO i=iMin,iMax
431 gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)*_maskS(i,j,k,bi,bj)
432 ENDDO
433 ENDDO
434
435 C-- Horizontal Coriolis terms
436 CALL MOM_VI_MASK_VORT3(bi,bj,k,hFacZ,r_hFacZ,vort3,myThid)
437 c CALL MOM_VI_CALC_ABSVORT3(bi,bj,k,vort3,omega3,myThid)
438 CALL MOM_VI_CORIOLIS(bi,bj,k,uFld,vFld,omega3,hFacZ,r_hFacZ,
439 & uCf,vCf,myThid)
440 DO j=jMin,jMax
441 DO i=iMin,iMax
442 gU(i,j,k,bi,bj) = (gU(i,j,k,bi,bj)+uCf(i,j))
443 & *_maskW(i,j,k,bi,bj)
444 gV(i,j,k,bi,bj) = (gV(i,j,k,bi,bj)+vCf(i,j))
445 & *_maskS(i,j,k,bi,bj)
446 ENDDO
447 ENDDO
448 c CALL MOM_VI_U_CORIOLIS(bi,bj,K,vFld,omega3,r_hFacZ,uCf,myThid)
449 CALL MOM_VI_U_CORIOLIS(bi,bj,K,vFld,vort3,hFacZ,r_hFacZ,
450 & uCf,myThid)
451 c CALL MOM_VI_U_CORIOLIS_C4(bi,bj,K,vFld,vort3,r_hFacZ,uCf,myThid)
452 DO j=jMin,jMax
453 DO i=iMin,iMax
454 gU(i,j,k,bi,bj) = (gU(i,j,k,bi,bj)+uCf(i,j))
455 & *_maskW(i,j,k,bi,bj)
456 ENDDO
457 ENDDO
458 c CALL MOM_VI_V_CORIOLIS(bi,bj,K,uFld,omega3,r_hFacZ,vCf,myThid)
459 CALL MOM_VI_V_CORIOLIS(bi,bj,K,uFld,vort3,hFacZ,r_hFacZ,
460 & vCf,myThid)
461 c CALL MOM_VI_V_CORIOLIS_C4(bi,bj,K,uFld,vort3,r_hFacZ,vCf,myThid)
462 DO j=jMin,jMax
463 DO i=iMin,iMax
464 gV(i,j,k,bi,bj) = (gV(i,j,k,bi,bj)+vCf(i,j))
465 & *_maskS(i,j,k,bi,bj)
466 ENDDO
467 ENDDO
468
469 IF (momAdvection) THEN
470 C-- Vertical shear terms (Coriolis)
471 CALL MOM_VI_U_VERTSHEAR(bi,bj,K,uVel,wVel,uCf,myThid)
472 DO j=jMin,jMax
473 DO i=iMin,iMax
474 gU(i,j,k,bi,bj) = (gU(i,j,k,bi,bj)+uCf(i,j))
475 & *_maskW(i,j,k,bi,bj)
476 ENDDO
477 ENDDO
478 CALL MOM_VI_V_VERTSHEAR(bi,bj,K,vVel,wVel,vCf,myThid)
479 DO j=jMin,jMax
480 DO i=iMin,iMax
481 gV(i,j,k,bi,bj) = (gV(i,j,k,bi,bj)+vCf(i,j))
482 & *_maskS(i,j,k,bi,bj)
483 ENDDO
484 ENDDO
485
486 C-- Bernoulli term
487 CALL MOM_VI_U_GRAD_KE(bi,bj,K,KE,uCf,myThid)
488 DO j=jMin,jMax
489 DO i=iMin,iMax
490 gU(i,j,k,bi,bj) = (gU(i,j,k,bi,bj)+uCf(i,j))
491 & *_maskW(i,j,k,bi,bj)
492 ENDDO
493 ENDDO
494 CALL MOM_VI_V_GRAD_KE(bi,bj,K,KE,vCf,myThid)
495 DO j=jMin,jMax
496 DO i=iMin,iMax
497 gV(i,j,k,bi,bj) = (gV(i,j,k,bi,bj)+vCf(i,j))
498 & *_maskS(i,j,k,bi,bj)
499 ENDDO
500 ENDDO
501 ENDIF
502
503 IF (
504 & DIFFERENT_MULTIPLE(diagFreq,myCurrentTime,
505 & myCurrentTime-deltaTClock)
506 & ) THEN
507 CALL WRITE_LOCAL_RL('Ph','I10',Nr,phi_hyd,bi,bj,1,myIter,myThid)
508 CALL WRITE_LOCAL_RL('Ds','I10',1,strain,bi,bj,k,myIter,myThid)
509 CALL WRITE_LOCAL_RL('Dt','I10',1,tension,bi,bj,k,myIter,myThid)
510 CALL WRITE_LOCAL_RL('fV','I10',1,uCf,bi,bj,k,myIter,myThid)
511 CALL WRITE_LOCAL_RL('fU','I10',1,vCf,bi,bj,k,myIter,myThid)
512 CALL WRITE_LOCAL_RL('Du','I10',1,uDiss,bi,bj,k,myIter,myThid)
513 CALL WRITE_LOCAL_RL('Dv','I10',1,vDiss,bi,bj,k,myIter,myThid)
514 CALL WRITE_LOCAL_RL('Z3','I10',1,vort3,bi,bj,k,myIter,myThid)
515 CALL WRITE_LOCAL_RL('W3','I10',1,omega3,bi,bj,k,myIter,myThid)
516 CALL WRITE_LOCAL_RL('KE','I10',1,KE,bi,bj,k,myIter,myThid)
517 CALL WRITE_LOCAL_RL('D','I10',1,hdiv,bi,bj,k,myIter,myThid)
518 ENDIF
519
520 RETURN
521 END

  ViewVC Help
Powered by ViewVC 1.1.22