/[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.3 by adcroft, Wed Sep 26 19:05:21 2001 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
4    CBOI
5    C !TITLE: pkg/mom\_advdiff
6    C !AUTHORS: adcroft@mit.edu
7    C !INTRODUCTION:
8    C \section{Flux-form Momentum Equations Package}
9    C
10    C Package "mom\_fluxform" provides methods for calculating explicit terms
11    C in the momentum equation cast in flux-form:
12    C \begin{eqnarray*}
13    C G^u & = & -\frac{1}{\rho} \partial_x \phi_h
14    C           -\nabla \cdot {\bf v} u
15    C           -fv
16    C           +\frac{1}{\rho} \nabla \cdot {\bf \tau}^x
17    C           + \mbox{metrics}
18    C \\
19    C G^v & = & -\frac{1}{\rho} \partial_y \phi_h
20    C           -\nabla \cdot {\bf v} v
21    C           +fu
22    C           +\frac{1}{\rho} \nabla \cdot {\bf \tau}^y
23    C           + \mbox{metrics}
24    C \end{eqnarray*}
25    C where ${\bf v}=(u,v,w)$ and $\tau$, the stress tensor, includes surface
26    C stresses as well as internal viscous stresses.
27    CEOI
28    
29  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
30    
31    CBOP
32    C !ROUTINE: MOM_FLUXFORM
33    
34    C !INTERFACE: ==========================================================
35        SUBROUTINE MOM_FLUXFORM(        SUBROUTINE MOM_FLUXFORM(
36       I        bi,bj,iMin,iMax,jMin,jMax,k,kUp,kDown,       I        bi,bj,iMin,iMax,jMin,jMax,k,kUp,kDown,
37       I        phi_hyd,KappaRU,KappaRV,       I        phi_hyd,KappaRU,KappaRV,
38       U        fVerU, fVerV,       U        fVerU, fVerV,
39       I        myCurrentTime, myIter, myThid)       I        myCurrentTime,myIter,myThid)
40  C     /==========================================================\  
41  C     | S/R MOM_FLUXFORM                                         |  C !DESCRIPTION:
42  C     | o Form the right hand-side of the momentum equation.     |  C Calculates all the horizontal accelerations except for the implicit surface
43  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  
44    
45    C !USES: ===============================================================
46  C     == Global variables ==  C     == Global variables ==
47          IMPLICIT NONE
48  #include "SIZE.h"  #include "SIZE.h"
49  #include "DYNVARS.h"  #include "DYNVARS.h"
50  #include "FFIELDS.h"  #include "FFIELDS.h"
# Line 34  C     == Global variables == Line 53  C     == Global variables ==
53  #include "GRID.h"  #include "GRID.h"
54  #include "SURFACE.h"  #include "SURFACE.h"
55    
56  C     == Routine arguments ==  C !INPUT PARAMETERS: ===================================================
57  C     fZon    - Work array for flux of momentum in the east-west  C  bi,bj                :: tile indices
58  C               direction at the west face of a cell.  C  iMin,iMax,jMin,jMAx  :: loop ranges
59  C     fMer    - Work array for flux of momentum in the north-south  C  k                    :: vertical level
60  C               direction at the south face of a cell.  C  kUp                  :: =1 or 2 for consecutive k
61  C     fVerU   - Flux of momentum in the vertical  C  kDown                :: =2 or 1 for consecutive k
62  C     fVerV     direction out of the upper face of a cell K  C  phi_hyd              :: hydrostatic pressure (perturbation)
63  C               ( flux into the cell above ).  C  KappaRU              :: vertical viscosity
64  C     phi_hyd - Hydrostatic pressure  C  KappaRV              :: vertical viscosity
65  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
66  C                                      results will be set.  C  fVerV                :: vertical flux of V, 2 1/2 dim for pipe-lining
67  C     kUp, kDown                     - Index for upper and lower layers.  C  myCurrentTime        :: current time
68  C     myThid - Instance number for this innvocation of CALC_MOM_RHS  C  myIter               :: current time-step number
69    C  myThid               :: thread number
70          INTEGER bi,bj,iMin,iMax,jMin,jMax
71          INTEGER k,kUp,kDown
72        _RL phi_hyd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL phi_hyd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
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)
       INTEGER kUp,kDown  
77        _RL     myCurrentTime        _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 94  C     uDudxFac, AhDudxFac, etc ... indiv Line 121  C     uDudxFac, AhDudxFac, etc ... indiv
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  C     I,J,K - Loop counters  C     I,J,K - Loop counters
       INTEGER i,j,k  
124  C     rVelMaskOverride - Factor for imposing special surface boundary conditions  C     rVelMaskOverride - Factor for imposing special surface boundary conditions
125  C                        ( set according to free-surface condition ).  C                        ( set according to free-surface condition ).
126  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 150  C     xxxFac - On-off tracer parameters
150        _RL  phyFac        _RL  phyFac
151        _RL  vForcFac        _RL  vForcFac
152        _RL  mtFacV        _RL  mtFacV
 C     ab05, ab15 - Adams-Bashforth time-stepping weights.  
       _RL  ab05, ab15  
153        INTEGER km1,kp1        INTEGER km1,kp1
154        _RL wVelBottomOverride        _RL wVelBottomOverride
155        LOGICAL bottomDragTerms        LOGICAL bottomDragTerms
156        _RL KE(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL KE(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
157    CEOP
158    
159        km1=MAX(1,k-1)        km1=MAX(1,k-1)
160        kp1=MIN(Nr,k+1)        kp1=MIN(Nr,k+1)
# Line 194  C-- with stagger time stepping, grad Phi Line 219  C-- with stagger time stepping, grad Phi
219          phyFac = 0.          phyFac = 0.
220        ENDIF        ENDIF
221    
 C--   Adams-Bashforth weighting factors  
       ab15   =  1.5 _d 0 + abEps  
       ab05   = -0.5 _d 0 - abEps  
     
222  C--   Calculate open water fraction at vorticity points  C--   Calculate open water fraction at vorticity points
223        CALL MOM_CALC_HFACZ(bi,bj,k,hFacZ,r_hFacZ,myThid)        CALL MOM_CALC_HFACZ(bi,bj,k,hFacZ,r_hFacZ,myThid)
224    

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

  ViewVC Help
Powered by ViewVC 1.1.22