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

Contents of /MITgcm/pkg/mom_vecinv/mom_vecinv.F

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


Revision 1.43 - (show annotations) (download)
Sat Jul 30 22:05:36 2005 UTC (18 years, 9 months ago) by jmc
Branch: MAIN
Changes since 1.42: +12 -21 lines
Hydrostatic-Phi gradient is always added to gU,gV in timestep.F
 (was already the case if staggered-timeStep)

1 C $Header: /u/gcmpack/MITgcm/pkg/mom_vecinv/mom_vecinv.F,v 1.42 2005/06/22 00:33:14 jmc Exp $
2 C $Name: $
3
4 #include "MOM_VECINV_OPTIONS.h"
5
6 SUBROUTINE MOM_VECINV(
7 I bi,bj,iMin,iMax,jMin,jMax,k,kUp,kDown,
8 I KappaRU, KappaRV,
9 U fVerU, fVerV,
10 O guDiss, gvDiss,
11 I myTime, myIter, myThid)
12 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 #ifdef ALLOW_MNC
35 #include "MNC_PARAMS.h"
36 #endif
37 #include "GRID.h"
38 #ifdef ALLOW_TIMEAVE
39 #include "TIMEAVE_STATV.h"
40 #endif
41
42 C == Routine arguments ==
43 C fVerU :: Flux of momentum in the vertical direction, out of the upper
44 C fVerV :: face of a cell K ( flux into the cell above ).
45 C guDiss :: dissipation tendency (all explicit terms), u component
46 C gvDiss :: dissipation tendency (all explicit terms), v component
47 C bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation
48 C results will be set.
49 C kUp, kDown - Index for upper and lower layers.
50 C myThid - Instance number for this innvocation of CALC_MOM_RHS
51 _RL KappaRU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
52 _RL KappaRV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
53 _RL fVerU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
54 _RL fVerV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
55 _RL guDiss(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
56 _RL gvDiss(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
57 INTEGER kUp,kDown
58 _RL myTime
59 INTEGER myIter
60 INTEGER myThid
61 INTEGER bi,bj,iMin,iMax,jMin,jMax
62
63 #ifdef ALLOW_MOM_VECINV
64
65 C == Functions ==
66 LOGICAL DIFFERENT_MULTIPLE
67 EXTERNAL DIFFERENT_MULTIPLE
68
69 C == Local variables ==
70 _RL vF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71 _RL vrF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72 _RL uCf (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
73 _RL vCf (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
74 c _RL mT (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
75 _RL del2u(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76 _RL del2v(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77 _RL tension(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78 _RL strain(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79 _RS hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80 _RS r_hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
81 _RL uFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
82 _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
83 _RL dStar(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
84 _RL zStar(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
85 C I,J,K - Loop counters
86 INTEGER i,j,k
87 C xxxFac - On-off tracer parameters used for switching terms off.
88 _RL ArDudrFac
89 c _RL mtFacU
90 _RL ArDvdrFac
91 c _RL mtFacV
92 LOGICAL bottomDragTerms
93 LOGICAL writeDiag
94 _RL KE(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
95 _RL omega3(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
96 _RL vort3(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
97 _RL hDiv(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
98
99 #ifdef ALLOW_MNC
100 INTEGER offsets(9)
101 #endif
102
103 #ifdef ALLOW_AUTODIFF_TAMC
104 C-- only the kDown part of fverU/V is set in this subroutine
105 C-- the kUp is still required
106 C-- In the case of mom_fluxform Kup is set as well
107 C-- (at least in part)
108 fVerU(1,1,kUp) = fVerU(1,1,kUp)
109 fVerV(1,1,kUp) = fVerV(1,1,kUp)
110 #endif
111
112 writeDiag = DIFFERENT_MULTIPLE(diagFreq, myTime, deltaTClock)
113
114 #ifdef ALLOW_MNC
115 IF (useMNC .AND. snapshot_mnc .AND. writeDiag) THEN
116 IF ((bi .EQ. 1).AND.(bj .EQ. 1).AND.(k .EQ. 1)) THEN
117 CALL MNC_CW_SET_UDIM('mom_vi', -1, myThid)
118 CALL MNC_CW_RL_W_S('D','mom_vi',0,0,'T',myTime,myThid)
119 CALL MNC_CW_SET_UDIM('mom_vi', 0, myThid)
120 CALL MNC_CW_I_W_S('I','mom_vi',0,0,'iter',myIter,myThid)
121 ENDIF
122 DO i = 1,9
123 offsets(i) = 0
124 ENDDO
125 offsets(3) = k
126 C write(*,*) 'offsets = ',(offsets(i),i=1,9)
127 ENDIF
128 #endif /* ALLOW_MNC */
129
130 C Initialise intermediate terms
131 DO J=1-OLy,sNy+OLy
132 DO I=1-OLx,sNx+OLx
133 vF(i,j) = 0.
134 vrF(i,j) = 0.
135 uCf(i,j) = 0.
136 vCf(i,j) = 0.
137 c mT(i,j) = 0.
138 del2u(i,j) = 0.
139 del2v(i,j) = 0.
140 dStar(i,j) = 0.
141 zStar(i,j) = 0.
142 guDiss(i,j)= 0.
143 gvDiss(i,j)= 0.
144 vort3(i,j) = 0.
145 omega3(i,j)= 0.
146 ke(i,j) = 0.
147 #ifdef ALLOW_AUTODIFF_TAMC
148 strain(i,j) = 0. _d 0
149 tension(i,j) = 0. _d 0
150 #endif
151 ENDDO
152 ENDDO
153
154 C-- Term by term tracer parmeters
155 C o U momentum equation
156 ArDudrFac = vfFacMom*1.
157 c mTFacU = mtFacMom*1.
158 C o V momentum equation
159 ArDvdrFac = vfFacMom*1.
160 c mTFacV = mtFacMom*1.
161
162 IF ( no_slip_bottom
163 & .OR. bottomDragQuadratic.NE.0.
164 & .OR. bottomDragLinear.NE.0.) THEN
165 bottomDragTerms=.TRUE.
166 ELSE
167 bottomDragTerms=.FALSE.
168 ENDIF
169
170 C-- Calculate open water fraction at vorticity points
171 CALL MOM_CALC_HFACZ(bi,bj,k,hFacZ,r_hFacZ,myThid)
172
173 C Make local copies of horizontal flow field
174 DO j=1-OLy,sNy+OLy
175 DO i=1-OLx,sNx+OLx
176 uFld(i,j) = uVel(i,j,k,bi,bj)
177 vFld(i,j) = vVel(i,j,k,bi,bj)
178 ENDDO
179 ENDDO
180
181 C note (jmc) : Dissipation and Vort3 advection do not necesary
182 C use the same maskZ (and hFacZ) => needs 2 call(s)
183 c CALL MOM_VI_HFACZ_DISS(bi,bj,k,hFacZ,r_hFacZ,myThid)
184
185 CALL MOM_CALC_KE(bi,bj,k,2,uFld,vFld,KE,myThid)
186
187 CALL MOM_CALC_HDIV(bi,bj,k,2,uFld,vFld,hDiv,myThid)
188
189 CALL MOM_CALC_RELVORT3(bi,bj,k,uFld,vFld,hFacZ,vort3,myThid)
190
191 IF (useAbsVorticity)
192 & CALL MOM_CALC_ABSVORT3(bi,bj,k,vort3,omega3,myThid)
193
194 IF (momViscosity) THEN
195 C Calculate del^2 u and del^2 v for bi-harmonic term
196 IF ( (viscA4.NE.0. .AND. no_slip_sides)
197 & .OR. viscA4D.NE.0. .OR. viscA4Z.NE.0.
198 & .OR. viscA4Grid.NE.0.
199 & .OR. viscC4leith.NE.0.
200 & .OR. viscC4leithD.NE.0.
201 & ) THEN
202 CALL MOM_VI_DEL2UV(bi,bj,k,hDiv,vort3,hFacZ,
203 O del2u,del2v,
204 & myThid)
205 CALL MOM_CALC_HDIV(bi,bj,k,2,del2u,del2v,dStar,myThid)
206 CALL MOM_CALC_RELVORT3(
207 & bi,bj,k,del2u,del2v,hFacZ,zStar,myThid)
208 ENDIF
209 C Calculate dissipation terms for U and V equations
210 C in terms of vorticity and divergence
211 IF ( viscAhD.NE.0. .OR. viscAhZ.NE.0.
212 & .OR. viscA4D.NE.0. .OR. viscA4Z.NE.0.
213 & .OR. viscAhGrid.NE.0. .OR. viscA4Grid.NE.0.
214 & .OR. viscC2leith.NE.0. .OR. viscC4leith.NE.0.
215 & .OR. viscC2leithD.NE.0. .OR. viscC4leithD.NE.0.
216 & ) THEN
217 CALL MOM_VI_HDISSIP(bi,bj,k,hDiv,vort3,hFacZ,dStar,zStar,
218 O guDiss,gvDiss,
219 & myThid)
220 ENDIF
221 C or in terms of tension and strain
222 IF (viscAstrain.NE.0. .OR. viscAtension.NE.0.
223 O .OR. viscC2smag.ne.0) THEN
224 CALL MOM_CALC_TENSION(bi,bj,k,uFld,vFld,
225 O tension,
226 I myThid)
227 CALL MOM_CALC_STRAIN(bi,bj,k,uFld,vFld,hFacZ,
228 O strain,
229 I myThid)
230 CALL MOM_HDISSIP(bi,bj,k,
231 I tension,strain,hFacZ,viscAtension,viscAstrain,
232 O guDiss,gvDiss,
233 I myThid)
234 ENDIF
235 ENDIF
236
237 C- Return to standard hfacZ (min-4) and mask vort3 accordingly:
238 c CALL MOM_VI_MASK_VORT3(bi,bj,k,hFacZ,r_hFacZ,vort3,myThid)
239
240 C---- Zonal momentum equation starts here
241
242 C-- Vertical flux (fVer is at upper face of "u" cell)
243
244 C Eddy component of vertical flux (interior component only) -> vrF
245 IF (momViscosity.AND..NOT.implicitViscosity) THEN
246 IF ( k.LT.Nr ) THEN
247 CALL MOM_U_RVISCFLUX(bi,bj,k+1,uVel,KappaRU,vrF,myThid)
248 ENDIF
249
250 C Combine fluxes
251 DO j=jMin,jMax
252 DO i=iMin,iMax
253 fVerU(i,j,kDown) = ArDudrFac*vrF(i,j)
254 ENDDO
255 ENDDO
256
257 C-- Tendency is minus divergence of the fluxes
258 DO j=2-Oly,sNy+Oly-1
259 DO i=2-Olx,sNx+Olx-1
260 guDiss(i,j) = guDiss(i,j)
261 & -_recip_hFacW(i,j,k,bi,bj)*recip_drF(k)
262 & *recip_rAw(i,j,bi,bj)
263 & *(
264 & fVerU(i,j,kDown) - fVerU(i,j,kUp)
265 & )*rkSign
266 ENDDO
267 ENDDO
268 ENDIF
269
270 C-- No-slip and drag BCs appear as body forces in cell abutting topography
271 IF (momViscosity.AND.no_slip_sides) THEN
272 C- No-slip BCs impose a drag at walls...
273 CALL MOM_U_SIDEDRAG(bi,bj,k,uFld,del2u,hFacZ,vF,myThid)
274 DO j=jMin,jMax
275 DO i=iMin,iMax
276 guDiss(i,j) = guDiss(i,j)+vF(i,j)
277 ENDDO
278 ENDDO
279 ENDIF
280
281 C- No-slip BCs impose a drag at bottom
282 IF (momViscosity.AND.bottomDragTerms) THEN
283 CALL MOM_U_BOTTOMDRAG(bi,bj,k,uFld,KE,KappaRU,vF,myThid)
284 DO j=jMin,jMax
285 DO i=iMin,iMax
286 guDiss(i,j) = guDiss(i,j)+vF(i,j)
287 ENDDO
288 ENDDO
289 ENDIF
290
291 C-- Metric terms for curvilinear grid systems
292 c IF (usingSphericalPolarMTerms) THEN
293 C o Spherical polar grid metric terms
294 c CALL MOM_U_METRIC_NH(bi,bj,k,uFld,wVel,mT,myThid)
295 c DO j=jMin,jMax
296 c DO i=iMin,iMax
297 c gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+mTFacU*mT(i,j)
298 c ENDDO
299 c ENDDO
300 c ENDIF
301
302 C---- Meridional momentum equation starts here
303
304 C-- Vertical flux (fVer is at upper face of "v" cell)
305
306 C Eddy component of vertical flux (interior component only) -> vrF
307 IF (momViscosity.AND..NOT.implicitViscosity) THEN
308 IF ( k.LT.Nr ) THEN
309 CALL MOM_V_RVISCFLUX(bi,bj,k+1,vVel,KappaRV,vrF,myThid)
310 ENDIF
311
312 C Combine fluxes -> fVerV
313 DO j=jMin,jMax
314 DO i=iMin,iMax
315 fVerV(i,j,kDown) = ArDvdrFac*vrF(i,j)
316 ENDDO
317 ENDDO
318
319 C-- Tendency is minus divergence of the fluxes
320 DO j=jMin,jMax
321 DO i=iMin,iMax
322 gvDiss(i,j) = gvDiss(i,j)
323 & -_recip_hFacS(i,j,k,bi,bj)*recip_drF(k)
324 & *recip_rAs(i,j,bi,bj)
325 & *(
326 & fVerV(i,j,kDown) - fVerV(i,j,kUp)
327 & )*rkSign
328 ENDDO
329 ENDDO
330 ENDIF
331
332 C-- No-slip and drag BCs appear as body forces in cell abutting topography
333 IF (momViscosity.AND.no_slip_sides) THEN
334 C- No-slip BCs impose a drag at walls...
335 CALL MOM_V_SIDEDRAG(bi,bj,k,vFld,del2v,hFacZ,vF,myThid)
336 DO j=jMin,jMax
337 DO i=iMin,iMax
338 gvDiss(i,j) = gvDiss(i,j)+vF(i,j)
339 ENDDO
340 ENDDO
341 ENDIF
342 C- No-slip BCs impose a drag at bottom
343 IF (momViscosity.AND.bottomDragTerms) THEN
344 CALL MOM_V_BOTTOMDRAG(bi,bj,k,vFld,KE,KappaRV,vF,myThid)
345 DO j=jMin,jMax
346 DO i=iMin,iMax
347 gvDiss(i,j) = gvDiss(i,j)+vF(i,j)
348 ENDDO
349 ENDDO
350 ENDIF
351
352 C-- Metric terms for curvilinear grid systems
353 c IF (usingSphericalPolarMTerms) THEN
354 C o Spherical polar grid metric terms
355 c CALL MOM_V_METRIC_NH(bi,bj,k,vFld,wVel,mT,myThid)
356 c DO j=jMin,jMax
357 c DO i=iMin,iMax
358 c gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+mTFacV*mT(i,j)
359 c ENDDO
360 c ENDDO
361 c ENDIF
362
363 C-- Horizontal Coriolis terms
364 c IF (useCoriolis .AND. .NOT.useCDscheme
365 c & .AND. .NOT. useAbsVorticity) THEN
366 C- jmc: change it to keep the Coriolis terms when useAbsVorticity=T & momAdvection=F
367 IF ( useCoriolis .AND.
368 & .NOT.( useCDscheme .OR. useAbsVorticity.AND.momAdvection )
369 & ) THEN
370 IF (useAbsVorticity) THEN
371 CALL MOM_VI_U_CORIOLIS(bi,bj,K,vFld,omega3,hFacZ,r_hFacZ,
372 & uCf,myThid)
373 CALL MOM_VI_V_CORIOLIS(bi,bj,K,uFld,omega3,hFacZ,r_hFacZ,
374 & vCf,myThid)
375 ELSE
376 CALL MOM_VI_CORIOLIS(bi,bj,k,uFld,vFld,hFacZ,r_hFacZ,
377 & uCf,vCf,myThid)
378 ENDIF
379 DO j=jMin,jMax
380 DO i=iMin,iMax
381 gU(i,j,k,bi,bj) = uCf(i,j)
382 gV(i,j,k,bi,bj) = vCf(i,j)
383 ENDDO
384 ENDDO
385 IF ( writeDiag ) THEN
386 IF (snapshot_mdsio) THEN
387 CALL WRITE_LOCAL_RL('fV','I10',1,uCf,bi,bj,k,myIter,myThid)
388 CALL WRITE_LOCAL_RL('fU','I10',1,vCf,bi,bj,k,myIter,myThid)
389 ENDIF
390 #ifdef ALLOW_MNC
391 IF (useMNC .AND. snapshot_mnc) THEN
392 CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj, 'fV', uCf,
393 & offsets, myThid)
394 CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj, 'fU', vCf,
395 & offsets, myThid)
396 ENDIF
397 #endif /* ALLOW_MNC */
398 ENDIF
399 ELSE
400 DO j=jMin,jMax
401 DO i=iMin,iMax
402 gU(i,j,k,bi,bj) = 0. _d 0
403 gV(i,j,k,bi,bj) = 0. _d 0
404 ENDDO
405 ENDDO
406 ENDIF
407
408 IF (momAdvection) THEN
409 C-- Horizontal advection of relative (or absolute) vorticity
410 IF (highOrderVorticity.AND.useAbsVorticity) THEN
411 CALL MOM_VI_U_CORIOLIS_C4(bi,bj,k,vFld,omega3,r_hFacZ,
412 & uCf,myThid)
413 ELSEIF (highOrderVorticity) THEN
414 CALL MOM_VI_U_CORIOLIS_C4(bi,bj,k,vFld,vort3, r_hFacZ,
415 & uCf,myThid)
416 ELSEIF (useAbsVorticity) THEN
417 CALL MOM_VI_U_CORIOLIS(bi,bj,K,vFld,omega3,hFacZ,r_hFacZ,
418 & uCf,myThid)
419 ELSE
420 CALL MOM_VI_U_CORIOLIS(bi,bj,k,vFld,vort3, hFacZ,r_hFacZ,
421 & uCf,myThid)
422 ENDIF
423 DO j=jMin,jMax
424 DO i=iMin,iMax
425 gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+uCf(i,j)
426 ENDDO
427 ENDDO
428 IF (highOrderVorticity.AND.useAbsVorticity) THEN
429 CALL MOM_VI_V_CORIOLIS_C4(bi,bj,K,uFld,omega3,r_hFacZ,
430 & vCf,myThid)
431 ELSEIF (highOrderVorticity) THEN
432 CALL MOM_VI_V_CORIOLIS_C4(bi,bj,K,uFld,vort3, r_hFacZ,
433 & vCf,myThid)
434 ELSEIF (useAbsVorticity) THEN
435 CALL MOM_VI_V_CORIOLIS(bi,bj,K,uFld,omega3,hFacZ,r_hFacZ,
436 & vCf,myThid)
437 ELSE
438 CALL MOM_VI_V_CORIOLIS(bi,bj,k,uFld,vort3, hFacZ,r_hFacZ,
439 & vCf,myThid)
440 ENDIF
441 DO j=jMin,jMax
442 DO i=iMin,iMax
443 gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vCf(i,j)
444 ENDDO
445 ENDDO
446
447 IF ( writeDiag ) THEN
448 IF (snapshot_mdsio) THEN
449 CALL WRITE_LOCAL_RL('zV','I10',1,uCf,bi,bj,k,myIter,myThid)
450 CALL WRITE_LOCAL_RL('zU','I10',1,vCf,bi,bj,k,myIter,myThid)
451 ENDIF
452 #ifdef ALLOW_MNC
453 IF (useMNC .AND. snapshot_mnc) THEN
454 CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj, 'zV', uCf,
455 & offsets, myThid)
456 CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj, 'zU', vCf,
457 & offsets, myThid)
458 ENDIF
459 #endif /* ALLOW_MNC */
460 ENDIF
461
462 #ifdef ALLOW_TIMEAVE
463 #ifndef MINIMAL_TAVE_OUTPUT
464 IF (taveFreq.GT.0.) THEN
465 CALL TIMEAVE_CUMUL_1K1T(uZetatave,vCf,deltaTClock,
466 & Nr, k, bi, bj, myThid)
467 CALL TIMEAVE_CUMUL_1K1T(vZetatave,uCf,deltaTClock,
468 & Nr, k, bi, bj, myThid)
469 ENDIF
470 #endif /* ndef MINIMAL_TAVE_OUTPUT */
471 #endif /* ALLOW_TIMEAVE */
472
473 C-- Vertical shear terms (-w*du/dr & -w*dv/dr)
474 IF ( .NOT. momImplVertAdv ) THEN
475 CALL MOM_VI_U_VERTSHEAR(bi,bj,K,uVel,wVel,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 ENDDO
480 ENDDO
481 CALL MOM_VI_V_VERTSHEAR(bi,bj,K,vVel,wVel,vCf,myThid)
482 DO j=jMin,jMax
483 DO i=iMin,iMax
484 gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vCf(i,j)
485 ENDDO
486 ENDDO
487 ENDIF
488
489 C-- Bernoulli term
490 CALL MOM_VI_U_GRAD_KE(bi,bj,K,KE,uCf,myThid)
491 DO j=jMin,jMax
492 DO i=iMin,iMax
493 gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+uCf(i,j)
494 ENDDO
495 ENDDO
496 CALL MOM_VI_V_GRAD_KE(bi,bj,K,KE,vCf,myThid)
497 DO j=jMin,jMax
498 DO i=iMin,iMax
499 gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vCf(i,j)
500 ENDDO
501 ENDDO
502 IF ( writeDiag ) THEN
503 IF (snapshot_mdsio) THEN
504 CALL WRITE_LOCAL_RL('KEx','I10',1,uCf,bi,bj,k,myIter,myThid)
505 CALL WRITE_LOCAL_RL('KEy','I10',1,vCf,bi,bj,k,myIter,myThid)
506 ENDIF
507 #ifdef ALLOW_MNC
508 IF (useMNC .AND. snapshot_mnc) THEN
509 CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj, 'KEx', uCf,
510 & offsets, myThid)
511 CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj, 'KEy', vCf,
512 & offsets, myThid)
513 ENDIF
514 #endif /* ALLOW_MNC */
515 ENDIF
516
517 C-- end if momAdvection
518 ENDIF
519
520 C-- Set du/dt & dv/dt on boundaries to zero
521 DO j=jMin,jMax
522 DO i=iMin,iMax
523 gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)*_maskW(i,j,k,bi,bj)
524 gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)*_maskS(i,j,k,bi,bj)
525 ENDDO
526 ENDDO
527
528 #ifdef ALLOW_DEBUG
529 IF ( debugLevel .GE. debLevB
530 & .AND. k.EQ.4 .AND. myIter.EQ.nIter0
531 & .AND. nPx.EQ.1 .AND. nPy.EQ.1
532 & .AND. useCubedSphereExchange ) THEN
533 CALL DEBUG_CS_CORNER_UV( ' uDiss,vDiss from MOM_VECINV',
534 & guDiss,gvDiss, k, standardMessageUnit,bi,bj,myThid )
535 ENDIF
536 #endif /* ALLOW_DEBUG */
537
538 IF ( writeDiag ) THEN
539 IF (snapshot_mdsio) THEN
540 CALL WRITE_LOCAL_RL('Ds','I10',1,strain,bi,bj,k,myIter,myThid)
541 CALL WRITE_LOCAL_RL('Dt','I10',1,tension,bi,bj,k,myIter,
542 & myThid)
543 CALL WRITE_LOCAL_RL('Du','I10',1,guDiss,bi,bj,k,myIter,myThid)
544 CALL WRITE_LOCAL_RL('Dv','I10',1,gvDiss,bi,bj,k,myIter,myThid)
545 CALL WRITE_LOCAL_RL('Z3','I10',1,vort3,bi,bj,k,myIter,myThid)
546 CALL WRITE_LOCAL_RL('W3','I10',1,omega3,bi,bj,k,myIter,myThid)
547 CALL WRITE_LOCAL_RL('KE','I10',1,KE,bi,bj,k,myIter,myThid)
548 CALL WRITE_LOCAL_RL('D','I10',1,hdiv,bi,bj,k,myIter,myThid)
549 ENDIF
550 #ifdef ALLOW_MNC
551 IF (useMNC .AND. snapshot_mnc) THEN
552 CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Ds',strain,
553 & offsets, myThid)
554 CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Dt',tension,
555 & offsets, myThid)
556 CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Du',guDiss,
557 & offsets, myThid)
558 CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Dv',gvDiss,
559 & offsets, myThid)
560 CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Z3',vort3,
561 & offsets, myThid)
562 CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'W3',omega3,
563 & offsets, myThid)
564 CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'KE',KE,
565 & offsets, myThid)
566 CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'D', hdiv,
567 & offsets, myThid)
568 ENDIF
569 #endif /* ALLOW_MNC */
570 ENDIF
571
572 #endif /* ALLOW_MOM_VECINV */
573
574 RETURN
575 END

  ViewVC Help
Powered by ViewVC 1.1.22