/[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.4 - (show annotations) (download)
Thu Apr 17 13:49:41 2003 UTC (21 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint50e_post, checkpoint50c_post, checkpoint50g_post, checkpoint51b_post, checkpoint50d_pre, checkpoint51, checkpoint50d_post, checkpoint51b_pre, checkpoint50c_pre, checkpoint50b_post, checkpoint51c_post, checkpoint50f_post, checkpoint50f_pre, checkpoint51d_post, checkpoint51a_post, checkpoint50e_pre, checkpoint50i_post
Changes since 1.3: +13 -14 lines
  move forcing & CD-scheme calls from mom_fluxform & mom_vecinv
  to timestep.F

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

  ViewVC Help
Powered by ViewVC 1.1.22