/[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.7 - (show annotations) (download)
Sun Aug 3 02:49:35 2003 UTC (20 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint51f_post, checkpoint51h_pre, branchpoint-genmake2, checkpoint51i_post, checkpoint51i_pre, checkpoint51e_post, checkpoint51f_pre, checkpoint51g_post
Branch point for: branch-genmake2
Changes since 1.6: +29 -17 lines
* changes related to hFac in vorticity advection: use S/R from aim.5l_cs/code
* add time-ave diagnostic of relative vorticity advection

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

  ViewVC Help
Powered by ViewVC 1.1.22