/[MITgcm]/MITgcm/pkg/generic_advdiff/gad_dst3_adv_y.F
ViewVC logotype

Diff of /MITgcm/pkg/generic_advdiff/gad_dst3_adv_y.F

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

revision 1.5 by heimbach, Sun Apr 3 16:05:34 2005 UTC revision 1.11 by jmc, Tue Dec 5 22:21:50 2006 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "GAD_OPTIONS.h"  #include "GAD_OPTIONS.h"
5    
6        SUBROUTINE GAD_DST3_ADV_Y(  CBOP
7    C !ROUTINE: GAD_DST3_ADV_Y
8    
9    C !INTERFACE: ==========================================================
10          SUBROUTINE GAD_DST3_ADV_Y(
11       I           bi,bj,k,deltaTloc,       I           bi,bj,k,deltaTloc,
12       I           vTrans, vVel,       I           vTrans, vFld,
13       I           maskLocS, tracer,       I           maskLocS, tracer,
14       O           vT,       O           vT,
15       I           myThid )       I           myThid )
16  C     /==========================================================\  C !DESCRIPTION:
17  C     | SUBROUTINE GAD_DST3_ADV_Y                                |  C  Calculates the area integrated Meridional flux due to advection of a
18  C     | o Compute Meridional advective Flux of Tracer using      |  C  tracer using 3rd-order Direct Space and Time (DST-3) Advection Scheme
19  C     |   3rd Order DST Sceheme                                  |  
20  C     |==========================================================|  C !USES: ===============================================================
21        IMPLICIT NONE        IMPLICIT NONE
22    
23  C     == GLobal variables ==  C     == GLobal variables ==
# Line 24  C     == GLobal variables == Line 28  C     == GLobal variables ==
28  #include "GAD.h"  #include "GAD.h"
29    
30  C     == Routine arguments ==  C     == Routine arguments ==
31    C !INPUT PARAMETERS: ===================================================
32    C  bi,bj             :: tile indices
33    C  k                 :: vertical level
34    C  deltaTloc         :: local time-step (s)
35    C  vTrans            :: meridional volume transport
36    C  vFld              :: meridional flow
37    C  tracer            :: tracer field
38    C  myThid            :: thread number
39        INTEGER bi,bj,k        INTEGER bi,bj,k
40        _RL deltaTloc        _RL deltaTloc
41        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
42        _RL vVel(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)        _RL vFld  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
43        _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
44        _RL tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
       _RL vT    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
45        INTEGER myThid        INTEGER myThid
46    
47    C !OUTPUT PARAMETERS: ==================================================
48    C  vT                :: meridional advective flux
49          _RL vT    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
50    
51  C     == Local variables ==  C     == Local variables ==
52  C     vFld    :: velocity [m/s], meridional component  C !LOCAL VARIABLES: ====================================================
53    C  i,j               :: loop indices
54    C  vLoc              :: velocity [m/s], meridional component
55    C  vCFL              :: Courant-Friedrich-Levy number
56        INTEGER i,j        INTEGER i,j
57        _RL Rjm,Rj,Rjp,cfl,d0,d1        _RL Rjm,Rj,Rjp,vCFL,d0,d1
58          _RL vLoc
59    #ifdef OLD_DST3_FORMULATION
60        _RL psiP,psiM,thetaP,thetaM        _RL psiP,psiM,thetaP,thetaM
       _RL vFld  
61        _RL smallNo        _RL smallNo
62        _RL Rjjm,Rjjp  c     _RL Rjjm,Rjjp
63    
64        IF (inAdMode) THEN        IF (inAdMode) THEN
65         smallNo = 1.0D-20         smallNo = 1.0D-20
66        ELSE        ELSE
67         smallNo = 1.0D-20         smallNo = 1.0D-20
68        ENDIF        ENDIF
69    #endif
70    
71        DO i=1-Olx,sNx+Olx        DO i=1-Olx,sNx+Olx
72         vT(i,1-Oly)=0.         vT(i,1-Oly)=0.
# Line 59  C     vFld    :: velocity [m/s], meridio Line 79  C     vFld    :: velocity [m/s], meridio
79          Rj =(tracer(i, j )-tracer(i,j-1))*maskLocS(i, j )          Rj =(tracer(i, j )-tracer(i,j-1))*maskLocS(i, j )
80          Rjm=(tracer(i,j-1)-tracer(i,j-2))*maskLocS(i,j-1)          Rjm=(tracer(i,j-1)-tracer(i,j-2))*maskLocS(i,j-1)
81    
82  c       vFld = vVel(i,j,k,bi,bj)          vLoc = vFld(i,j)
83          vFld = vTrans(i,j)*recip_dxG(i,j,bi,bj)          vCFL = ABS( vLoc*deltaTloc
84       &       *recip_drF(k)*recip_hFacS(i,j,k,bi,bj)       &                  *recip_dyC(i,j,bi,bj)*recip_deepFacC(k) )
85          cfl=abs(vFld*deltaTloc*recip_dyC(i,j,bi,bj))          d0=(2.-vCFL)*(1.-vCFL)*oneSixth
86          d0=(2.-cfl)*(1.-cfl)*oneSixth          d1=(1.-vCFL*vCFL)*oneSixth
87          d1=(1.-cfl*cfl)*oneSixth  #ifdef OLD_DST3_FORMULATION
88          IF ( ABS(Rj).LT.smallNo .OR.          IF ( ABS(Rj).LT.smallNo .OR.
89       &       ABS(Rjm).LT.smallNo ) THEN       &       ABS(Rjm).LT.smallNo ) THEN
90           thetaP=0.           thetaP=0.
91           psiP=0.           psiP=0.
92          ELSE            ELSE
93           thetaP=(Rjm+smallNo)/(smallNo+Rj)           thetaP=(Rjm+smallNo)/(smallNo+Rj)
94           psiP=d0+d1*thetaP           psiP=d0+d1*thetaP
95          ENDIF          ENDIF
# Line 82  c       vFld = vVel(i,j,k,bi,bj) Line 102  c       vFld = vVel(i,j,k,bi,bj)
102           psiM=d0+d1*thetaM           psiM=d0+d1*thetaM
103          ENDIF          ENDIF
104          vT(i,j)=          vT(i,j)=
105       &   0.5*(vTrans(i,j)+abs(vTrans(i,j)))       &   0.5*(vTrans(i,j)+ABS(vTrans(i,j)))
106       &      *( Tracer(i,j-1) + psiP*Rj )       &      *( Tracer(i,j-1) + psiP*Rj )
107       &  +0.5*(vTrans(i,j)-abs(vTrans(i,j)))       &  +0.5*(vTrans(i,j)-ABS(vTrans(i,j)))
108       &      *( Tracer(i, j ) - psiM*Rj )       &      *( Tracer(i, j ) - psiM*Rj )
109    #else /* OLD_DST3_FORMULATION */
110            vT(i,j)=
111         &   0.5*(vTrans(i,j)+ABS(vTrans(i,j)))
112         &      *( Tracer(i,j-1) + (d0*Rj+d1*Rjm) )
113         &  +0.5*(vTrans(i,j)-ABS(vTrans(i,j)))
114         &      *( Tracer(i, j ) - (d0*Rj+d1*Rjp) )
115    #endif /* OLD_DST3_FORMULATION */
116    
117         ENDDO         ENDDO
118        ENDDO        ENDDO

Legend:
Removed from v.1.5  
changed lines
  Added in v.1.11

  ViewVC Help
Powered by ViewVC 1.1.22