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

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

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

revision 1.2 by adcroft, Mon Sep 10 00:14:05 2001 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_X(  CBOP
7       I           bi,bj,k,deltaT,  C !ROUTINE: GAD_DST3_ADV_X
8       I           uTrans, uVel,  
9       I           tracer,  C !INTERFACE: ==========================================================
10          SUBROUTINE GAD_DST3_ADV_X(
11         I           bi,bj,k,deltaTloc,
12         I           uTrans, uFld,
13         I           maskLocW, tracer,
14       O           uT,       O           uT,
15       I           myThid )       I           myThid )
16  C     /==========================================================\  
17  C     | SUBROUTINE GAD_DST3_ADV_X                                |  C !DESCRIPTION:
18  C     | o Compute Zonal advective Flux of Tracer using           |  C  Calculates the area integrated zonal flux due to advection of a
19  C     |   3rd Order DST Sceheme                                  |  C  tracer using 3rd-order Direct Space and Time (DST-3) Advection Scheme
20  C     |==========================================================|  
21    C !USES: ===============================================================
22        IMPLICIT NONE        IMPLICIT NONE
23    
24  C     == GLobal variables ==  C     == GLobal variables ==
25  #include "SIZE.h"  #include "SIZE.h"
26  #include "GRID.h"  #include "GRID.h"
27    #include "EEPARAMS.h"
28    #include "PARAMS.h"
29  #include "GAD.h"  #include "GAD.h"
30    
31  C     == Routine arguments ==  C     == Routine arguments ==
32    C !INPUT PARAMETERS: ===================================================
33    C  bi,bj             :: tile indices
34    C  k                 :: vertical level
35    C  deltaTloc         :: local time-step (s)
36    C  uTrans            :: zonal volume transport
37    C  uFld              :: zonal flow
38    C  tracer            :: tracer field
39    C  myThid            :: thread number
40        INTEGER bi,bj,k        INTEGER bi,bj,k
41        _RL deltaT        _RL deltaTloc
42        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
43        _RL uVel(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)        _RL uFld  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
44          _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
45        _RL tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
       _RL uT    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
46        INTEGER myThid        INTEGER myThid
47    
48    C !OUTPUT PARAMETERS: ==================================================
49    C  uT                :: zonal advective flux
50          _RL uT    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
51    
52  C     == Local variables ==  C     == Local variables ==
53    C !LOCAL VARIABLES: ====================================================
54    C  i,j               :: loop indices
55    C  uLoc              :: velocity [m/s], zonal component
56    C  uCFL              :: Courant-Friedrich-Levy number
57        INTEGER i,j        INTEGER i,j
58        _RL Rjm,Rj,Rjp,cfl,d0,d1        _RL uLoc
59          _RL Rjm,Rj,Rjp,uCFL,d0,d1
60    #ifdef OLD_DST3_FORMULATION
61        _RL psiP,psiM,thetaP,thetaM        _RL psiP,psiM,thetaP,thetaM
62          _RL smallNo
63    c     _RL Rjjm,Rjjp
64    
65          IF (inAdMode) THEN
66           smallNo = 1.0D-20
67          ELSE
68           smallNo = 1.0D-20
69          ENDIF
70    #endif
71    
72        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
73         uT(1-Olx,j)=0.         uT(1-Olx,j)=0.
74         uT(2-Olx,j)=0.         uT(2-Olx,j)=0.
75         uT(sNx+Olx,j)=0.         uT(sNx+Olx,j)=0.
76         DO i=1-Olx+2,sNx+Olx-1         DO i=1-Olx+2,sNx+Olx-1
77          Rjp=(tracer(i+1,j)-tracer(i,j))*maskW(i+1,j,k,bi,bj)          Rjp=(tracer(i+1,j)-tracer( i ,j))*maskLocW(i+1,j)
78          Rj =(tracer(i,j)-tracer(i-1,j))*maskW(i,j,k,bi,bj)          Rj =(tracer( i ,j)-tracer(i-1,j))*maskLocW( i ,j)
79          Rjm=(tracer(i-1,j)-tracer(i-2,j))*maskW(i-1,j,k,bi,bj)          Rjm=(tracer(i-1,j)-tracer(i-2,j))*maskLocW(i-1,j)
80    
81          cfl=abs(uVel(i,j,k,bi,bj)*deltaT*recip_dxc(i,j,bi,bj))          uLoc = uFld(i,j)
82          d0=(2.-cfl)*(1.-cfl)*oneSixth          uCFL = ABS( uLoc*deltaTloc
83          d1=(1.-cfl*cfl)*oneSixth       &                  *recip_dxC(i,j,bi,bj)*recip_deepFacC(k) )
84  c       thetaP=0.          d0=(2.-uCFL)*(1.-uCFL)*oneSixth
85  c       IF (Rj.NE.0.) thetaP=Rjm/Rj          d1=(1.-uCFL*uCFL)*oneSixth
86          thetaP=Rjm/(1.D-20+Rj)  #ifdef OLD_DST3_FORMULATION
87          psiP=d0+d1*thetaP          IF ( ABS(Rj).LT.smallNo .OR.
88  c       psiP=max(0.,min(min(1.,psiP),(1.-cfl)/(1.D-20+cfl)*thetaP))       &       ABS(Rjm).LT.smallNo ) THEN
89          thetaM=Rjp/(1.D-20+Rj)           thetaP=0.
90  c       thetaM=0.           psiP=0.
91  c       IF (Rj.NE.0.) thetaM=Rjp/Rj          ELSE
92          psiM=d0+d1*thetaM           thetaP=(Rjm+smallNo)/(smallNo+Rj)
93  c       psiM=max(0.,min(min(1.,psiM),(1.-cfl)/(1.D-20+cfl)*thetaM))           psiP=d0+d1*thetaP
94            ENDIF
95            IF ( ABS(Rj).LT.smallNo .OR.
96         &       ABS(Rjp).LT.smallNo ) THEN
97             thetaM=0.
98             psiM=0.
99            ELSE
100             thetaM=(Rjp+smallNo)/(smallNo+Rj)
101             psiM=d0+d1*thetaM
102            ENDIF
103          uT(i,j)=          uT(i,j)=
104       &   0.5*(uTrans(i,j)+abs(uTrans(i,j)))       &   0.5*(uTrans(i,j)+ABS(uTrans(i,j)))
105       &      *( Tracer(i-1,j) + psiP*Rj )       &      *( Tracer(i-1,j) + psiP*Rj )
106       &  +0.5*(uTrans(i,j)-abs(uTrans(i,j)))       &  +0.5*(uTrans(i,j)-ABS(uTrans(i,j)))
107       &      *( Tracer( i ,j) - psiM*Rj )       &      *( Tracer( i ,j) - psiM*Rj )
108    #else /* OLD_DST3_FORMULATION */
109            uT(i,j)=
110         &   0.5*(uTrans(i,j)+ABS(uTrans(i,j)))
111         &      *( Tracer(i-1,j) + (d0*Rj+d1*Rjm) )
112         &  +0.5*(uTrans(i,j)-ABS(uTrans(i,j)))
113         &      *( Tracer( i ,j) - (d0*Rj+d1*Rjp) )
114    #endif /* OLD_DST3_FORMULATION */
115    
116         ENDDO         ENDDO
117        ENDDO        ENDDO

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

  ViewVC Help
Powered by ViewVC 1.1.22