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

Diff of /MITgcm/pkg/mom_vecinv/mom_vecinv.F

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

revision 1.3 by adcroft, Thu Sep 6 14:23:58 2001 UTC revision 1.14 by dimitri, Sat Feb 7 23:15:47 2004 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
4    #include "PACKAGES_CONFIG.h"
5  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
6    
7        SUBROUTINE MOM_VECINV(        SUBROUTINE MOM_VECINV(
8       I        bi,bj,iMin,iMax,jMin,jMax,k,kUp,kDown,       I        bi,bj,iMin,iMax,jMin,jMax,k,kUp,kDown,
9       I        phi_hyd,KappaRU,KappaRV,       I        dPhiHydX,dPhiHydY,KappaRU,KappaRV,
10       U        fVerU, fVerV,       U        fVerU, fVerV,
11       I        myCurrentTime, myIter, myThid)       I        myCurrentTime, myIter, myThid)
12  C     /==========================================================\  C     /==========================================================\
# Line 31  C     == Global variables == Line 32  C     == Global variables ==
32  #include "EEPARAMS.h"  #include "EEPARAMS.h"
33  #include "PARAMS.h"  #include "PARAMS.h"
34  #include "GRID.h"  #include "GRID.h"
35    #ifdef ALLOW_TIMEAVE
36    #include "TIMEAVE_STATV.h"
37    #endif
38    
39  C     == Routine arguments ==  C     == Routine arguments ==
40  C     fVerU   - Flux of momentum in the vertical  C     fVerU   - Flux of momentum in the vertical
41  C     fVerV     direction out of the upper face of a cell K  C     fVerV     direction out of the upper face of a cell K
42  C               ( flux into the cell above ).  C               ( flux into the cell above ).
43  C     phi_hyd - Hydrostatic pressure  C     dPhiHydX,Y :: Gradient (X & Y dir.) of Hydrostatic Potential
44  C     bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation  C     bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation
45  C                                      results will be set.  C                                      results will be set.
46  C     kUp, kDown                     - Index for upper and lower layers.  C     kUp, kDown                     - Index for upper and lower layers.
47  C     myThid - Instance number for this innvocation of CALC_MOM_RHS  C     myThid - Instance number for this innvocation of CALC_MOM_RHS
48        _RL phi_hyd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL dPhiHydX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
49          _RL dPhiHydY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
50        _RL KappaRU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL KappaRU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
51        _RL KappaRV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL KappaRV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
52        _RL fVerU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
# Line 52  C     myThid - Instance number for this Line 57  C     myThid - Instance number for this
57        INTEGER myThid        INTEGER myThid
58        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
59    
60    #ifdef ALLOW_MOM_VECINV
61    
62  C     == Functions ==  C     == Functions ==
63        LOGICAL  DIFFERENT_MULTIPLE        LOGICAL  DIFFERENT_MULTIPLE
64        EXTERNAL DIFFERENT_MULTIPLE        EXTERNAL DIFFERENT_MULTIPLE
# Line 72  C     == Local variables == Line 79  C     == Local variables ==
79        _RS r_hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS r_hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80        _RS xA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
81        _RS yA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
       _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
82        _RL uFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
83        _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
84        _RL dStar(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL dStar(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 111  C     xxxFac - On-off tracer parameters Line 116  C     xxxFac - On-off tracer parameters
116        _RL  phyFac        _RL  phyFac
117        _RL  vForcFac        _RL  vForcFac
118        _RL  mtFacV        _RL  mtFacV
       INTEGER km1,kp1  
119        _RL wVelBottomOverride        _RL wVelBottomOverride
120        LOGICAL bottomDragTerms        LOGICAL bottomDragTerms
121        _RL KE(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL KE(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 119  C     xxxFac - On-off tracer parameters Line 123  C     xxxFac - On-off tracer parameters
123        _RL vort3(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vort3(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
124        _RL hDiv(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL hDiv(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
125    
126        km1=MAX(1,k-1)  #ifdef ALLOW_AUTODIFF_TAMC
127        kp1=MIN(Nr,k+1)  C--   only the kDown part of fverU/V is set in this subroutine
128    C--   the kUp is still required
129    C--   In the case of mom_fluxform Kup is set as well
130    C--   (at least in part)
131          fVerU(1,1,kUp) = fVerU(1,1,kUp)
132          fVerV(1,1,kUp) = fVerV(1,1,kUp)
133    #endif
134    
135        rVelMaskOverride=1.        rVelMaskOverride=1.
136        IF ( k .EQ. 1 ) rVelMaskOverride=freeSurfFac        IF ( k .EQ. 1 ) rVelMaskOverride=freeSurfFac
137        wVelBottomOverride=1.        wVelBottomOverride=1.
# Line 145  C     Initialise intermediate terms Line 156  C     Initialise intermediate terms
156          vort3(i,j) = 0.          vort3(i,j) = 0.
157          omega3(i,j) = 0.          omega3(i,j) = 0.
158          ke(i,j) = 0.          ke(i,j) = 0.
159    #ifdef ALLOW_AUTODIFF_TAMC
160            strain(i,j)  = 0. _d 0
161            tension(i,j) = 0. _d 0
162    #endif
163         ENDDO         ENDDO
164        ENDDO        ENDDO
165    
# Line 211  C     Make local copies of horizontal fl Line 226  C     Make local copies of horizontal fl
226         ENDDO         ENDDO
227        ENDDO        ENDDO
228    
229  C     Calculate velocity field "volume transports" through tracer cell faces.  C note (jmc) : Dissipation and Vort3 advection do not necesary
230        DO j=1-OLy,sNy+OLy  C              use the same maskZ (and hFacZ)  => needs 2 call(s)
231         DO i=1-OLx,sNx+OLx  c     CALL MOM_VI_HFACZ_DISS(bi,bj,k,hFacZ,r_hFacZ,myThid)
         uTrans(i,j) = uFld(i,j)*xA(i,j)  
         vTrans(i,j) = vFld(i,j)*yA(i,j)  
        ENDDO  
       ENDDO  
232    
233        CALL MOM_VI_CALC_KE(bi,bj,k,uFld,vFld,KE,myThid)        CALL MOM_VI_CALC_KE(bi,bj,k,uFld,vFld,KE,myThid)
234    
# Line 225  C     Calculate velocity field "volume t Line 236  C     Calculate velocity field "volume t
236    
237        CALL MOM_VI_CALC_RELVORT3(bi,bj,k,uFld,vFld,hFacZ,vort3,myThid)        CALL MOM_VI_CALC_RELVORT3(bi,bj,k,uFld,vFld,hFacZ,vort3,myThid)
238    
239        CALL MOM_VI_CALC_ABSVORT3(bi,bj,k,vort3,omega3,myThid)  c     CALL MOM_VI_CALC_ABSVORT3(bi,bj,k,vort3,omega3,myThid)
240    
241        IF (momViscosity) THEN        IF (momViscosity) THEN
242  C      Calculate del^2 u and del^2 v for bi-harmonic term  C      Calculate del^2 u and del^2 v for bi-harmonic term
243         IF (viscA4.NE.0.) THEN         IF (viscA4.NE.0. .OR. viscA4Grid.NE.0.) THEN
244           CALL MOM_VI_DEL2UV(bi,bj,k,hDiv,vort3,hFacZ,           CALL MOM_VI_DEL2UV(bi,bj,k,hDiv,vort3,hFacZ,
245       O                      del2u,del2v,       O                      del2u,del2v,
246       &                      myThid)       &                      myThid)
# Line 239  C      Calculate del^2 u and del^2 v for Line 250  C      Calculate del^2 u and del^2 v for
250         ENDIF         ENDIF
251  C      Calculate dissipation terms for U and V equations  C      Calculate dissipation terms for U and V equations
252  C      in terms of vorticity and divergence  C      in terms of vorticity and divergence
253         IF (viscAh.NE.0. .OR. viscA4.NE.0.) THEN         IF (viscAh.NE.0. .OR. viscA4.NE.0. .OR.
254         &      viscAhGrid.NE.0. .OR. viscA4Grid.NE.0. ) THEN
255           CALL MOM_VI_HDISSIP(bi,bj,k,hDiv,vort3,hFacZ,dStar,zStar,           CALL MOM_VI_HDISSIP(bi,bj,k,hDiv,vort3,hFacZ,dStar,zStar,
256       O                       uDiss,vDiss,       O                       uDiss,vDiss,
257       &                       myThid)       &                       myThid)
# Line 259  C      or in terms of tension and strain Line 271  C      or in terms of tension and strain
271         ENDIF         ENDIF
272        ENDIF        ENDIF
273    
274    C-    Return to standard hfacZ (min-4) and mask vort3 accordingly:
275    c     CALL MOM_VI_MASK_VORT3(bi,bj,k,hFacZ,r_hFacZ,vort3,myThid)
276    
277  C---- Zonal momentum equation starts here  C---- Zonal momentum equation starts here
278    
279  C--   Vertical flux (fVer is at upper face of "u" cell)  C--   Vertical flux (fVer is at upper face of "u" cell)
# Line 274  C     Combine fluxes Line 289  C     Combine fluxes
289         ENDDO         ENDDO
290        ENDDO        ENDDO
291    
 C---  Hydrostatic term ( -1/rhoConst . dphi/dx )  
       IF (momPressureForcing) THEN  
        DO j=1-Olx,sNy+Oly  
         DO i=2-Olx,sNx+Olx  
          pf(i,j) = - _recip_dxC(i,j,bi,bj)  
      &    *(phi_hyd(i,j,k)-phi_hyd(i-1,j,k))  
         ENDDO  
        ENDDO  
       ENDIF  
   
292  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term
293        DO j=2-Oly,sNy+Oly-1        DO j=2-Oly,sNy+Oly-1
294         DO i=2-Olx,sNx+Olx-1         DO i=2-Olx,sNx+Olx-1
# Line 293  C--   Tendency is minus divergence of th Line 298  C--   Tendency is minus divergence of th
298       &  *(       &  *(
299       &   +fVerU(i,j,kUp)*rkFac - fVerU(i,j,kDown)*rkFac       &   +fVerU(i,j,kUp)*rkFac - fVerU(i,j,kDown)*rkFac
300       &   )       &   )
301       & _PHM( +phxFac * pf(i,j) )       &  - phxFac*dPhiHydX(i,j)
302         ENDDO         ENDDO
303        ENDDO        ENDDO
304    
# Line 307  C-     No-slip BCs impose a drag at wall Line 312  C-     No-slip BCs impose a drag at wall
312          ENDDO          ENDDO
313         ENDDO         ENDDO
314        ENDIF        ENDIF
315    
316  C-    No-slip BCs impose a drag at bottom  C-    No-slip BCs impose a drag at bottom
317        IF (momViscosity.AND.bottomDragTerms) THEN        IF (momViscosity.AND.bottomDragTerms) THEN
318         CALL MOM_U_BOTTOMDRAG(bi,bj,k,uFld,KE,KappaRU,vF,myThid)         CALL MOM_U_BOTTOMDRAG(bi,bj,k,uFld,KE,KappaRU,vF,myThid)
# Line 317  C-    No-slip BCs impose a drag at botto Line 323  C-    No-slip BCs impose a drag at botto
323         ENDDO         ENDDO
324        ENDIF        ENDIF
325    
 C--   Forcing term  
       IF (momForcing)  
      &  CALL EXTERNAL_FORCING_U(  
      I     iMin,iMax,jMin,jMax,bi,bj,k,  
      I     myCurrentTime,myThid)  
   
326  C--   Metric terms for curvilinear grid systems  C--   Metric terms for curvilinear grid systems
327  c     IF (usingSphericalPolarMTerms) THEN  c     IF (usingSphericalPolarMTerms) THEN
328  C      o Spherical polar grid metric terms  C      o Spherical polar grid metric terms
# Line 334  c       ENDDO Line 334  c       ENDDO
334  c      ENDDO  c      ENDDO
335  c     ENDIF  c     ENDIF
336    
 C--   Set du/dt on boundaries to zero  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)*_maskW(i,j,k,bi,bj)  
        ENDDO  
       ENDDO  
   
   
337  C---- Meridional momentum equation starts here  C---- Meridional momentum equation starts here
338    
339  C--   Vertical flux (fVer is at upper face of "v" cell)  C--   Vertical flux (fVer is at upper face of "v" cell)
# Line 357  C     Combine fluxes -> fVerV Line 349  C     Combine fluxes -> fVerV
349         ENDDO         ENDDO
350        ENDDO        ENDDO
351    
 C---  Hydorstatic term (-1/rhoConst . dphi/dy )  
       IF (momPressureForcing) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          pF(i,j) = -_recip_dyC(i,j,bi,bj)  
      &    *(phi_hyd(i,j,k)-phi_hyd(i,j-1,k))  
         ENDDO  
        ENDDO  
       ENDIF  
   
352  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term
353        DO j=jMin,jMax        DO j=jMin,jMax
354         DO i=iMin,iMax         DO i=iMin,iMax
# Line 376  C--   Tendency is minus divergence of th Line 358  C--   Tendency is minus divergence of th
358       &  *(       &  *(
359       &   +fVerV(i,j,kUp)*rkFac - fVerV(i,j,kDown)*rkFac       &   +fVerV(i,j,kUp)*rkFac - fVerV(i,j,kDown)*rkFac
360       &   )       &   )
361       & _PHM( +phyFac*pf(i,j) )       &  - phyFac*dPhiHydY(i,j)
362         ENDDO         ENDDO
363        ENDDO        ENDDO
364    
# Line 400  C-    No-slip BCs impose a drag at botto Line 382  C-    No-slip BCs impose a drag at botto
382         ENDDO         ENDDO
383        ENDIF        ENDIF
384    
 C--   Forcing term  
       IF (momForcing)  
      & CALL EXTERNAL_FORCING_V(  
      I     iMin,iMax,jMin,jMax,bi,bj,k,  
      I     myCurrentTime,myThid)  
   
385  C--   Metric terms for curvilinear grid systems  C--   Metric terms for curvilinear grid systems
386  c     IF (usingSphericalPolarMTerms) THEN  c     IF (usingSphericalPolarMTerms) THEN
387  C      o Spherical polar grid metric terms  C      o Spherical polar grid metric terms
# Line 417  c       ENDDO Line 393  c       ENDDO
393  c      ENDDO  c      ENDDO
394  c     ENDIF  c     ENDIF
395    
 C--   Set dv/dt on boundaries to zero  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)*_maskS(i,j,k,bi,bj)  
        ENDDO  
       ENDDO  
   
396  C--   Horizontal Coriolis terms  C--   Horizontal Coriolis terms
397        CALL MOM_VI_CORIOLIS(bi,bj,K,uFld,vFld,omega3,r_hFacZ,        IF (useCoriolis .AND. .NOT.useCDscheme) THEN
398       &                     uCf,vCf,myThid)         CALL MOM_VI_CORIOLIS(bi,bj,k,uFld,vFld,omega3,hFacZ,r_hFacZ,
399        DO j=jMin,jMax       &                      uCf,vCf,myThid)
400         DO i=iMin,iMax         DO j=jMin,jMax
401          gU(i,j,k,bi,bj) = (gU(i,j,k,bi,bj)+uCf(i,j))          DO i=iMin,iMax
402       &                    *_maskW(i,j,k,bi,bj)           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+uCf(i,j)
403          gV(i,j,k,bi,bj) = (gV(i,j,k,bi,bj)+vCf(i,j))           gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vCf(i,j)
404       &                    *_maskS(i,j,k,bi,bj)          ENDDO
        ENDDO  
       ENDDO  
 c     CALL MOM_VI_U_CORIOLIS(bi,bj,K,vFld,omega3,r_hFacZ,uCf,myThid)  
       CALL MOM_VI_U_CORIOLIS(bi,bj,K,vFld,vort3,r_hFacZ,uCf,myThid)  
 c     CALL MOM_VI_U_CORIOLIS_C4(bi,bj,K,vFld,vort3,r_hFacZ,uCf,myThid)  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         gU(i,j,k,bi,bj) = (gU(i,j,k,bi,bj)+uCf(i,j))  
      &                    *_maskW(i,j,k,bi,bj)  
        ENDDO  
       ENDDO  
 c     CALL MOM_VI_V_CORIOLIS(bi,bj,K,uFld,omega3,r_hFacZ,vCf,myThid)  
       CALL MOM_VI_V_CORIOLIS(bi,bj,K,uFld,vort3,r_hFacZ,vCf,myThid)  
 c     CALL MOM_VI_V_CORIOLIS_C4(bi,bj,K,uFld,vort3,r_hFacZ,vCf,myThid)  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         gV(i,j,k,bi,bj) = (gV(i,j,k,bi,bj)+vCf(i,j))  
      &                    *_maskS(i,j,k,bi,bj)  
405         ENDDO         ENDDO
406        ENDDO        ENDIF
407    
408        IF (momAdvection) THEN        IF (momAdvection) THEN
409  C--   Vertical shear terms (Coriolis)  C--   Horizontal advection of relative vorticity
410        CALL MOM_VI_U_VERTSHEAR(bi,bj,K,uVel,wVel,uCf,myThid)  c      CALL MOM_VI_U_CORIOLIS(bi,bj,K,vFld,omega3,r_hFacZ,uCf,myThid)
411        DO j=jMin,jMax         CALL MOM_VI_U_CORIOLIS(bi,bj,k,vFld,vort3,hFacZ,r_hFacZ,
412         DO i=iMin,iMax       &                        uCf,myThid)
413          gU(i,j,k,bi,bj) = (gU(i,j,k,bi,bj)+uCf(i,j))  c      CALL MOM_VI_U_CORIOLIS_C4(bi,bj,K,vFld,vort3,r_hFacZ,uCf,myThid)
414       &                    *_maskW(i,j,k,bi,bj)         DO j=jMin,jMax
415            DO i=iMin,iMax
416             gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+uCf(i,j)
417            ENDDO
418         ENDDO         ENDDO
419        ENDDO  c      CALL MOM_VI_V_CORIOLIS(bi,bj,K,uFld,omega3,r_hFacZ,vCf,myThid)
420        CALL MOM_VI_V_VERTSHEAR(bi,bj,K,vVel,wVel,vCf,myThid)         CALL MOM_VI_V_CORIOLIS(bi,bj,k,uFld,vort3,hFacZ,r_hFacZ,
421        DO j=jMin,jMax       &                        vCf,myThid)
422         DO i=iMin,iMax  c      CALL MOM_VI_V_CORIOLIS_C4(bi,bj,K,uFld,vort3,r_hFacZ,vCf,myThid)
423          gV(i,j,k,bi,bj) = (gV(i,j,k,bi,bj)+vCf(i,j))         DO j=jMin,jMax
424       &                    *_maskS(i,j,k,bi,bj)          DO i=iMin,iMax
425             gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vCf(i,j)
426            ENDDO
427         ENDDO         ENDDO
428        ENDDO  
429    #ifdef ALLOW_TIMEAVE
430    #ifndef HRCUBE
431           IF (taveFreq.GT.0.) THEN
432             CALL TIMEAVE_CUMUL_1K1T(uZetatave,vCf,deltaTClock,
433         &                           Nr, k, bi, bj, myThid)
434             CALL TIMEAVE_CUMUL_1K1T(vZetatave,uCf,deltaTClock,
435         &                           Nr, k, bi, bj, myThid)
436           ENDIF
437    #endif /* ALLOW_TIMEAVE */
438    #endif /* ndef HRCUBE */
439    
440    C--   Vertical shear terms (-w*du/dr & -w*dv/dr)
441           IF ( .NOT. momImplVertAdv ) THEN
442            CALL MOM_VI_U_VERTSHEAR(bi,bj,K,uVel,wVel,uCf,myThid)
443            DO j=jMin,jMax
444             DO i=iMin,iMax
445              gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+uCf(i,j)
446             ENDDO
447            ENDDO
448            CALL MOM_VI_V_VERTSHEAR(bi,bj,K,vVel,wVel,vCf,myThid)
449            DO j=jMin,jMax
450             DO i=iMin,iMax
451              gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vCf(i,j)
452             ENDDO
453            ENDDO
454           ENDIF
455    
456  C--   Bernoulli term  C--   Bernoulli term
457        CALL MOM_VI_U_GRAD_KE(bi,bj,K,KE,uCf,myThid)         CALL MOM_VI_U_GRAD_KE(bi,bj,K,KE,uCf,myThid)
458        DO j=jMin,jMax         DO j=jMin,jMax
459         DO i=iMin,iMax          DO i=iMin,iMax
460          gU(i,j,k,bi,bj) = (gU(i,j,k,bi,bj)+uCf(i,j))           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+uCf(i,j)
461       &                    *_maskW(i,j,k,bi,bj)          ENDDO
462         ENDDO         ENDDO
463        ENDDO         CALL MOM_VI_V_GRAD_KE(bi,bj,K,KE,vCf,myThid)
464        CALL MOM_VI_V_GRAD_KE(bi,bj,K,KE,vCf,myThid)         DO j=jMin,jMax
465            DO i=iMin,iMax
466             gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vCf(i,j)
467            ENDDO
468           ENDDO
469    C--   end if momAdvection
470          ENDIF
471    
472    C--   Set du/dt & dv/dt on boundaries to zero
473        DO j=jMin,jMax        DO j=jMin,jMax
474         DO i=iMin,iMax         DO i=iMin,iMax
475          gV(i,j,k,bi,bj) = (gV(i,j,k,bi,bj)+vCf(i,j))          gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)*_maskW(i,j,k,bi,bj)
476       &                    *_maskS(i,j,k,bi,bj)          gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)*_maskS(i,j,k,bi,bj)
477         ENDDO         ENDDO
478        ENDDO        ENDDO
479        ENDIF  
480    
481        IF (        IF (
482       &  DIFFERENT_MULTIPLE(diagFreq,myCurrentTime,       &  DIFFERENT_MULTIPLE(diagFreq,myCurrentTime,
483       &                     myCurrentTime-deltaTClock)       &                     myCurrentTime-deltaTClock)
484       & ) THEN       & ) THEN
        CALL WRITE_LOCAL_RL('Ph','I10',Nr,phi_hyd,bi,bj,1,myIter,myThid)  
485         CALL WRITE_LOCAL_RL('Ds','I10',1,strain,bi,bj,k,myIter,myThid)         CALL WRITE_LOCAL_RL('Ds','I10',1,strain,bi,bj,k,myIter,myThid)
486         CALL WRITE_LOCAL_RL('Dt','I10',1,tension,bi,bj,k,myIter,myThid)         CALL WRITE_LOCAL_RL('Dt','I10',1,tension,bi,bj,k,myIter,myThid)
487         CALL WRITE_LOCAL_RL('fV','I10',1,uCf,bi,bj,k,myIter,myThid)         CALL WRITE_LOCAL_RL('fV','I10',1,uCf,bi,bj,k,myIter,myThid)
# Line 500  C--   Bernoulli term Line 489  C--   Bernoulli term
489         CALL WRITE_LOCAL_RL('Du','I10',1,uDiss,bi,bj,k,myIter,myThid)         CALL WRITE_LOCAL_RL('Du','I10',1,uDiss,bi,bj,k,myIter,myThid)
490         CALL WRITE_LOCAL_RL('Dv','I10',1,vDiss,bi,bj,k,myIter,myThid)         CALL WRITE_LOCAL_RL('Dv','I10',1,vDiss,bi,bj,k,myIter,myThid)
491         CALL WRITE_LOCAL_RL('Z3','I10',1,vort3,bi,bj,k,myIter,myThid)         CALL WRITE_LOCAL_RL('Z3','I10',1,vort3,bi,bj,k,myIter,myThid)
492         CALL WRITE_LOCAL_RL('W3','I10',1,omega3,bi,bj,k,myIter,myThid)  c      CALL WRITE_LOCAL_RL('W3','I10',1,omega3,bi,bj,k,myIter,myThid)
493         CALL WRITE_LOCAL_RL('KE','I10',1,KE,bi,bj,k,myIter,myThid)         CALL WRITE_LOCAL_RL('KE','I10',1,KE,bi,bj,k,myIter,myThid)
494         CALL WRITE_LOCAL_RL('D','I10',1,hdiv,bi,bj,k,myIter,myThid)         CALL WRITE_LOCAL_RL('D','I10',1,hdiv,bi,bj,k,myIter,myThid)
495        ENDIF        ENDIF
496    
497    #endif /* ALLOW_MOM_VECINV */
498    
499        RETURN        RETURN
500        END        END

Legend:
Removed from v.1.3  
changed lines
  Added in v.1.14

  ViewVC Help
Powered by ViewVC 1.1.22