/[MITgcm]/MITgcm/model/src/timestep.F
ViewVC logotype

Diff of /MITgcm/model/src/timestep.F

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

revision 1.30 by jmc, Sun Feb 9 02:00:50 2003 UTC revision 1.31 by jmc, Tue Feb 18 15:27:25 2003 UTC
# Line 7  CBOP Line 7  CBOP
7  C     !ROUTINE: TIMESTEP  C     !ROUTINE: TIMESTEP
8  C     !INTERFACE:  C     !INTERFACE:
9        SUBROUTINE TIMESTEP( bi, bj, iMin, iMax, jMin, jMax, K,        SUBROUTINE TIMESTEP( bi, bj, iMin, iMax, jMin, jMax, K,
10       I             phiHyd, dPhiHydX,dPhiHydY, phiSurfX, phiSurfY,       I                     dPhiHydX,dPhiHydY, phiSurfX, phiSurfY,
11       I                     myIter, myThid )       I                     myIter, myThid )
12  C     !DESCRIPTION: \bv  C     !DESCRIPTION: \bv
13  C     *==========================================================*  C     *==========================================================*
# Line 28  C     == Global variables == Line 28  C     == Global variables ==
28    
29  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
30  C     == Routine Arguments ==  C     == Routine Arguments ==
 C     phiHyd     :: Hydrostatic Potential (ocean: pressure/rho)  
 C                                         (atmos: geopotential)  
31  C     dPhiHydX,Y :: Gradient (X & Y directions) of Hydrostatic Potential  C     dPhiHydX,Y :: Gradient (X & Y directions) of Hydrostatic Potential
32  C     phiSurfX :: gradient of Surface potential (Pressure/rho, ocean)  C     phiSurfX :: gradient of Surface potential (Pressure/rho, ocean)
33  C     phiSurfY ::          or geopotential (atmos) in X and Y direction  C     phiSurfY ::          or geopotential (atmos) in X and Y direction
34        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
35        INTEGER K        INTEGER K
       _RL     phiHyd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)  
36        _RL     dPhiHydX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)        _RL     dPhiHydX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
37        _RL     dPhiHydY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)        _RL     dPhiHydY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
38        _RL     phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL     phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 62  C     Adams-Bashforth timestepping weigh Line 59  C     Adams-Bashforth timestepping weigh
59    
60  C-- stagger time step: grad Phi_Hyp is not in gU,gV => add it in this S/R  C-- stagger time step: grad Phi_Hyp is not in gU,gV => add it in this S/R
61        IF (staggerTimeStep) THEN        IF (staggerTimeStep) THEN
 c     IF (.FALSE.) THEN  
62          phxFac = pfFacMom          phxFac = pfFacMom
63          phyFac = pfFacMom          phyFac = pfFacMom
64        ELSE        ELSE
# Line 119  C     Step forward zonal velocity (store Line 115  C     Step forward zonal velocity (store
115          ENDDO          ENDDO
116        ENDDO        ENDDO
117    
       IF (.FALSE.) THEN  
 c     IF (staggerTimeStep) THEN  
 C--   -grad Phi_Hyd has not been incorporated to gU and is added here:  
         phxFac = pfFacMom*deltaTmom  
         DO j=jMin,jMax  
           DO i=iMin,iMax  
             gUNm1(i,j,k,bi,bj)=gUNm1(i,j,k,bi,bj)  
      &       - _recip_dxC(i,j,bi,bj)  
      &         *(phiHyd(i,j,k)-phiHyd(i-1,j,k))*phxFac  
      &         *_maskW(i,j,k,bi,bj)  
           ENDDO  
         ENDDO  
       ENDIF  
   
118  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
119  C-    Compute effective gV term (including Adams-Bashforth weights) :  C-    Compute effective gV term (including Adams-Bashforth weights) :
120        DO j=jMin,jMax        DO j=jMin,jMax
# Line 179  C     Step forward meridional velocity ( Line 161  C     Step forward meridional velocity (
161          ENDDO          ENDDO
162        ENDDO        ENDDO
163    
       IF (.FALSE.) THEN  
 c     IF (staggerTimeStep) THEN  
 C--   -grad Phi_Hyd has not been incorporated to gV and is added here:  
         phyFac = pfFacMom*deltaTmom  
         DO j=jMin,jMax  
           DO i=iMin,iMax  
             gVNm1(i,j,k,bi,bj)=gVNm1(i,j,k,bi,bj)  
      &       - _recip_dyC(i,j,bi,bj)  
      &         *(phiHyd(i,j,k)-phiHyd(i,j-1,k))*phyFac  
      &         *_maskS(i,j,k,bi,bj)  
           ENDDO  
         ENDDO  
       ENDIF  
   
164        RETURN        RETURN
165        END        END

Legend:
Removed from v.1.30  
changed lines
  Added in v.1.31

  ViewVC Help
Powered by ViewVC 1.1.22