/[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.35 by heimbach, Thu Oct 30 18:44:26 2003 UTC revision 1.36 by jmc, Wed Nov 10 03:02:00 2004 UTC
# Line 9  C     !ROUTINE: TIMESTEP Line 9  C     !ROUTINE: TIMESTEP
9  C     !INTERFACE:  C     !INTERFACE:
10        SUBROUTINE TIMESTEP( bi, bj, iMin, iMax, jMin, jMax, k,        SUBROUTINE TIMESTEP( bi, bj, iMin, iMax, jMin, jMax, k,
11       I                     dPhiHydX,dPhiHydY, phiSurfX, phiSurfY,       I                     dPhiHydX,dPhiHydY, phiSurfX, phiSurfY,
12         I                     guDissip, gvDissip,
13       I                     myTime, myIter, myThid )       I                     myTime, myIter, myThid )
14  C     !DESCRIPTION: \bv  C     !DESCRIPTION: \bv
15  C     *==========================================================*  C     *==========================================================*
# Line 32  C     == Routine Arguments == Line 33  C     == Routine Arguments ==
33  C     dPhiHydX,Y :: Gradient (X & Y directions) of Hydrostatic Potential  C     dPhiHydX,Y :: Gradient (X & Y directions) of Hydrostatic Potential
34  C     phiSurfX :: gradient of Surface potential (Pressure/rho, ocean)  C     phiSurfX :: gradient of Surface potential (Pressure/rho, ocean)
35  C     phiSurfY ::          or geopotential (atmos) in X and Y direction  C     phiSurfY ::          or geopotential (atmos) in X and Y direction
36    C     guDissip :: dissipation tendency (all explicit terms), u component
37    C     gvDissip :: dissipation tendency (all explicit terms), v component
38    
39        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
40        INTEGER k        INTEGER k
41        _RL     dPhiHydX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)        _RL     dPhiHydX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
42        _RL     dPhiHydY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)        _RL     dPhiHydY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
43        _RL     phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL     phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
44        _RL     phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL     phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
45          _RL     guDissip(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
46          _RL     gvDissip(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
47        _RL     myTime        _RL     myTime
48        INTEGER myIter, myThid        INTEGER myIter, myThid
49    
50  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
51  C     == Local variables ==  C     == Local variables ==
52        LOGICAL momForcing_In_AB        LOGICAL momForcing_In_AB
53          LOGICAL momDissip_In_AB
54        INTEGER i,j        INTEGER i,j
55        _RL ab15,ab05        _RL ab15,ab05
56        _RL phxFac,phyFac, psFac        _RL phxFac,phyFac, psFac
# Line 64  C     Adams-Bashforth timestepping weigh Line 71  C     Adams-Bashforth timestepping weigh
71         ab05=-0.5-abeps         ab05=-0.5-abeps
72        ENDIF        ENDIF
73    
 C-- stagger time step: grad Phi_Hyp is not in gU,gV => add it in this S/R  
       IF (staggerTimeStep) THEN  
         phxFac = pfFacMom  
         phyFac = pfFacMom  
       ELSE  
         phxFac = 0.  
         phyFac = 0.  
       ENDIF  
   
74  C-- explicit part of the surface potential gradient is added in this S/R  C-- explicit part of the surface potential gradient is added in this S/R
75        psFac = pfFacMom*(1. _d 0 - implicSurfPress)        psFac = pfFacMom*(1. _d 0 - implicSurfPress)
76    
77  C-- including or excluding momentum forcing from Adams-Bashforth:  C-- including or excluding momentum forcing from Adams-Bashforth:
78        momForcing_In_AB = forcing_In_AB        momForcing_In_AB = forcing_In_AB
79        momForcing_In_AB = .TRUE.        momForcing_In_AB = .TRUE.
80          momDissip_In_AB  = .TRUE.
81    
82  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
83    
# Line 94  C-    Initialize local arrays (not reall Line 93  C-    Initialize local arrays (not reall
93         ENDDO         ENDDO
94        ENDDO        ENDDO
95    
96    C--   Stagger time step: grad Phi_Hyp will be added later
97          IF (staggerTimeStep) THEN
98            phxFac = pfFacMom
99            phyFac = pfFacMom
100          ELSE
101    C--   Synchronous time step: add grad Phi_Hyp to gU,gV before doing Adams-Bashforth
102    C     note: already done in S/R mom_vecinv and mom_fluxform but would be better
103    C     to add it to gU,gV here.
104    c       DO j=jMin,jMax
105    c        DO i=iMin,iMax
106    c         gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj) - pfFacMom*dPhiHydX(i,j)
107    c         gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj) - pfFacMom*dPhiHydY(i,j)
108    c        ENDDO
109    c       ENDDO
110            phxFac = 0.
111            phyFac = 0.
112          ENDIF
113    
114    #ifdef ALLOW_MOM_VECINV
115    C--   Dissipation term inside the Adams-Bashforth:
116    C     note: already in gU,gV if using fluxform
117          IF ( momViscosity .AND. momDissip_In_AB
118         &          .AND. vectorInvariantMomentum ) THEN
119            DO j=jMin,jMax
120             DO i=iMin,iMax
121              gU(i,j,k,bi,bj) = gU(i,j,k,bi,bj) + guDissip(i,j)
122              gV(i,j,k,bi,bj) = gV(i,j,k,bi,bj) + gvDissip(i,j)
123             ENDDO
124            ENDDO
125          ENDIF
126    #endif
127    
128  C--   Forcing term inside the Adams-Bashforth:  C--   Forcing term inside the Adams-Bashforth:
129        IF (momForcing .AND. momForcing_In_AB) THEN        IF (momForcing .AND. momForcing_In_AB) THEN
130          CALL EXTERNAL_FORCING_U(          CALL EXTERNAL_FORCING_U(
# Line 203  C      and return coriolis terms on C-gr Line 234  C      and return coriolis terms on C-gr
234    
235  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
236    
237    #ifdef ALLOW_MOM_VECINV
238    C--   Dissipation term outside the Adams-Bashforth:
239    C     note: only implemented with vecinv formulation
240          IF ( momViscosity .AND. .NOT.momDissip_In_AB
241         &               .AND. vectorInvariantMomentum ) THEN
242            DO j=jMin,jMax
243             DO i=iMin,iMax
244              gUtmp(i,j) = gUtmp(i,j) + guDissip(i,j)
245              gVtmp(i,j) = gVtmp(i,j) + gvDissip(i,j)
246             ENDDO
247            ENDDO
248          ENDIF
249    #endif
250    
251  C     Step forward zonal velocity (store in Gu)  C     Step forward zonal velocity (store in Gu)
252        DO j=jMin,jMax        DO j=jMin,jMax
253          DO i=iMin,iMax          DO i=iMin,iMax

Legend:
Removed from v.1.35  
changed lines
  Added in v.1.36

  ViewVC Help
Powered by ViewVC 1.1.22