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

Annotation 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.2 - (hide annotations) (download)
Sat Feb 8 02:20:25 2003 UTC (21 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint48d_pre, checkpoint48e_post, checkpoint48d_post, checkpoint48f_post, checkpoint49, checkpoint48i_post, checkpoint48h_post, checkpoint50, checkpoint50a_post, checkpoint48g_post
Changes since 1.1: +7 -27 lines
follows cahnges in pkg/mom_vecinv: preparation for r*, grad-Phi-Hyd

1 jmc 1.2 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 jmc 1.1 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 jmc 1.2 I dPhiHydX,dPhiHydY,KappaRU,KappaRV,
9 jmc 1.1 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 jmc 1.2 C dPhiHydX,Y :: Gradient (X & Y dir.) of Hydrostatic Potential
40 jmc 1.1 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 jmc 1.2 _RL dPhiHydX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
45     _RL dPhiHydY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
46 jmc 1.1 _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---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
268     c include 'mom_vecinv.inc'
269     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
270    
271     C---- Zonal momentum equation starts here
272    
273     C-- Vertical flux (fVer is at upper face of "u" cell)
274    
275     C Eddy component of vertical flux (interior component only) -> vrF
276     IF (momViscosity.AND..NOT.implicitViscosity)
277     & CALL MOM_U_RVISCFLUX(bi,bj,k,uVel,KappaRU,vrF,myThid)
278    
279     C Combine fluxes
280     DO j=jMin,jMax
281     DO i=iMin,iMax
282     fVerU(i,j,kDown) = ArDudrFac*vrF(i,j)
283     ENDDO
284     ENDDO
285    
286     C-- Tendency is minus divergence of the fluxes + coriolis + pressure term
287     DO j=2-Oly,sNy+Oly-1
288     DO i=2-Olx,sNx+Olx-1
289     gU(i,j,k,bi,bj) = uDiss(i,j)
290     & -_recip_hFacW(i,j,k,bi,bj)*recip_drF(k)
291     & *recip_rAw(i,j,bi,bj)
292     & *(
293     & +fVerU(i,j,kUp)*rkFac - fVerU(i,j,kDown)*rkFac
294     & )
295 jmc 1.2 & - phxFac*dPhiHydX(i,j)
296 jmc 1.1 ENDDO
297     ENDDO
298    
299     C-- No-slip and drag BCs appear as body forces in cell abutting topography
300     IF (momViscosity.AND.no_slip_sides) THEN
301     C- No-slip BCs impose a drag at walls...
302     CALL MOM_U_SIDEDRAG(bi,bj,k,uFld,del2u,hFacZ,vF,myThid)
303     DO j=jMin,jMax
304     DO i=iMin,iMax
305     gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+vF(i,j)
306     ENDDO
307     ENDDO
308     ENDIF
309     C- No-slip BCs impose a drag at bottom
310     IF (momViscosity.AND.bottomDragTerms) THEN
311     CALL MOM_U_BOTTOMDRAG(bi,bj,k,uFld,KE,KappaRU,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    
319     C-- Forcing term
320     IF (momForcing)
321     & CALL EXTERNAL_FORCING_U(
322     I iMin,iMax,jMin,jMax,bi,bj,k,
323     I myCurrentTime,myThid)
324    
325     C-- Metric terms for curvilinear grid systems
326     c IF (usingSphericalPolarMTerms) THEN
327     C o Spherical polar grid metric terms
328     c CALL MOM_U_METRIC_NH(bi,bj,k,uFld,wVel,mT,myThid)
329     c DO j=jMin,jMax
330     c DO i=iMin,iMax
331     c gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+mTFacU*mT(i,j)
332     c ENDDO
333     c ENDDO
334     c ENDIF
335    
336     C-- Set du/dt on boundaries to zero
337     DO j=jMin,jMax
338     DO i=iMin,iMax
339     gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)*_maskW(i,j,k,bi,bj)
340     ENDDO
341     ENDDO
342    
343    
344     C---- Meridional momentum equation starts here
345    
346     C-- Vertical flux (fVer is at upper face of "v" cell)
347    
348     C Eddy component of vertical flux (interior component only) -> vrF
349     IF (momViscosity.AND..NOT.implicitViscosity)
350     & CALL MOM_V_RVISCFLUX(bi,bj,k,vVel,KappaRV,vrf,myThid)
351    
352     C Combine fluxes -> fVerV
353     DO j=jMin,jMax
354     DO i=iMin,iMax
355     fVerV(i,j,kDown) = ArDvdrFac*vrF(i,j)
356     ENDDO
357     ENDDO
358    
359     C-- Tendency is minus divergence of the fluxes + coriolis + pressure term
360     DO j=jMin,jMax
361     DO i=iMin,iMax
362     gV(i,j,k,bi,bj) = vDiss(i,j)
363     & -_recip_hFacS(i,j,k,bi,bj)*recip_drF(k)
364     & *recip_rAs(i,j,bi,bj)
365     & *(
366     & +fVerV(i,j,kUp)*rkFac - fVerV(i,j,kDown)*rkFac
367     & )
368 jmc 1.2 & - phyFac*dPhiHydY(i,j)
369 jmc 1.1 ENDDO
370     ENDDO
371    
372     C-- No-slip and drag BCs appear as body forces in cell abutting topography
373     IF (momViscosity.AND.no_slip_sides) THEN
374     C- No-slip BCs impose a drag at walls...
375     CALL MOM_V_SIDEDRAG(bi,bj,k,vFld,del2v,hFacZ,vF,myThid)
376     DO j=jMin,jMax
377     DO i=iMin,iMax
378     gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vF(i,j)
379     ENDDO
380     ENDDO
381     ENDIF
382     C- No-slip BCs impose a drag at bottom
383     IF (momViscosity.AND.bottomDragTerms) THEN
384     CALL MOM_V_BOTTOMDRAG(bi,bj,k,vFld,KE,KappaRV,vF,myThid)
385     DO j=jMin,jMax
386     DO i=iMin,iMax
387     gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vF(i,j)
388     ENDDO
389     ENDDO
390     ENDIF
391    
392     C-- Forcing term
393     IF (momForcing)
394     & CALL EXTERNAL_FORCING_V(
395     I iMin,iMax,jMin,jMax,bi,bj,k,
396     I myCurrentTime,myThid)
397    
398     C-- Metric terms for curvilinear grid systems
399     c IF (usingSphericalPolarMTerms) THEN
400     C o Spherical polar grid metric terms
401     c CALL MOM_V_METRIC_NH(bi,bj,k,vFld,wVel,mT,myThid)
402     c DO j=jMin,jMax
403     c DO i=iMin,iMax
404     c gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+mTFacV*mT(i,j)
405     c ENDDO
406     c ENDDO
407     c ENDIF
408    
409     C-- Set dv/dt on boundaries to zero
410     DO j=jMin,jMax
411     DO i=iMin,iMax
412     gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)*_maskS(i,j,k,bi,bj)
413     ENDDO
414     ENDDO
415    
416     C-- Horizontal Coriolis terms
417     CALL MOM_VI_MASK_VORT3(bi,bj,k,hFacZ,r_hFacZ,vort3,myThid)
418     c CALL MOM_VI_CALC_ABSVORT3(bi,bj,k,vort3,omega3,myThid)
419     CALL MOM_VI_CORIOLIS(bi,bj,k,uFld,vFld,omega3,hFacZ,r_hFacZ,
420     & uCf,vCf,myThid)
421     DO j=jMin,jMax
422     DO i=iMin,iMax
423     gU(i,j,k,bi,bj) = (gU(i,j,k,bi,bj)+uCf(i,j))
424     & *_maskW(i,j,k,bi,bj)
425     gV(i,j,k,bi,bj) = (gV(i,j,k,bi,bj)+vCf(i,j))
426     & *_maskS(i,j,k,bi,bj)
427     ENDDO
428     ENDDO
429     c CALL MOM_VI_U_CORIOLIS(bi,bj,K,vFld,omega3,r_hFacZ,uCf,myThid)
430     CALL MOM_VI_U_CORIOLIS(bi,bj,K,vFld,vort3,hFacZ,r_hFacZ,
431     & uCf,myThid)
432     c CALL MOM_VI_U_CORIOLIS_C4(bi,bj,K,vFld,vort3,r_hFacZ,uCf,myThid)
433     DO j=jMin,jMax
434     DO i=iMin,iMax
435     gU(i,j,k,bi,bj) = (gU(i,j,k,bi,bj)+uCf(i,j))
436     & *_maskW(i,j,k,bi,bj)
437     ENDDO
438     ENDDO
439     c CALL MOM_VI_V_CORIOLIS(bi,bj,K,uFld,omega3,r_hFacZ,vCf,myThid)
440     CALL MOM_VI_V_CORIOLIS(bi,bj,K,uFld,vort3,hFacZ,r_hFacZ,
441     & vCf,myThid)
442     c CALL MOM_VI_V_CORIOLIS_C4(bi,bj,K,uFld,vort3,r_hFacZ,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     & *_maskS(i,j,k,bi,bj)
447     ENDDO
448     ENDDO
449    
450     IF (momAdvection) THEN
451     C-- Vertical shear terms (Coriolis)
452     CALL MOM_VI_U_VERTSHEAR(bi,bj,K,uVel,wVel,uCf,myThid)
453     DO j=jMin,jMax
454     DO i=iMin,iMax
455     gU(i,j,k,bi,bj) = (gU(i,j,k,bi,bj)+uCf(i,j))
456     & *_maskW(i,j,k,bi,bj)
457     ENDDO
458     ENDDO
459     CALL MOM_VI_V_VERTSHEAR(bi,bj,K,vVel,wVel,vCf,myThid)
460     DO j=jMin,jMax
461     DO i=iMin,iMax
462     gV(i,j,k,bi,bj) = (gV(i,j,k,bi,bj)+vCf(i,j))
463     & *_maskS(i,j,k,bi,bj)
464     ENDDO
465     ENDDO
466    
467     C-- Bernoulli term
468     CALL MOM_VI_U_GRAD_KE(bi,bj,K,KE,uCf,myThid)
469     DO j=jMin,jMax
470     DO i=iMin,iMax
471     gU(i,j,k,bi,bj) = (gU(i,j,k,bi,bj)+uCf(i,j))
472     & *_maskW(i,j,k,bi,bj)
473     ENDDO
474     ENDDO
475     CALL MOM_VI_V_GRAD_KE(bi,bj,K,KE,vCf,myThid)
476     DO j=jMin,jMax
477     DO i=iMin,iMax
478     gV(i,j,k,bi,bj) = (gV(i,j,k,bi,bj)+vCf(i,j))
479     & *_maskS(i,j,k,bi,bj)
480     ENDDO
481     ENDDO
482     ENDIF
483    
484     IF (
485     & DIFFERENT_MULTIPLE(diagFreq,myCurrentTime,
486     & myCurrentTime-deltaTClock)
487     & ) THEN
488     CALL WRITE_LOCAL_RL('Ds','I10',1,strain,bi,bj,k,myIter,myThid)
489     CALL WRITE_LOCAL_RL('Dt','I10',1,tension,bi,bj,k,myIter,myThid)
490     CALL WRITE_LOCAL_RL('fV','I10',1,uCf,bi,bj,k,myIter,myThid)
491     CALL WRITE_LOCAL_RL('fU','I10',1,vCf,bi,bj,k,myIter,myThid)
492     CALL WRITE_LOCAL_RL('Du','I10',1,uDiss,bi,bj,k,myIter,myThid)
493     CALL WRITE_LOCAL_RL('Dv','I10',1,vDiss,bi,bj,k,myIter,myThid)
494     CALL WRITE_LOCAL_RL('Z3','I10',1,vort3,bi,bj,k,myIter,myThid)
495     CALL WRITE_LOCAL_RL('W3','I10',1,omega3,bi,bj,k,myIter,myThid)
496     CALL WRITE_LOCAL_RL('KE','I10',1,KE,bi,bj,k,myIter,myThid)
497     CALL WRITE_LOCAL_RL('D','I10',1,hdiv,bi,bj,k,myIter,myThid)
498     ENDIF
499    
500     RETURN
501     END

  ViewVC Help
Powered by ViewVC 1.1.22