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

Diff of /MITgcm/pkg/mom_fluxform/mom_fluxform.F

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

revision 1.2 by adcroft, Fri Aug 17 18:40:30 2001 UTC revision 1.21 by jmc, Fri Oct 29 16:25:37 2004 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
4  #include "CPP_OPTIONS.h"  CBOI
5    C !TITLE: pkg/mom\_advdiff
6    C !AUTHORS: adcroft@mit.edu
7    C !INTRODUCTION: Flux-form Momentum Equations Package
8    C
9    C Package "mom\_fluxform" provides methods for calculating explicit terms
10    C in the momentum equation cast in flux-form:
11    C \begin{eqnarray*}
12    C G^u & = & -\frac{1}{\rho} \partial_x \phi_h
13    C           -\nabla \cdot {\bf v} u
14    C           -fv
15    C           +\frac{1}{\rho} \nabla \cdot {\bf \tau}^x
16    C           + \mbox{metrics}
17    C \\
18    C G^v & = & -\frac{1}{\rho} \partial_y \phi_h
19    C           -\nabla \cdot {\bf v} v
20    C           +fu
21    C           +\frac{1}{\rho} \nabla \cdot {\bf \tau}^y
22    C           + \mbox{metrics}
23    C \end{eqnarray*}
24    C where ${\bf v}=(u,v,w)$ and $\tau$, the stress tensor, includes surface
25    C stresses as well as internal viscous stresses.
26    CEOI
27    
28    #include "MOM_FLUXFORM_OPTIONS.h"
29    
30    CBOP
31    C !ROUTINE: MOM_FLUXFORM
32    
33    C !INTERFACE: ==========================================================
34        SUBROUTINE MOM_FLUXFORM(        SUBROUTINE MOM_FLUXFORM(
35       I        bi,bj,iMin,iMax,jMin,jMax,k,kUp,kDown,       I        bi,bj,iMin,iMax,jMin,jMax,k,kUp,kDown,
36       I        phi_hyd,KappaRU,KappaRV,       I        dPhihydX,dPhiHydY,KappaRU,KappaRV,
37       U        fVerU, fVerV,       U        fVerU, fVerV,
38       I        myCurrentTime, myIter, myThid)       I        myTime,myIter,myThid)
39  C     /==========================================================\  
40  C     | S/R MOM_FLUXFORM                                         |  C !DESCRIPTION:
41  C     | o Form the right hand-side of the momentum equation.     |  C Calculates all the horizontal accelerations except for the implicit surface
42  C     |==========================================================|  C pressure gradient and implciit vertical viscosity.
 C     | Terms are evaluated one layer at a time working from     |  
 C     | the bottom to the top. The vertically integrated         |  
 C     | barotropic flow tendency term is evluated by summing the |  
 C     | tendencies.                                              |  
 C     | Notes:                                                   |  
 C     | We have not sorted out an entirely satisfactory formula  |  
 C     | for the diffusion equation bc with lopping. The present  |  
 C     | form produces a diffusive flux that does not scale with  |  
 C     | open-area. Need to do something to solidfy this and to   |  
 C     | deal "properly" with thin walls.                         |  
 C     \==========================================================/  
       IMPLICIT NONE  
43    
44    C !USES: ===============================================================
45  C     == Global variables ==  C     == Global variables ==
46          IMPLICIT NONE
47  #include "SIZE.h"  #include "SIZE.h"
48  #include "DYNVARS.h"  #include "DYNVARS.h"
49  #include "FFIELDS.h"  #include "FFIELDS.h"
# Line 34  C     == Global variables == Line 52  C     == Global variables ==
52  #include "GRID.h"  #include "GRID.h"
53  #include "SURFACE.h"  #include "SURFACE.h"
54    
55  C     == Routine arguments ==  C !INPUT PARAMETERS: ===================================================
56  C     fZon    - Work array for flux of momentum in the east-west  C  bi,bj                :: tile indices
57  C               direction at the west face of a cell.  C  iMin,iMax,jMin,jMAx  :: loop ranges
58  C     fMer    - Work array for flux of momentum in the north-south  C  k                    :: vertical level
59  C               direction at the south face of a cell.  C  kUp                  :: =1 or 2 for consecutive k
60  C     fVerU   - Flux of momentum in the vertical  C  kDown                :: =2 or 1 for consecutive k
61  C     fVerV     direction out of the upper face of a cell K  C  dPhiHydX,Y           :: Gradient (X & Y dir.) of Hydrostatic Potential
62  C               ( flux into the cell above ).  C  KappaRU              :: vertical viscosity
63  C     phi_hyd - Hydrostatic pressure  C  KappaRV              :: vertical viscosity
64  C     bi, bj, iMin, iMax, jMin, jMax - Range of points for which calculation  C  fVerU                :: vertical flux of U, 2 1/2 dim for pipe-lining
65  C                                      results will be set.  C  fVerV                :: vertical flux of V, 2 1/2 dim for pipe-lining
66  C     kUp, kDown                     - Index for upper and lower layers.  C  myTime               :: current time
67  C     myThid - Instance number for this innvocation of CALC_MOM_RHS  C  myIter               :: current time-step number
68        _RL phi_hyd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)  C  myThid               :: thread number
69          INTEGER bi,bj,iMin,iMax,jMin,jMax
70          INTEGER k,kUp,kDown
71          _RL dPhiHydX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72          _RL dPhiHydY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
73        _RL KappaRU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL KappaRU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
74        _RL KappaRV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL KappaRV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
75        _RL fVerU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerU(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
76        _RL fVerV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerV(1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
77        INTEGER kUp,kDown        _RL     myTime
       _RL     myCurrentTime  
78        INTEGER myIter        INTEGER myIter
79        INTEGER myThid        INTEGER myThid
       INTEGER bi,bj,iMin,iMax,jMin,jMax  
80    
81  C     == Local variables ==  C !OUTPUT PARAMETERS: ==================================================
82  C     ab15, ab05    - Weights for Adams-Bashforth time stepping scheme.  C None - updates gU() and gV() in common blocks
83  C     i,j,k         - Loop counters  
84    C !LOCAL VARIABLES: ====================================================
85    C  i,j                  :: loop indices
86    C  aF                   :: advective flux
87    C  vF                   :: viscous flux
88    C  v4F                  :: bi-harmonic viscous flux
89    C  vrF                  :: vertical viscous flux
90    C  cF                   :: Coriolis acceleration
91    C  mT                   :: Metric terms
92    C  pF                   :: Pressure gradient
93    C  fZon                 :: zonal fluxes
94    C  fMer                 :: meridional fluxes
95          INTEGER i,j
96          _RL aF(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
97          _RL vF(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
98          _RL v4F(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
99          _RL vrF(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
100          _RL cF(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
101          _RL mT(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
102          _RL pF(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
103          _RL fZon(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
104          _RL fMer(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
105  C     wMaskOverride - Land sea flag override for top layer.  C     wMaskOverride - Land sea flag override for top layer.
106  C     afFacMom      - Tracer parameters for turning terms  C     afFacMom      - Tracer parameters for turning terms
107  C     vfFacMom        on and off.  C     vfFacMom        on and off.
# Line 70  C     mTFacMom        pfFacMom - Pressur Line 111  C     mTFacMom        pfFacMom - Pressur
111  C                     cfFacMom - Coriolis terms  C                     cfFacMom - Coriolis terms
112  C                     foFacMom - Forcing  C                     foFacMom - Forcing
113  C                     mTFacMom - Metric term  C                     mTFacMom - Metric term
 C     vF            - Temporary holding viscous term (Laplacian)  
 C     v4F           - Temporary holding viscous term (Biharmonic)  
 C     cF            - Temporary holding coriolis term.  
 C     mT            - Temporary holding metric terms(s).  
 C     pF            - Temporary holding pressure|potential gradient terms.  
114  C     uDudxFac, AhDudxFac, etc ... individual term tracer parameters  C     uDudxFac, AhDudxFac, etc ... individual term tracer parameters
       _RL      aF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL      vF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL      v4F(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL      vrF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL      cF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL      mT (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL      pF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL    fZon (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL    fMer (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
115        _RS    hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS    hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
116        _RS  r_hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS  r_hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
117        _RS      xA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS      xA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 93  C     uDudxFac, AhDudxFac, etc ... indiv Line 120  C     uDudxFac, AhDudxFac, etc ... indiv
120        _RL  vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL  vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
121        _RL  uFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL  uFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
122        _RL  vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL  vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
123          _RL  rTransU(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
124          _RL  rTransV(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
125          _RL KE(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
126    c     _RL viscAh_D(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
127    c     _RL viscAh_Z(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
128    c     _RL viscA4_D(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
129    c     _RL viscA4_Z(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
130    c     _RL vort3(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
131    c     _RL hDiv(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
132          _RL strain(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
133          _RL tension(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
134  C     I,J,K - Loop counters  C     I,J,K - Loop counters
       INTEGER i,j,k  
135  C     rVelMaskOverride - Factor for imposing special surface boundary conditions  C     rVelMaskOverride - Factor for imposing special surface boundary conditions
136  C                        ( set according to free-surface condition ).  C                        ( set according to free-surface condition ).
137  C     hFacROpen        - Lopped cell factos used tohold fraction of open  C     hFacROpen        - Lopped cell factos used tohold fraction of open
# Line 124  C     xxxFac - On-off tracer parameters Line 161  C     xxxFac - On-off tracer parameters
161        _RL  phyFac        _RL  phyFac
162        _RL  vForcFac        _RL  vForcFac
163        _RL  mtFacV        _RL  mtFacV
 C     ab05, ab15 - Adams-Bashforth time-stepping weights.  
       _RL  ab05, ab15  
164        INTEGER km1,kp1        INTEGER km1,kp1
165        _RL wVelBottomOverride        _RL wVelBottomOverride
166        LOGICAL bottomDragTerms        LOGICAL bottomDragTerms
167        _RL KE(1-OLx:sNx+OLx,1-OLy:sNy+OLy)  CEOP
168    
169        km1=MAX(1,k-1)        km1=MAX(1,k-1)
170        kp1=MIN(Nr,k+1)        kp1=MIN(Nr,k+1)
# Line 150  C     Initialise intermediate terms Line 185  C     Initialise intermediate terms
185          pF(i,j)   = 0.          pF(i,j)   = 0.
186          fZon(i,j) = 0.          fZon(i,j) = 0.
187          fMer(i,j) = 0.          fMer(i,j) = 0.
188            rTransU(i,j) = 0.
189            rTransV(i,j) = 0.
190            strain(i,j) = 0.
191            tension(i,j) = 0.
192         ENDDO         ENDDO
193        ENDDO        ENDDO
194    
# Line 194  C-- with stagger time stepping, grad Phi Line 233  C-- with stagger time stepping, grad Phi
233          phyFac = 0.          phyFac = 0.
234        ENDIF        ENDIF
235    
 C--   Adams-Bashforth weighting factors  
       ab15   =  1.5 _d 0 + abEps  
       ab05   = -0.5 _d 0 - abEps  
     
236  C--   Calculate open water fraction at vorticity points  C--   Calculate open water fraction at vorticity points
237        CALL MOM_CALC_HFACZ(bi,bj,k,hFacZ,r_hFacZ,myThid)        CALL MOM_CALC_HFACZ(bi,bj,k,hFacZ,r_hFacZ,myThid)
238    
# Line 228  C     Calculate velocity field "volume t Line 263  C     Calculate velocity field "volume t
263         ENDDO         ENDDO
264        ENDDO        ENDDO
265    
266        CALL MOM_CALC_KE(bi,bj,k,uFld,vFld,KE,myThid)        CALL MOM_CALC_KE(bi,bj,k,3,uFld,vFld,KE,myThid)
267    
268          IF (viscAstrain.NE.0. .OR. viscAtension.NE.0.) THEN
269             CALL MOM_CALC_TENSION(bi,bj,k,uFld,vFld,
270         O                         tension,
271         I                         myThid)
272             CALL MOM_CALC_STRAIN(bi,bj,k,uFld,vFld,hFacZ,
273         O                        strain,
274         I                        myThid)
275          ENDIF
276    
277    C---  First call (k=1): compute vertical adv. flux fVerU(kUp) & fVerV(kUp)
278          IF (momAdvection.AND.k.EQ.1) THEN
279    
280    C-    Calculate vertical transports above U & V points (West & South face):
281           CALL MOM_CALC_RTRANS( k, bi, bj,
282         O                       rTransU, rTransV,
283         I                       myTime, myIter, myThid)
284    
285    C-    Free surface correction term (flux at k=1)
286           CALL MOM_U_ADV_WU(bi,bj,k,uVel,wVel,rTransU,af,myThid)
287           DO j=jMin,jMax
288            DO i=iMin,iMax
289             fVerU(i,j,kUp) = af(i,j)
290            ENDDO
291           ENDDO
292    
293           CALL MOM_V_ADV_WV(bi,bj,k,vVel,wVel,rTransV,af,myThid)
294           DO j=jMin,jMax
295            DO i=iMin,iMax
296             fVerV(i,j,kUp) = af(i,j)
297            ENDDO
298           ENDDO
299    
300    C---  endif momAdvection & k=1
301          ENDIF
302    
303    
304    C---  Calculate vertical transports (at k+1) below U & V points :
305          IF (momAdvection) THEN
306           CALL MOM_CALC_RTRANS( k+1, bi, bj,
307         O                       rTransU, rTransV,
308         I                       myTime, myIter, myThid)
309          ENDIF
310    
311    c     IF (momViscosity) THEN
312    c    &  CALL MOM_CALC_VISCOSITY(bi,bj,k,
313    c    I                         uFld,vFld,
314    c    O                         viscAh_D,viscAh_Z,myThid)
315    
316  C---- Zonal momentum equation starts here  C---- Zonal momentum equation starts here
317    
318  C     Bi-harmonic term del^2 U -> v4F  C     Bi-harmonic term del^2 U -> v4F
319        IF (momViscosity)        IF (momViscosity .AND. viscA4.NE.0. )
320       & CALL MOM_U_DEL2U(bi,bj,k,uFld,hFacZ,v4f,myThid)       & CALL MOM_U_DEL2U(bi,bj,k,uFld,hFacZ,v4f,myThid)
321    
322  C---  Calculate mean and eddy fluxes between cells for zonal flow.  C---  Calculate mean and eddy fluxes between cells for zonal flow.
# Line 266  C     Laplacian and bi-harmonic term Line 349  C     Laplacian and bi-harmonic term
349       & CALL MOM_U_YVISCFLUX(bi,bj,k,uFld,v4F,hFacZ,vF,myThid)       & CALL MOM_U_YVISCFLUX(bi,bj,k,uFld,v4F,hFacZ,vF,myThid)
350    
351  C     Combine fluxes -> fMer  C     Combine fluxes -> fMer
352        DO j=jMin,jMax        DO j=jMin,jMax+1
353         DO i=iMin,iMax         DO i=iMin,iMax
354          fMer(i,j) = vDudyFac*aF(i,j) + AhDudyFac*vF(i,j)          fMer(i,j) = vDudyFac*aF(i,j) + AhDudyFac*vF(i,j)
355         ENDDO         ENDDO
# Line 274  C     Combine fluxes -> fMer Line 357  C     Combine fluxes -> fMer
357    
358  C--   Vertical flux (fVer is at upper face of "u" cell)  C--   Vertical flux (fVer is at upper face of "u" cell)
359    
 C--   Free surface correction term (flux at k=1)  
       IF (momAdvection.AND.k.EQ.1) THEN  
        CALL MOM_U_ADV_WU(bi,bj,k,uVel,wVel,af,myThid)  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          fVerU(i,j,kUp) = af(i,j)  
         ENDDO  
        ENDDO  
       ENDIF  
360  C     Mean flow component of vertical flux (at k+1) -> aF  C     Mean flow component of vertical flux (at k+1) -> aF
361        IF (momAdvection)        IF (momAdvection)
362       & CALL MOM_U_ADV_WU(bi,bj,k+1,uVel,wVel,af,myThid)       & CALL MOM_U_ADV_WU(bi,bj,k+1,uVel,wVel,rTransU,af,myThid)
363    
364  C     Eddy component of vertical flux (interior component only) -> vrF  C     Eddy component of vertical flux (interior component only) -> vrF
365        IF (momViscosity.AND..NOT.implicitViscosity)        IF (momViscosity.AND..NOT.implicitViscosity)
# Line 298  C     Combine fluxes Line 372  C     Combine fluxes
372         ENDDO         ENDDO
373        ENDDO        ENDDO
374    
 C---  Hydrostatic term ( -1/rhoConst . dphi/dx )  
       IF (momPressureForcing) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          pf(i,j) = - _recip_dxC(i,j,bi,bj)  
      &    *(phi_hyd(i,j,k)-phi_hyd(i-1,j,k))  
         ENDDO  
        ENDDO  
       ENDIF  
   
375  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term
376        DO j=jMin,jMax        DO j=jMin,jMax
377         DO i=iMin,iMax         DO i=iMin,iMax
# Line 323  C--   Tendency is minus divergence of th Line 387  C--   Tendency is minus divergence of th
387       &   +fMer(i,j+1)          - fMer(i  ,j)       &   +fMer(i,j+1)          - fMer(i  ,j)
388       &   +fVerU(i,j,kUp)*rkFac - fVerU(i,j,kDown)*rkFac       &   +fVerU(i,j,kUp)*rkFac - fVerU(i,j,kDown)*rkFac
389       &   )       &   )
390       & _PHM( +phxFac * pf(i,j) )       &  - phxFac*dPhiHydX(i,j)
391         ENDDO         ENDDO
392        ENDDO        ENDDO
393    
394    #ifdef NONLIN_FRSURF
395    C-- account for 3.D divergence of the flow in rStar coordinate:
396          IF ( momAdvection .AND. select_rStar.GT.0 ) THEN
397           DO j=jMin,jMax
398            DO i=iMin,iMax
399             gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)
400         &     - (rStarExpW(i,j,bi,bj) - 1. _d 0)/deltaTfreesurf
401         &       *uVel(i,j,k,bi,bj)
402            ENDDO
403           ENDDO
404          ENDIF
405          IF ( momAdvection .AND. select_rStar.LT.0 ) THEN
406           DO j=jMin,jMax
407            DO i=iMin,iMax
408             gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)
409         &     - rStarDhWDt(i,j,bi,bj)*uVel(i,j,k,bi,bj)
410            ENDDO
411           ENDDO
412          ENDIF
413    #endif /* NONLIN_FRSURF */
414    
415  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
416        IF (momViscosity.AND.no_slip_sides) THEN        IF (momViscosity.AND.no_slip_sides) THEN
417  C-     No-slip BCs impose a drag at walls...  C-     No-slip BCs impose a drag at walls...
# Line 347  C-    No-slip BCs impose a drag at botto Line 432  C-    No-slip BCs impose a drag at botto
432         ENDDO         ENDDO
433        ENDIF        ENDIF
434    
435  C--   Forcing term  C--   Forcing term (moved to timestep.F)
436        IF (momForcing)  c     IF (momForcing)
437       &  CALL EXTERNAL_FORCING_U(  c    &  CALL EXTERNAL_FORCING_U(
438       I     iMin,iMax,jMin,jMax,bi,bj,k,  c    I     iMin,iMax,jMin,jMax,bi,bj,k,
439       I     myCurrentTime,myThid)  c    I     myTime,myThid)
440    
441  C--   Metric terms for curvilinear grid systems  C--   Metric terms for curvilinear grid systems
442        IF (usingSphericalPolarMTerms) THEN        IF (useNHMTerms) THEN
443  C      o Spherical polar grid metric terms  C      o Non-hydrosatic metric terms
444         CALL MOM_U_METRIC_NH(bi,bj,k,uFld,wVel,mT,myThid)         CALL MOM_U_METRIC_NH(bi,bj,k,uFld,wVel,mT,myThid)
445         DO j=jMin,jMax         DO j=jMin,jMax
446          DO i=iMin,iMax          DO i=iMin,iMax
447           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+mTFacU*mT(i,j)           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+mTFacU*mT(i,j)
448          ENDDO          ENDDO
449         ENDDO         ENDDO
450          ENDIF
451          IF (usingSphericalPolarMTerms) THEN
452         CALL MOM_U_METRIC_SPHERE(bi,bj,k,uFld,vFld,mT,myThid)         CALL MOM_U_METRIC_SPHERE(bi,bj,k,uFld,vFld,mT,myThid)
453         DO j=jMin,jMax         DO j=jMin,jMax
454          DO i=iMin,iMax          DO i=iMin,iMax
455           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+mTFacU*mT(i,j)           gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+mTFacU*mT(i,j)
456          ENDDO          ENDDO
457         ENDDO         ENDDO
458                                                                                    
459          ENDIF
460          IF (usingCylindricalGrid) THEN
461             CALL MOM_U_METRIC_CYLINDER(bi,bj,k,uFld,vFld,mT,myThid)
462             DO j=jMin,jMax
463              DO i=iMin,iMax
464                 gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+mTFacU*mT(i,j)
465              ENDDO
466           ENDDO
467                                                                                    
468        ENDIF        ENDIF
   
469  C--   Set du/dt on boundaries to zero  C--   Set du/dt on boundaries to zero
470        DO j=jMin,jMax        DO j=jMin,jMax
471         DO i=iMin,iMax         DO i=iMin,iMax
# Line 381  C--   Set du/dt on boundaries to zero Line 477  C--   Set du/dt on boundaries to zero
477  C---- Meridional momentum equation starts here  C---- Meridional momentum equation starts here
478    
479  C     Bi-harmonic term del^2 V -> v4F  C     Bi-harmonic term del^2 V -> v4F
480        IF (momViscosity)        IF (momViscosity .AND. viscA4.NE.0. )
481       & CALL MOM_V_DEL2V(bi,bj,k,vFld,hFacZ,v4f,myThid)       & CALL MOM_V_DEL2V(bi,bj,k,vFld,hFacZ,v4f,myThid)
482    
483  C---  Calculate mean and eddy fluxes between cells for meridional flow.  C---  Calculate mean and eddy fluxes between cells for meridional flow.
# Line 398  C     Laplacian and bi-harmonic terms -> Line 494  C     Laplacian and bi-harmonic terms ->
494    
495  C     Combine fluxes -> fZon  C     Combine fluxes -> fZon
496        DO j=jMin,jMax        DO j=jMin,jMax
497         DO i=iMin,iMax         DO i=iMin,iMax+1
498          fZon(i,j) = uDvdxFac*aF(i,j) + AhDvdxFac*vF(i,j)          fZon(i,j) = uDvdxFac*aF(i,j) + AhDvdxFac*vF(i,j)
499         ENDDO         ENDDO
500        ENDDO        ENDDO
# Line 422  C     Combine fluxes -> fMer Line 518  C     Combine fluxes -> fMer
518    
519  C--   Vertical flux (fVer is at upper face of "v" cell)  C--   Vertical flux (fVer is at upper face of "v" cell)
520    
 C--   Free surface correction term (flux at k=1)  
       IF (momAdvection.AND.k.EQ.1) THEN  
        CALL MOM_V_ADV_WV(bi,bj,k,vVel,wVel,af,myThid)  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          fVerV(i,j,kUp) = af(i,j)  
         ENDDO  
        ENDDO  
       ENDIF  
521  C     o Mean flow component of vertical flux  C     o Mean flow component of vertical flux
522        IF (momAdvection)        IF (momAdvection)
523       & CALL MOM_V_ADV_WV(bi,bj,k+1,vVel,wVel,af,myThid)       & CALL MOM_V_ADV_WV(bi,bj,k+1,vVel,wVel,rTransV,af,myThid)
524    
525  C     Eddy component of vertical flux (interior component only) -> vrF  C     Eddy component of vertical flux (interior component only) -> vrF
526        IF (momViscosity.AND..NOT.implicitViscosity)        IF (momViscosity.AND..NOT.implicitViscosity)
# Line 446  C     Combine fluxes -> fVerV Line 533  C     Combine fluxes -> fVerV
533         ENDDO         ENDDO
534        ENDDO        ENDDO
535    
 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  
   
536  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term  C--   Tendency is minus divergence of the fluxes + coriolis + pressure term
537        DO j=jMin,jMax        DO j=jMin,jMax
538         DO i=iMin,iMax         DO i=iMin,iMax
# Line 471  C--   Tendency is minus divergence of th Line 548  C--   Tendency is minus divergence of th
548       &   +fMer(i,j  )          - fMer(i,j-1)       &   +fMer(i,j  )          - fMer(i,j-1)
549       &   +fVerV(i,j,kUp)*rkFac - fVerV(i,j,kDown)*rkFac       &   +fVerV(i,j,kUp)*rkFac - fVerV(i,j,kDown)*rkFac
550       &   )       &   )
551       & _PHM( +phyFac*pf(i,j) )       &  - phyFac*dPhiHydY(i,j)
552         ENDDO         ENDDO
553        ENDDO        ENDDO
554    
555    #ifdef NONLIN_FRSURF
556    C-- account for 3.D divergence of the flow in rStar coordinate:
557          IF ( momAdvection .AND. select_rStar.GT.0 ) THEN
558           DO j=jMin,jMax
559            DO i=iMin,iMax
560             gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)
561         &     - (rStarExpS(i,j,bi,bj) - 1. _d 0)/deltaTfreesurf
562         &       *vVel(i,j,k,bi,bj)
563            ENDDO
564           ENDDO
565          ENDIF
566          IF ( momAdvection .AND. select_rStar.LT.0 ) THEN
567           DO j=jMin,jMax
568            DO i=iMin,iMax
569             gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)
570         &     - rStarDhSDt(i,j,bi,bj)*vVel(i,j,k,bi,bj)
571            ENDDO
572           ENDDO
573          ENDIF
574    #endif /* NONLIN_FRSURF */
575    
576  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
577        IF (momViscosity.AND.no_slip_sides) THEN        IF (momViscosity.AND.no_slip_sides) THEN
578  C-     No-slip BCs impose a drag at walls...  C-     No-slip BCs impose a drag at walls...
# Line 495  C-    No-slip BCs impose a drag at botto Line 593  C-    No-slip BCs impose a drag at botto
593         ENDDO         ENDDO
594        ENDIF        ENDIF
595    
596  C--   Forcing term  C--   Forcing term (moved to timestep.F)
597        IF (momForcing)  c     IF (momForcing)
598       & CALL EXTERNAL_FORCING_V(  c    & CALL EXTERNAL_FORCING_V(
599       I     iMin,iMax,jMin,jMax,bi,bj,k,  c    I     iMin,iMax,jMin,jMax,bi,bj,k,
600       I     myCurrentTime,myThid)  c    I     myTime,myThid)
601    
602  C--   Metric terms for curvilinear grid systems  C--   Metric terms for curvilinear grid systems
603        IF (usingSphericalPolarMTerms) THEN        IF (useNHMTerms) THEN
604  C      o Spherical polar grid metric terms  C      o Spherical polar grid metric terms
605         CALL MOM_V_METRIC_NH(bi,bj,k,vFld,wVel,mT,myThid)         CALL MOM_V_METRIC_NH(bi,bj,k,vFld,wVel,mT,myThid)
606         DO j=jMin,jMax         DO j=jMin,jMax
# Line 510  C      o Spherical polar grid metric ter Line 608  C      o Spherical polar grid metric ter
608           gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+mTFacV*mT(i,j)           gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+mTFacV*mT(i,j)
609          ENDDO          ENDDO
610         ENDDO         ENDDO
611          ENDIF
612          IF (usingSphericalPolarMTerms) THEN
613         CALL MOM_V_METRIC_SPHERE(bi,bj,k,uFld,mT,myThid)         CALL MOM_V_METRIC_SPHERE(bi,bj,k,uFld,mT,myThid)
614         DO j=jMin,jMax         DO j=jMin,jMax
615          DO i=iMin,iMax          DO i=iMin,iMax
# Line 517  C      o Spherical polar grid metric ter Line 617  C      o Spherical polar grid metric ter
617          ENDDO          ENDDO
618         ENDDO         ENDDO
619        ENDIF        ENDIF
620          IF (usingCylindricalGrid) THEN
621             CALL MOM_V_METRIC_CYLINDER(bi,bj,k,uFld,vFld,mT,myThid)
622             DO j=jMin,jMax
623                DO i=iMin,iMax
624                   gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+mTFacV*mT(i,j)
625                ENDDO
626             ENDDO
627          ENDIF
628    
629  C--   Set dv/dt on boundaries to zero  C--   Set dv/dt on boundaries to zero
630        DO j=jMin,jMax        DO j=jMin,jMax
# Line 527  C--   Set dv/dt on boundaries to zero Line 635  C--   Set dv/dt on boundaries to zero
635    
636  C--   Coriolis term  C--   Coriolis term
637  C     Note. As coded here, coriolis will not work with "thin walls"  C     Note. As coded here, coriolis will not work with "thin walls"
638  #ifdef INCLUDE_CD_CODE  c     IF (useCDscheme) THEN
639        CALL MOM_CDSCHEME(bi,bj,k,phi_hyd,myThid)  c       CALL MOM_CDSCHEME(bi,bj,k,dPhiHydX,dPhiHydY,myThid)
640  #else  c     ELSE
641        CALL MOM_U_CORIOLIS(bi,bj,k,vFld,cf,myThid)        IF (.NOT.useCDscheme) THEN
642        DO j=jMin,jMax          CALL MOM_U_CORIOLIS(bi,bj,k,vFld,cf,myThid)
643         DO i=iMin,iMax          DO j=jMin,jMax
644          gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+fuFac*cf(i,j)           DO i=iMin,iMax
645         ENDDO            gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+fuFac*cf(i,j)
646        ENDDO           ENDDO
647        CALL MOM_V_CORIOLIS(bi,bj,k,uFld,cf,myThid)          ENDDO
648        DO j=jMin,jMax          CALL MOM_V_CORIOLIS(bi,bj,k,uFld,cf,myThid)
649         DO i=iMin,iMax          DO j=jMin,jMax
650          gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+fvFac*cf(i,j)           DO i=iMin,iMax
651              gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj)+fvFac*cf(i,j)
652             ENDDO
653            ENDDO
654          ENDIF
655    
656          IF (nonHydrostatic.OR.quasiHydrostatic) THEN
657           CALL MOM_U_CORIOLIS_NH(bi,bj,k,wVel,cf,myThid)
658           DO j=jMin,jMax
659            DO i=iMin,iMax
660             gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj)+fuFac*cf(i,j)
661            ENDDO
662         ENDDO         ENDDO
663        ENDDO        ENDIF
 #endif /* INCLUDE_CD_CODE */  
664    
665        RETURN        RETURN
666        END        END

Legend:
Removed from v.1.2  
changed lines
  Added in v.1.21

  ViewVC Help
Powered by ViewVC 1.1.22