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

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

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

revision 1.3 by adcroft, Wed Sep 26 19:05:21 2001 UTC revision 1.3.6.1 by heimbach, Fri Mar 7 04:46:40 2003 UTC
# Line 8  C !ROUTINE: MOM_CDSCHEME Line 8  C !ROUTINE: MOM_CDSCHEME
8    
9  C !INTERFACE: ==========================================================  C !INTERFACE: ==========================================================
10        SUBROUTINE MOM_CDSCHEME(        SUBROUTINE MOM_CDSCHEME(
11       I        bi,bj,k,phi_hyd,       I        bi,bj,k,dPhiHydX,dPhiHydY,
12       I        myThid)       I        myThid)
13    
14  C !DESCRIPTION:  C !DESCRIPTION:
# Line 27  C     == Global variables == Line 27  C     == Global variables ==
27  C !INPUT PARAMETERS: ===================================================  C !INPUT PARAMETERS: ===================================================
28  C  bi,bj                :: tile indices  C  bi,bj                :: tile indices
29  C  k                    :: vertical level  C  k                    :: vertical level
30  C  phi_hyd              :: hydrostatic pressure  C     dPhiHydX,Y        :: Gradient (X & Y dir.) of Hydrostatic Potential
31  C  myThid               :: thread number  C  myThid               :: thread number
32        INTEGER bi,bj,K        INTEGER bi,bj,k
33        _RL phi_hyd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL dPhiHydX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
34          _RL dPhiHydY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
35        INTEGER myThid        INTEGER myThid
36    
37    
# Line 45  C  aF                   :: work space Line 46  C  aF                   :: work space
46        _RL aF(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL aF(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
47        INTEGER i,j,iMin,iMax,jMin,jMax        INTEGER i,j,iMin,iMax,jMin,jMax
48        _RL ab15,ab05        _RL ab15,ab05
49          _RL phxFac, phyFac
50  CEOP  CEOP
51    
52  C     Compute ranges  C     Compute ranges
# Line 57  C     Adams-Bashforth weighting factors Line 59  C     Adams-Bashforth weighting factors
59        ab15   =  1.5 + abEps        ab15   =  1.5 + abEps
60        ab05   = -0.5 - abEps        ab05   = -0.5 - abEps
61    
62    C-- stagger time stepping: grad Phi_Hyp is not in gU,gV and needs to be added:
63          IF (staggerTimeStep) THEN
64            phxFac = pfFacMom
65            phyFac = pfFacMom
66          ELSE
67            phxFac = 0.
68            phyFac = 0.
69          ENDIF
70    
71  C     Pressure extrapolated forward in time  C     Pressure extrapolated forward in time
72        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
73         DO i=1-Olx,sNx+Olx         DO i=1-Olx,sNx+Olx
# Line 65  C     Pressure extrapolated forward in t Line 76  C     Pressure extrapolated forward in t
76       &  +ab05*(etaNm1(i,j,bi,bj)*Bo_surf(i,j,bi,bj) )       &  +ab05*(etaNm1(i,j,bi,bj)*Bo_surf(i,j,bi,bj) )
77         ENDDO         ENDDO
78        ENDDO        ENDDO
       IF (staggerTimeStep) THEN  
        DO j=jMin,jMax  
         DO i=iMin,iMax  
          pf(i,j) = pf(i,j)+phi_hyd(i,j,k)  
         ENDDO  
        ENDDO  
       ENDIF  
79    
80  C--   Zonal velocity coriolis term  C--   Zonal velocity coriolis term
81  C     Note. As coded here, coriolis will not work with "thin walls"  C     Note. As coded here, coriolis will not work with "thin walls"
# Line 79  C--   Coriolis with CD scheme allowed Line 83  C--   Coriolis with CD scheme allowed
83  C     grady(p) + gV  C     grady(p) + gV
84        DO j=1-Oly+1,sNy+Oly        DO j=1-Oly+1,sNy+Oly
85         DO i=1-Olx,sNx+Olx         DO i=1-Olx,sNx+Olx
86          af(i,j) = -_maskS(i,j,k,bi,bj)          af(i,j) = -_maskS(i,j,k,bi,bj)*(
87       &            *_recip_dyC(i,j,bi,bj)       &            _recip_dyC(i,j,bi,bj)*(pf(i,j)-pf(i,j-1))
88       &            *(pf(i,j)-pf(i,j-1))       &           +phyFac*dPhiHydY(i,j) )
89       &            +gV(i,j,k,bi,bj)       &          + gV(i,j,k,bi,bj)
90         ENDDO         ENDDO
91        ENDDO        ENDDO
92  C     Average to Vd point and add coriolis  C     Average to Vd point and add coriolis
# Line 135  C--   Meridional velocity coriolis term Line 139  C--   Meridional velocity coriolis term
139  C     gradx(p)+gU  C     gradx(p)+gU
140        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
141         DO i=1-Olx+1,sNx+Olx         DO i=1-Olx+1,sNx+Olx
142          af(i,j) = -_maskW(i,j,k,bi,bj)          af(i,j) = -_maskW(i,j,k,bi,bj)*(
143       &            *_recip_dxC(i,j,bi,bj)*       &            _recip_dxC(i,j,bi,bj)*(pf(i,j)-pf(i-1,j))
144       &            (pf(i,j)-pf(i-1,j))       &           +phxFac*dPhiHydX(i,j) )
145       &            +gU(i,j,k,bi,bj)       &          + gU(i,j,k,bi,bj)
146         ENDDO         ENDDO
147        ENDDO        ENDDO
148  C     Average to Ud point and add coriolis  C     Average to Ud point and add coriolis

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

  ViewVC Help
Powered by ViewVC 1.1.22