/[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.24 by edhill, Thu Oct 7 21:52:29 2004 UTC revision 1.38 by jmc, Sun May 15 03:04:56 2005 UTC
# Line 7  C $Name$ Line 7  C $Name$
7       I        bi,bj,iMin,iMax,jMin,jMax,k,kUp,kDown,       I        bi,bj,iMin,iMax,jMin,jMax,k,kUp,kDown,
8       I        dPhiHydX,dPhiHydY,KappaRU,KappaRV,       I        dPhiHydX,dPhiHydY,KappaRU,KappaRV,
9       U        fVerU, fVerV,       U        fVerU, fVerV,
10         O        guDiss, gvDiss,
11       I        myTime, myIter, myThid)       I        myTime, myIter, myThid)
12  C     /==========================================================\  C     /==========================================================\
13  C     | S/R MOM_VECINV                                           |  C     | S/R MOM_VECINV                                           |
# Line 39  C     == Global variables == Line 40  C     == Global variables ==
40  #endif  #endif
41    
42  C     == Routine arguments ==  C     == Routine arguments ==
43  C     fVerU   - Flux of momentum in the vertical  C     fVerU  :: Flux of momentum in the vertical direction, out of the upper
44  C     fVerV     direction out of the upper face of a cell K  C     fVerV  :: face of a cell K ( flux into the cell above ).
 C               ( flux into the cell above ).  
45  C     dPhiHydX,Y :: Gradient (X & Y dir.) of Hydrostatic Potential  C     dPhiHydX,Y :: Gradient (X & Y dir.) of Hydrostatic Potential
46    C     guDiss :: dissipation tendency (all explicit terms), u component
47    C     gvDiss :: dissipation tendency (all explicit terms), v component
48  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
49  C                                      results will be set.  C                                      results will be set.
50  C     kUp, kDown                     - Index for upper and lower layers.  C     kUp, kDown                     - Index for upper and lower layers.
# Line 53  C     myThid - Instance number for this Line 55  C     myThid - Instance number for this
55        _RL KappaRV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL KappaRV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
56        _RL fVerU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
57        _RL fVerV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
58          _RL guDiss(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
59          _RL gvDiss(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
60        INTEGER kUp,kDown        INTEGER kUp,kDown
61        _RL     myTime        _RL     myTime
62        INTEGER myIter        INTEGER myIter
# Line 66  C     == Functions == Line 70  C     == Functions ==
70        EXTERNAL DIFFERENT_MULTIPLE        EXTERNAL DIFFERENT_MULTIPLE
71    
72  C     == Local variables ==  C     == Local variables ==
       _RL      aF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
73        _RL      vF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL      vF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
74        _RL      vrF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL      vrF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
75        _RL      uCf (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL      uCf (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76        _RL      vCf (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL      vCf (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77        _RL      mT (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  c     _RL      mT (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
       _RL      pF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
78        _RL del2u(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL del2u(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79        _RL del2v(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL del2v(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80        _RL tension(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL tension(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
81        _RL strain(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL strain(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
82        _RS hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
83        _RS r_hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS r_hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
       _RS xA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RS yA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
84        _RL uFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
85        _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
86        _RL dStar(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL dStar(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
87        _RL zStar(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL zStar(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
       _RL uDiss(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL vDiss(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
88  C     I,J,K - Loop counters  C     I,J,K - Loop counters
89        INTEGER i,j,k        INTEGER i,j,k
 C     rVelMaskOverride - Factor for imposing special surface boundary conditions  
 C                        ( set according to free-surface condition ).  
 C     hFacROpen        - Lopped cell factos used tohold fraction of open  
 C     hFacRClosed        and closed cell wall.  
       _RL  rVelMaskOverride  
90  C     xxxFac - On-off tracer parameters used for switching terms off.  C     xxxFac - On-off tracer parameters used for switching terms off.
       _RL  uDudxFac  
       _RL  AhDudxFac  
       _RL  A4DuxxdxFac  
       _RL  vDudyFac  
       _RL  AhDudyFac  
       _RL  A4DuyydyFac  
       _RL  rVelDudrFac  
91        _RL  ArDudrFac        _RL  ArDudrFac
       _RL  fuFac  
92        _RL  phxFac        _RL  phxFac
93        _RL  mtFacU  c     _RL  mtFacU
       _RL  uDvdxFac  
       _RL  AhDvdxFac  
       _RL  A4DvxxdxFac  
       _RL  vDvdyFac  
       _RL  AhDvdyFac  
       _RL  A4DvyydyFac  
       _RL  rVelDvdrFac  
94        _RL  ArDvdrFac        _RL  ArDvdrFac
       _RL  fvFac  
95        _RL  phyFac        _RL  phyFac
96        _RL  vForcFac  c     _RL  mtFacV
       _RL  mtFacV  
       _RL wVelBottomOverride  
97        LOGICAL bottomDragTerms        LOGICAL bottomDragTerms
98        LOGICAL writeDiag        LOGICAL writeDiag
99        _RL KE(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL KE(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 126  C     xxxFac - On-off tracer parameters Line 101  C     xxxFac - On-off tracer parameters
101        _RL vort3(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vort3(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
102        _RL hDiv(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL hDiv(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
103    
104    #ifdef ALLOW_MNC
105          INTEGER offsets(9)
106    #endif
107    
108  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
109  C--   only the kDown part of fverU/V is set in this subroutine  C--   only the kDown part of fverU/V is set in this subroutine
110  C--   the kUp is still required  C--   the kUp is still required
# Line 135  C--   (at least in part) Line 114  C--   (at least in part)
114        fVerV(1,1,kUp) = fVerV(1,1,kUp)        fVerV(1,1,kUp) = fVerV(1,1,kUp)
115  #endif  #endif
116    
117        rVelMaskOverride=1.        writeDiag = DIFFERENT_MULTIPLE(diagFreq, myTime, deltaTClock)
       IF ( k .EQ. 1 ) rVelMaskOverride=freeSurfFac  
       wVelBottomOverride=1.  
       IF (k.EQ.Nr) wVelBottomOverride=0.  
       writeDiag = DIFFERENT_MULTIPLE(diagFreq, myTime,  
      &                                         myTime-deltaTClock)  
118    
119  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
120        IF (useMNC .AND. snapshot_mnc .AND. writeDiag) THEN        IF (useMNC .AND. snapshot_mnc .AND. writeDiag) THEN
121          CALL MNC_CW_SET_UDIM('mom_vi', -1, myThid)          IF ((bi .EQ. 1).AND.(bj .EQ. 1).AND.(k .EQ. 1)) THEN
122          CALL MNC_CW_I_W_S('I','mom_vi',0,0,'iter',myIter,myThid)            CALL MNC_CW_SET_UDIM('mom_vi', -1, myThid)
123          CALL MNC_CW_SET_UDIM('mom_vi', 0, myThid)            CALL MNC_CW_I_W_S('I','mom_vi',0,0,'T',myIter,myThid)
124              CALL MNC_CW_SET_UDIM('mom_vi', 0, myThid)
125            ENDIF
126            DO i = 1,9
127              offsets(i) = 0
128            ENDDO
129            offsets(3) = k
130    C       write(*,*) 'offsets = ',(offsets(i),i=1,9)
131        ENDIF        ENDIF
132  #endif /*  ALLOW_MNC  */  #endif /*  ALLOW_MNC  */
133    
134  C     Initialise intermediate terms  C     Initialise intermediate terms
135        DO J=1-OLy,sNy+OLy        DO J=1-OLy,sNy+OLy
136         DO I=1-OLx,sNx+OLx         DO I=1-OLx,sNx+OLx
137          aF(i,j)   = 0.          vF(i,j)    = 0.
138          vF(i,j)   = 0.          vrF(i,j)   = 0.
         vrF(i,j)  = 0.  
139          uCf(i,j)   = 0.          uCf(i,j)   = 0.
140          vCf(i,j)   = 0.          vCf(i,j)   = 0.
141          mT(i,j)   = 0.  c       mT(i,j)    = 0.
         pF(i,j)   = 0.  
142          del2u(i,j) = 0.          del2u(i,j) = 0.
143          del2v(i,j) = 0.          del2v(i,j) = 0.
144          dStar(i,j) = 0.          dStar(i,j) = 0.
145          zStar(i,j) = 0.          zStar(i,j) = 0.
146          uDiss(i,j) = 0.          guDiss(i,j)= 0.
147          vDiss(i,j) = 0.          gvDiss(i,j)= 0.
148          vort3(i,j) = 0.          vort3(i,j) = 0.
149          omega3(i,j) = 0.          omega3(i,j)= 0.
150          ke(i,j) = 0.          ke(i,j)    = 0.
151  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
152          strain(i,j)  = 0. _d 0          strain(i,j)  = 0. _d 0
153          tension(i,j) = 0. _d 0          tension(i,j) = 0. _d 0
# Line 178  C     Initialise intermediate terms Line 157  C     Initialise intermediate terms
157    
158  C--   Term by term tracer parmeters  C--   Term by term tracer parmeters
159  C     o U momentum equation  C     o U momentum equation
       uDudxFac     = afFacMom*1.  
       AhDudxFac    = vfFacMom*1.  
       A4DuxxdxFac  = vfFacMom*1.  
       vDudyFac     = afFacMom*1.  
       AhDudyFac    = vfFacMom*1.  
       A4DuyydyFac  = vfFacMom*1.  
       rVelDudrFac  = afFacMom*1.  
160        ArDudrFac    = vfFacMom*1.        ArDudrFac    = vfFacMom*1.
161        mTFacU       = mtFacMom*1.  c     mTFacU       = mtFacMom*1.
       fuFac        = cfFacMom*1.  
162        phxFac       = pfFacMom*1.        phxFac       = pfFacMom*1.
163  C     o V momentum equation  C     o V momentum equation
       uDvdxFac     = afFacMom*1.  
       AhDvdxFac    = vfFacMom*1.  
       A4DvxxdxFac  = vfFacMom*1.  
       vDvdyFac     = afFacMom*1.  
       AhDvdyFac    = vfFacMom*1.  
       A4DvyydyFac  = vfFacMom*1.  
       rVelDvdrFac  = afFacMom*1.  
164        ArDvdrFac    = vfFacMom*1.        ArDvdrFac    = vfFacMom*1.
165        mTFacV       = mtFacMom*1.  c     mTFacV       = mtFacMom*1.
       fvFac        = cfFacMom*1.  
166        phyFac       = pfFacMom*1.        phyFac       = pfFacMom*1.
       vForcFac     = foFacMom*1.  
167    
168        IF (     no_slip_bottom        IF (     no_slip_bottom
169       &    .OR. bottomDragQuadratic.NE.0.       &    .OR. bottomDragQuadratic.NE.0.
# Line 220  C-- with stagger time stepping, grad Phi Line 182  C-- with stagger time stepping, grad Phi
182  C--   Calculate open water fraction at vorticity points  C--   Calculate open water fraction at vorticity points
183        CALL MOM_CALC_HFACZ(bi,bj,k,hFacZ,r_hFacZ,myThid)        CALL MOM_CALC_HFACZ(bi,bj,k,hFacZ,r_hFacZ,myThid)
184    
 C---- Calculate common quantities used in both U and V equations  
 C     Calculate tracer cell face open areas  
       DO j=1-OLy,sNy+OLy  
        DO i=1-OLx,sNx+OLx  
         xA(i,j) = _dyG(i,j,bi,bj)  
      &   *drF(k)*_hFacW(i,j,k,bi,bj)  
         yA(i,j) = _dxG(i,j,bi,bj)  
      &   *drF(k)*_hFacS(i,j,k,bi,bj)  
        ENDDO  
       ENDDO  
   
185  C     Make local copies of horizontal flow field  C     Make local copies of horizontal flow field
186        DO j=1-OLy,sNy+OLy        DO j=1-OLy,sNy+OLy
187         DO i=1-OLx,sNx+OLx         DO i=1-OLx,sNx+OLx
# Line 254  c     CALL MOM_VI_HFACZ_DISS(bi,bj,k,hFa Line 205  c     CALL MOM_VI_HFACZ_DISS(bi,bj,k,hFa
205    
206        IF (momViscosity) THEN        IF (momViscosity) THEN
207  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
208         IF (viscA4.NE.0.         IF ( (viscA4.NE.0. .AND. no_slip_sides)
209         &     .OR. viscA4D.NE.0. .OR. viscA4Z.NE.0.
210       &     .OR. viscA4Grid.NE.0.       &     .OR. viscA4Grid.NE.0.
211       &     .OR. viscC4leith.NE.0.       &     .OR. viscC4leith.NE.0.
212         &     .OR. viscC4leithD.NE.0.
213       &    ) THEN       &    ) THEN
214           CALL MOM_VI_DEL2UV(bi,bj,k,hDiv,vort3,hFacZ,           CALL MOM_VI_DEL2UV(bi,bj,k,hDiv,vort3,hFacZ,
215       O                      del2u,del2v,       O                      del2u,del2v,
# Line 267  C      Calculate del^2 u and del^2 v for Line 220  C      Calculate del^2 u and del^2 v for
220         ENDIF         ENDIF
221  C      Calculate dissipation terms for U and V equations  C      Calculate dissipation terms for U and V equations
222  C      in terms of vorticity and divergence  C      in terms of vorticity and divergence
223         IF (viscAh.NE.0. .OR. viscA4.NE.0.         IF (    viscAhD.NE.0. .OR. viscAhZ.NE.0.
224       &    .OR.  viscAhGrid.NE.0. .OR. viscA4Grid.NE.0.       &    .OR. viscA4D.NE.0. .OR. viscA4Z.NE.0.
225       &    .OR.  viscC2leith.NE.0. .OR. viscC4leith.NE.0.       &    .OR. viscAhGrid.NE.0. .OR. viscA4Grid.NE.0.
226         &    .OR. viscC2leith.NE.0. .OR. viscC4leith.NE.0.
227         &    .OR. viscC2leithD.NE.0. .OR. viscC4leithD.NE.0.
228       &    ) THEN       &    ) THEN
229           CALL MOM_VI_HDISSIP(bi,bj,k,hDiv,vort3,hFacZ,dStar,zStar,           CALL MOM_VI_HDISSIP(bi,bj,k,hDiv,vort3,hFacZ,dStar,zStar,
230       O                       uDiss,vDiss,       O                       guDiss,gvDiss,
231       &                       myThid)       &                       myThid)
232         ENDIF         ENDIF
233  C      or in terms of tension and strain  C      or in terms of tension and strain
234         IF (viscAstrain.NE.0. .OR. viscAtension.NE.0.) THEN         IF (viscAstrain.NE.0. .OR. viscAtension.NE.0.
235         O      .OR. viscC2smag.ne.0) THEN
236           CALL MOM_CALC_TENSION(bi,bj,k,uFld,vFld,           CALL MOM_CALC_TENSION(bi,bj,k,uFld,vFld,
237       O                         tension,       O                         tension,
238       I                         myThid)       I                         myThid)
# Line 285  C      or in terms of tension and strain Line 241  C      or in terms of tension and strain
241       I                        myThid)       I                        myThid)
242           CALL MOM_HDISSIP(bi,bj,k,           CALL MOM_HDISSIP(bi,bj,k,
243       I                    tension,strain,hFacZ,viscAtension,viscAstrain,       I                    tension,strain,hFacZ,viscAtension,viscAstrain,
244       O                    uDiss,vDiss,       O                    guDiss,gvDiss,
245       I                    myThid)       I                    myThid)
246         ENDIF         ENDIF
247        ENDIF        ENDIF
# Line 298  C---- Zonal momentum equation starts her Line 254  C---- Zonal momentum equation starts her
254  C--   Vertical flux (fVer is at upper face of "u" cell)  C--   Vertical flux (fVer is at upper face of "u" cell)
255    
256  C     Eddy component of vertical flux (interior component only) -> vrF  C     Eddy component of vertical flux (interior component only) -> vrF
257        IF (momViscosity.AND..NOT.implicitViscosity)        IF (momViscosity.AND..NOT.implicitViscosity) THEN
258       & CALL MOM_U_RVISCFLUX(bi,bj,k,uVel,KappaRU,vrF,myThid)         CALL MOM_U_RVISCFLUX(bi,bj,k,uVel,KappaRU,vrF,myThid)
259    
260  C     Combine fluxes  C     Combine fluxes
261        DO j=jMin,jMax         DO j=jMin,jMax
262         DO i=iMin,iMax          DO i=iMin,iMax
263          fVerU(i,j,kDown) = ArDudrFac*vrF(i,j)           fVerU(i,j,kDown) = ArDudrFac*vrF(i,j)
264            ENDDO
265         ENDDO         ENDDO
       ENDDO  
266    
267  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term  C--   Tendency is minus divergence of the fluxes
268        DO j=2-Oly,sNy+Oly-1         DO j=2-Oly,sNy+Oly-1
269         DO i=2-Olx,sNx+Olx-1          DO i=2-Olx,sNx+Olx-1
270          gU(i,j,k,bi,bj) = uDiss(i,j)           guDiss(i,j) = guDiss(i,j)
271       &   -_recip_hFacW(i,j,k,bi,bj)*recip_drF(k)       &   -_recip_hFacW(i,j,k,bi,bj)*recip_drF(k)
272       &   *recip_rAw(i,j,bi,bj)       &   *recip_rAw(i,j,bi,bj)
273       &  *(       &  *(
274       &   +fVerU(i,j,kUp)*rkFac - fVerU(i,j,kDown)*rkFac       &   +fVerU(i,j,kUp)*rkFac - fVerU(i,j,kDown)*rkFac
275       &   )       &   )
276       &  - phxFac*dPhiHydX(i,j)          ENDDO
277         ENDDO         ENDDO
278        ENDDO        ENDIF
279    
280  C-- No-slip and drag BCs appear as body forces in cell abutting topography  C-- No-slip and drag BCs appear as body forces in cell abutting topography
281        IF (momViscosity.AND.no_slip_sides) THEN        IF (momViscosity.AND.no_slip_sides) THEN
# Line 327  C-     No-slip BCs impose a drag at wall Line 283  C-     No-slip BCs impose a drag at wall
283         CALL MOM_U_SIDEDRAG(bi,bj,k,uFld,del2u,hFacZ,vF,myThid)         CALL MOM_U_SIDEDRAG(bi,bj,k,uFld,del2u,hFacZ,vF,myThid)
284         DO j=jMin,jMax         DO j=jMin,jMax
285          DO i=iMin,iMax          DO i=iMin,iMax
286           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+vF(i,j)           guDiss(i,j) = guDiss(i,j)+vF(i,j)
287          ENDDO          ENDDO
288         ENDDO         ENDDO
289        ENDIF        ENDIF
# Line 337  C-    No-slip BCs impose a drag at botto Line 293  C-    No-slip BCs impose a drag at botto
293         CALL MOM_U_BOTTOMDRAG(bi,bj,k,uFld,KE,KappaRU,vF,myThid)         CALL MOM_U_BOTTOMDRAG(bi,bj,k,uFld,KE,KappaRU,vF,myThid)
294         DO j=jMin,jMax         DO j=jMin,jMax
295          DO i=iMin,iMax          DO i=iMin,iMax
296           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+vF(i,j)           guDiss(i,j) = guDiss(i,j)+vF(i,j)
297          ENDDO          ENDDO
298         ENDDO         ENDDO
299        ENDIF        ENDIF
# Line 358  C---- Meridional momentum equation start Line 314  C---- Meridional momentum equation start
314  C--   Vertical flux (fVer is at upper face of "v" cell)  C--   Vertical flux (fVer is at upper face of "v" cell)
315    
316  C     Eddy component of vertical flux (interior component only) -> vrF  C     Eddy component of vertical flux (interior component only) -> vrF
317        IF (momViscosity.AND..NOT.implicitViscosity)        IF (momViscosity.AND..NOT.implicitViscosity) THEN
318       & CALL MOM_V_RVISCFLUX(bi,bj,k,vVel,KappaRV,vrf,myThid)         CALL MOM_V_RVISCFLUX(bi,bj,k,vVel,KappaRV,vrf,myThid)
319    
320  C     Combine fluxes -> fVerV  C     Combine fluxes -> fVerV
321        DO j=jMin,jMax         DO j=jMin,jMax
322         DO i=iMin,iMax          DO i=iMin,iMax
323          fVerV(i,j,kDown) = ArDvdrFac*vrF(i,j)           fVerV(i,j,kDown) = ArDvdrFac*vrF(i,j)
324            ENDDO
325         ENDDO         ENDDO
       ENDDO  
326    
327  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term  C--   Tendency is minus divergence of the fluxes
328        DO j=jMin,jMax         DO j=jMin,jMax
329         DO i=iMin,iMax          DO i=iMin,iMax
330          gV(i,j,k,bi,bj) = vDiss(i,j)           gvDiss(i,j) = gvDiss(i,j)
331       &   -_recip_hFacS(i,j,k,bi,bj)*recip_drF(k)       &   -_recip_hFacS(i,j,k,bi,bj)*recip_drF(k)
332       &    *recip_rAs(i,j,bi,bj)       &    *recip_rAs(i,j,bi,bj)
333       &  *(       &  *(
334       &   +fVerV(i,j,kUp)*rkFac - fVerV(i,j,kDown)*rkFac       &   +fVerV(i,j,kUp)*rkFac - fVerV(i,j,kDown)*rkFac
335       &   )       &   )
336       &  - phyFac*dPhiHydY(i,j)          ENDDO
337         ENDDO         ENDDO
338        ENDDO        ENDIF
339    
340  C-- No-slip and drag BCs appear as body forces in cell abutting topography  C-- No-slip and drag BCs appear as body forces in cell abutting topography
341        IF (momViscosity.AND.no_slip_sides) THEN        IF (momViscosity.AND.no_slip_sides) THEN
# Line 387  C-     No-slip BCs impose a drag at wall Line 343  C-     No-slip BCs impose a drag at wall
343         CALL MOM_V_SIDEDRAG(bi,bj,k,vFld,del2v,hFacZ,vF,myThid)         CALL MOM_V_SIDEDRAG(bi,bj,k,vFld,del2v,hFacZ,vF,myThid)
344         DO j=jMin,jMax         DO j=jMin,jMax
345          DO i=iMin,iMax          DO i=iMin,iMax
346           gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vF(i,j)           gvDiss(i,j) = gvDiss(i,j)+vF(i,j)
347          ENDDO          ENDDO
348         ENDDO         ENDDO
349        ENDIF        ENDIF
# Line 396  C-    No-slip BCs impose a drag at botto Line 352  C-    No-slip BCs impose a drag at botto
352         CALL MOM_V_BOTTOMDRAG(bi,bj,k,vFld,KE,KappaRV,vF,myThid)         CALL MOM_V_BOTTOMDRAG(bi,bj,k,vFld,KE,KappaRV,vF,myThid)
353         DO j=jMin,jMax         DO j=jMin,jMax
354          DO i=iMin,iMax          DO i=iMin,iMax
355           gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vF(i,j)           gvDiss(i,j) = gvDiss(i,j)+vF(i,j)
356          ENDDO          ENDDO
357         ENDDO         ENDDO
358        ENDIF        ENDIF
# Line 413  c      ENDDO Line 369  c      ENDDO
369  c     ENDIF  c     ENDIF
370    
371  C--   Horizontal Coriolis terms  C--   Horizontal Coriolis terms
372        IF (useCoriolis .AND. .NOT.useCDscheme  c     IF (useCoriolis .AND. .NOT.useCDscheme
373       &    .AND. .NOT. useAbsVorticity) THEN  c    &    .AND. .NOT. useAbsVorticity) THEN
374         CALL MOM_VI_CORIOLIS(bi,bj,k,uFld,vFld,hFacZ,r_hFacZ,  C- jmc: change it to keep the Coriolis terms when useAbsVorticity=T & momAdvection=F
375       &                      uCf,vCf,myThid)        IF ( useCoriolis .AND.
376         &     .NOT.( useCDscheme .OR. useAbsVorticity.AND.momAdvection )
377         &   ) THEN
378           IF (useAbsVorticity) THEN
379            CALL MOM_VI_U_CORIOLIS(bi,bj,K,vFld,omega3,hFacZ,r_hFacZ,
380         &                         uCf,myThid)
381            CALL MOM_VI_V_CORIOLIS(bi,bj,K,uFld,omega3,hFacZ,r_hFacZ,
382         &                         vCf,myThid)
383           ELSE
384            CALL MOM_VI_CORIOLIS(bi,bj,k,uFld,vFld,hFacZ,r_hFacZ,
385         &                       uCf,vCf,myThid)
386           ENDIF
387         DO j=jMin,jMax         DO j=jMin,jMax
388          DO i=iMin,iMax          DO i=iMin,iMax
389           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+uCf(i,j)           gU(i,j,k,bi,bj) = uCf(i,j) - phxFac*dPhiHydX(i,j)
390           gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+vCf(i,j)           gV(i,j,k,bi,bj) = vCf(i,j) - phyFac*dPhiHydY(i,j)
391          ENDDO          ENDDO
392         ENDDO         ENDDO
393         IF ( writeDiag ) THEN         IF ( writeDiag ) THEN
# Line 430  C--   Horizontal Coriolis terms Line 397  C--   Horizontal Coriolis terms
397           ENDIF           ENDIF
398  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
399           IF (useMNC .AND. snapshot_mnc) THEN           IF (useMNC .AND. snapshot_mnc) THEN
400             CALL MNC_CW_RL_W('D','mom_vi',0,0, 'fV', uCf, myThid)             CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj, 'fV', uCf,
401             CALL MNC_CW_RL_W('D','mom_vi',0,0, 'fU', vCf, myThid)       &          offsets, myThid)
402               CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj, 'fU', vCf,
403         &          offsets, myThid)
404           ENDIF           ENDIF
405  #endif /*  ALLOW_MNC  */  #endif /*  ALLOW_MNC  */
406         ENDIF         ENDIF
407          ELSE
408           DO j=jMin,jMax
409            DO i=iMin,iMax
410             gU(i,j,k,bi,bj) = -phxFac*dPhiHydX(i,j)
411             gV(i,j,k,bi,bj) = -phyFac*dPhiHydY(i,j)
412            ENDDO
413           ENDDO
414        ENDIF        ENDIF
415    
416        IF (momAdvection) THEN        IF (momAdvection) THEN
# Line 473  c      CALL MOM_VI_V_CORIOLIS_C4(bi,bj,K Line 449  c      CALL MOM_VI_V_CORIOLIS_C4(bi,bj,K
449           ENDIF           ENDIF
450  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
451           IF (useMNC .AND. snapshot_mnc) THEN           IF (useMNC .AND. snapshot_mnc) THEN
452             CALL MNC_CW_RL_W('D','mom_vi',0,0, 'zV', uCf, myThid)             CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj, 'zV', uCf,
453             CALL MNC_CW_RL_W('D','mom_vi',0,0, 'zU', vCf, myThid)       &          offsets, myThid)
454               CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj, 'zU', vCf,
455         &          offsets, myThid)
456           ENDIF           ENDIF
457  #endif /*  ALLOW_MNC  */  #endif /*  ALLOW_MNC  */
458         ENDIF         ENDIF
459    
460  #ifdef ALLOW_TIMEAVE  #ifdef ALLOW_TIMEAVE
461  #ifndef HRCUBE  #ifndef MINIMAL_TAVE_OUTPUT
462         IF (taveFreq.GT.0.) THEN         IF (taveFreq.GT.0.) THEN
463           CALL TIMEAVE_CUMUL_1K1T(uZetatave,vCf,deltaTClock,           CALL TIMEAVE_CUMUL_1K1T(uZetatave,vCf,deltaTClock,
464       &                           Nr, k, bi, bj, myThid)       &                           Nr, k, bi, bj, myThid)
465           CALL TIMEAVE_CUMUL_1K1T(vZetatave,uCf,deltaTClock,           CALL TIMEAVE_CUMUL_1K1T(vZetatave,uCf,deltaTClock,
466       &                           Nr, k, bi, bj, myThid)       &                           Nr, k, bi, bj, myThid)
467         ENDIF         ENDIF
468  #endif /* ndef HRCUBE */  #endif /* ndef MINIMAL_TAVE_OUTPUT */
469  #endif /* ALLOW_TIMEAVE */  #endif /* ALLOW_TIMEAVE */
470    
471  C--   Vertical shear terms (-w*du/dr & -w*dv/dr)  C--   Vertical shear terms (-w*du/dr & -w*dv/dr)
# Line 526  C--   Bernoulli term Line 504  C--   Bernoulli term
504           ENDIF           ENDIF
505  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
506           IF (useMNC .AND. snapshot_mnc) THEN           IF (useMNC .AND. snapshot_mnc) THEN
507             CALL MNC_CW_RL_W('D','mom_vi',0,0, 'KEx', uCf, myThid)             CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj, 'KEx', uCf,
508             CALL MNC_CW_RL_W('D','mom_vi',0,0, 'KEy', vCf, myThid)       &          offsets, myThid)
509           ENDIF             CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj, 'KEy', vCf,
510         &          offsets, myThid)
511            ENDIF
512  #endif /*  ALLOW_MNC  */  #endif /*  ALLOW_MNC  */
513         ENDIF         ENDIF
514    
# Line 549  C--   Set du/dt & dv/dt on boundaries to Line 529  C--   Set du/dt & dv/dt on boundaries to
529       &   .AND. nPx.EQ.1 .AND. nPy.EQ.1       &   .AND. nPx.EQ.1 .AND. nPy.EQ.1
530       &   .AND. useCubedSphereExchange ) THEN       &   .AND. useCubedSphereExchange ) THEN
531          CALL DEBUG_CS_CORNER_UV( ' uDiss,vDiss from MOM_VECINV',          CALL DEBUG_CS_CORNER_UV( ' uDiss,vDiss from MOM_VECINV',
532       &             uDiss,vDiss, k, standardMessageUnit,bi,bj,myThid )       &             guDiss,gvDiss, k, standardMessageUnit,bi,bj,myThid )
533        ENDIF        ENDIF
534  #endif /* ALLOW_DEBUG */  #endif /* ALLOW_DEBUG */
535    
# Line 558  C--   Set du/dt & dv/dt on boundaries to Line 538  C--   Set du/dt & dv/dt on boundaries to
538            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)
539            CALL WRITE_LOCAL_RL('Dt','I10',1,tension,bi,bj,k,myIter,            CALL WRITE_LOCAL_RL('Dt','I10',1,tension,bi,bj,k,myIter,
540       &         myThid)       &         myThid)
541            CALL WRITE_LOCAL_RL('Du','I10',1,uDiss,bi,bj,k,myIter,myThid)            CALL WRITE_LOCAL_RL('Du','I10',1,guDiss,bi,bj,k,myIter,myThid)
542            CALL WRITE_LOCAL_RL('Dv','I10',1,vDiss,bi,bj,k,myIter,myThid)            CALL WRITE_LOCAL_RL('Dv','I10',1,gvDiss,bi,bj,k,myIter,myThid)
543            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)
544            CALL WRITE_LOCAL_RL('W3','I10',1,omega3,bi,bj,k,myIter,myThid)            CALL WRITE_LOCAL_RL('W3','I10',1,omega3,bi,bj,k,myIter,myThid)
545            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)
# Line 567  C--   Set du/dt & dv/dt on boundaries to Line 547  C--   Set du/dt & dv/dt on boundaries to
547          ENDIF          ENDIF
548  #ifdef ALLOW_MNC  #ifdef ALLOW_MNC
549          IF (useMNC .AND. snapshot_mnc) THEN          IF (useMNC .AND. snapshot_mnc) THEN
550            CALL MNC_CW_RL_W('D','mom_vi',0,0,'Ds',strain, myThid)            CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Ds',strain,
551            CALL MNC_CW_RL_W('D','mom_vi',0,0,'Dt',tension, myThid)       &          offsets, myThid)
552            CALL MNC_CW_RL_W('D','mom_vi',0,0,'Du',uDiss, myThid)            CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Dt',tension,
553            CALL MNC_CW_RL_W('D','mom_vi',0,0,'Dv',vDiss, myThid)       &          offsets, myThid)
554            CALL MNC_CW_RL_W('D','mom_vi',0,0,'Z3',vort3, myThid)            CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Du',guDiss,
555            CALL MNC_CW_RL_W('D','mom_vi',0,0,'W3',omega3, myThid)       &          offsets, myThid)
556            CALL MNC_CW_RL_W('D','mom_vi',0,0,'KE',KE, myThid)            CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Dv',gvDiss,
557            CALL MNC_CW_RL_W('D','mom_vi',0,0,'D', hdiv, myThid)       &          offsets, myThid)
558              CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'Z3',vort3,
559         &          offsets, myThid)
560              CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'W3',omega3,
561         &          offsets, myThid)
562              CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'KE',KE,
563         &          offsets, myThid)
564              CALL MNC_CW_RL_W_OFFSET('D','mom_vi',bi,bj,'D', hdiv,
565         &          offsets, myThid)
566          ENDIF          ENDIF
567  #endif /*  ALLOW_MNC  */  #endif /*  ALLOW_MNC  */
568        ENDIF        ENDIF

Legend:
Removed from v.1.24  
changed lines
  Added in v.1.38

  ViewVC Help
Powered by ViewVC 1.1.22