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

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

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

revision 1.4 by jmc, Tue Jul 27 00:16:17 2004 UTC revision 1.9 by jmc, Tue Feb 19 13:42:19 2013 UTC
# Line 7  CBOP Line 7  CBOP
7  C     !ROUTINE: ADAMS_BASHFORTH2  C     !ROUTINE: ADAMS_BASHFORTH2
8  C     !INTERFACE:  C     !INTERFACE:
9        SUBROUTINE ADAMS_BASHFORTH2(        SUBROUTINE ADAMS_BASHFORTH2(
10       I                     bi, bj, K,       I                     bi, bj, k, kSize,
11       U                     gTracer, gTrNm1,       U                     gTracer, gTrNm1,
12       I                     myIter, myThid )       O                     AB_gTr,
13         I                     startAB, myIter, myThid )
14  C     !DESCRIPTION: \bv  C     !DESCRIPTION: \bv
15  C     *==========================================================*  C     *==========================================================*
16  C     | S/R ADAMS_BASHFORTH2                                        C     | S/R ADAMS_BASHFORTH2
17  C     | o Extrapolate tendancies forward in time using              C     | o Extrapolate tendencies forward in time using
18  C     |   quasi-second order Adams-Bashforth method.                C     |   quasi-second order Adams-Bashforth method.
19  C     *==========================================================*  C     *==========================================================*
20  C     \ev  C     \ev
21    
# Line 24  C     == Global variables === Line 25  C     == Global variables ===
25  #include "SIZE.h"  #include "SIZE.h"
26  #include "EEPARAMS.h"  #include "EEPARAMS.h"
27  #include "PARAMS.h"  #include "PARAMS.h"
 #include "GAD.h"  
 #include "GRID.h"  
 #include "SURFACE.h"  
28    
29  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
30  C     == Routine Arguments ==  C     == Routine Arguments ==
31  C     bi,bj,K :: Tile and level indices  C     bi,bj,k :: Tile and level indices
32  C     gTracer :: Tendency at current time  ( generally units of quantity/sec )  C     kSize   :: 3rd dimension of tracer and tendency arrays
33  C     gTrNm1  :: Tendency at previous time ( generally units of quantity/sec )  C     gTracer ::  in: Tendency at current time  ( generally units of quantity/sec )
34    C             :: out: Extrapolated Tendency at current time ( same units )
35    C     gTrNm1  ::  in: Tendency at previous time             ( same units )
36    C             :: out: Save tendency at current time         ( same units )
37    C     AB_gTr  :: Adams-Bashforth tendency increment
38    C     startAB :: number of previous time level available to start/restart AB
39  C     myIter  :: Current time step number  C     myIter  :: Current time step number
40  C     myThid  :: Thread number of this thread  C     myThid  :: my Thread Id. number
41        INTEGER bi,bj,K        INTEGER bi, bj, k, kSize
42        _RL  gTracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)        _RL  gTracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,kSize,nSx,nSy)
43        _RL  gTrNm1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)        _RL  gTrNm1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,kSize,nSx,nSy)
44          _RL  AB_gTr (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
45          INTEGER startAB
46        INTEGER myIter, myThid        INTEGER myIter, myThid
47    
48  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
49  C     == Local variables ==  C     == Local variables ==
50  C     i,j        :: Loop counters  C     i,j        :: Loop counters
51  C     ab15, ab05 :: Adams bashforth extrapolation weights.  C     abFac      :: Adams bashforth extrapolation factor
52        INTEGER i,j        INTEGER i,j
53        _RL ab15,ab05        _RL abFac
       _RL gTrtmp  
54  CEOP  CEOP
55    
56  C     Adams-Bashforth timestepping weights  C     Adams-Bashforth extrapolation factor
57        IF ( myIter.EQ.0 .OR.        IF ( myIter.EQ.nIter0 .AND. startAB.EQ.0 ) THEN
58       &    (myIter.EQ.1 .AND. staggerTimeStep) ) THEN         abFac = 0. _d 0
        ab15=1.0  
        ab05=0.0  
59        ELSE        ELSE
60         ab15=1.5+abEps         abFac = 0.5 _d 0 + abEps
        ab05=-(0.5+abEps)  
61        ENDIF        ENDIF
62    
63  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
64    
65  C-    Compute effective G-term with Adams-Bashforth weights:  C-    Compute effective G-term with Adams-Bashforth weights:
66        DO j=1-Oly,sNy+Oly        DO j=1-OLy,sNy+OLy
67         DO i=1-Olx,sNx+Olx         DO i=1-OLx,sNx+OLx
68          gTrtmp = ab15*gTracer(i,j,k,bi,bj)          AB_gTr(i,j) = abFac
69       &         + ab05*gTrNm1(i,j,k,bi,bj)       &              *( gTracer(i,j,k,bi,bj)- gTrNm1(i,j,k,bi,bj) )
70          gTrNm1(i,j,k,bi,bj) = gTracer(i,j,k,bi,bj)          gTrNm1(i,j,k,bi,bj) = gTracer(i,j,k,bi,bj)
71          gTracer(i,j,k,bi,bj) = gTrtmp          gTracer(i,j,k,bi,bj) = gTracer(i,j,k,bi,bj) + AB_gTr(i,j)
72         ENDDO         ENDDO
73        ENDDO        ENDDO
74    

Legend:
Removed from v.1.4  
changed lines
  Added in v.1.9

  ViewVC Help
Powered by ViewVC 1.1.22