/[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.14 by jmc, Tue Mar 29 15:47:19 2011 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, calcCFL, 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    #ifdef OLD_DST3_FORMULATION
27    #include "EEPARAMS.h"
28    #include "PARAMS.h"
29    #endif
30  #include "GRID.h"  #include "GRID.h"
31  #include "GAD.h"  #include "GAD.h"
32    
33  C     == Routine arguments ==  C     == Routine arguments ==
34    C !INPUT PARAMETERS: ===================================================
35    C  bi,bj             :: tile indices
36    C  k                 :: vertical level
37    C  calcCFL           :: =T: calculate CFL number ; =F: take uFld as CFL.
38    C  deltaTloc         :: local time-step (s)
39    C  uTrans            :: zonal volume transport
40    C  uFld              :: zonal flow / CFL number
41    C  tracer            :: tracer field
42    C  myThid            :: thread number
43        INTEGER bi,bj,k        INTEGER bi,bj,k
44        _RL deltaT        LOGICAL calcCFL
45          _RL deltaTloc
46        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
47        _RL uVel(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)        _RL uFld  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
48          _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
49        _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)  
50        INTEGER myThid        INTEGER myThid
51    
52    C !OUTPUT PARAMETERS: ==================================================
53    C  uT                :: zonal advective flux
54          _RL uT    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
55    
56  C     == Local variables ==  C     == Local variables ==
57    C !LOCAL VARIABLES: ====================================================
58    C  i,j               :: loop indices
59    C  uCFL              :: Courant-Friedrich-Levy number
60        INTEGER i,j        INTEGER i,j
61        _RL Rjm,Rj,Rjp,cfl,d0,d1        _RL Rjm,Rj,Rjp,uCFL,d0,d1
62    #ifdef OLD_DST3_FORMULATION
63        _RL psiP,psiM,thetaP,thetaM        _RL psiP,psiM,thetaP,thetaM
64          _RL smallNo
65    c     _RL Rjjm,Rjjp
66    
67          IF (inAdMode) THEN
68           smallNo = 1.0D-20
69          ELSE
70           smallNo = 1.0D-20
71          ENDIF
72    #endif
73    
74        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
75         uT(1-Olx,j)=0.         uT(1-Olx,j)=0.
76         uT(2-Olx,j)=0.         uT(2-Olx,j)=0.
77         uT(sNx+Olx,j)=0.         uT(sNx+Olx,j)=0.
78          ENDDO
79          DO j=1-Oly,sNy+Oly
80         DO i=1-Olx+2,sNx+Olx-1         DO i=1-Olx+2,sNx+Olx-1
81          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)
82          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)
83          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)
84    
85          cfl=abs(uVel(i,j,k,bi,bj)*deltaT*recip_dxc(i,j,bi,bj))          uCFL = uFld(i,j)
86          d0=(2.-cfl)*(1.-cfl)*oneSixth          IF ( calcCFL ) uCFL = ABS( uFld(i,j)*deltaTloc
87          d1=(1.-cfl*cfl)*oneSixth       &                  *recip_dxC(i,j,bi,bj)*recip_deepFacC(k) )
88  c       thetaP=0.          d0=(2.-uCFL)*(1.-uCFL)*oneSixth
89  c       IF (Rj.NE.0.) thetaP=Rjm/Rj          d1=(1.-uCFL*uCFL)*oneSixth
90          thetaP=Rjm/(1.D-20+Rj)  #ifdef OLD_DST3_FORMULATION
91          psiP=d0+d1*thetaP          IF ( ABS(Rj).LT.smallNo .OR.
92  c       psiP=max(0.,min(min(1.,psiP),(1.-cfl)/(1.D-20+cfl)*thetaP))       &       ABS(Rjm).LT.smallNo ) THEN
93          thetaM=Rjp/(1.D-20+Rj)           thetaP=0.
94  c       thetaM=0.           psiP=0.
95  c       IF (Rj.NE.0.) thetaM=Rjp/Rj          ELSE
96          psiM=d0+d1*thetaM           thetaP=(Rjm+smallNo)/(smallNo+Rj)
97  c       psiM=max(0.,min(min(1.,psiM),(1.-cfl)/(1.D-20+cfl)*thetaM))           psiP=d0+d1*thetaP
98            ENDIF
99            IF ( ABS(Rj).LT.smallNo .OR.
100         &       ABS(Rjp).LT.smallNo ) THEN
101             thetaM=0.
102             psiM=0.
103            ELSE
104             thetaM=(Rjp+smallNo)/(smallNo+Rj)
105             psiM=d0+d1*thetaM
106            ENDIF
107          uT(i,j)=          uT(i,j)=
108       &   0.5*(uTrans(i,j)+abs(uTrans(i,j)))       &   0.5*(uTrans(i,j)+ABS(uTrans(i,j)))
109       &      *( Tracer(i-1,j) + psiP*Rj )       &      *( Tracer(i-1,j) + psiP*Rj )
110       &  +0.5*(uTrans(i,j)-abs(uTrans(i,j)))       &  +0.5*(uTrans(i,j)-ABS(uTrans(i,j)))
111       &      *( Tracer( i ,j) - psiM*Rj )       &      *( Tracer( i ,j) - psiM*Rj )
112    #else /* OLD_DST3_FORMULATION */
113            uT(i,j)=
114         &   0.5*(uTrans(i,j)+ABS(uTrans(i,j)))
115         &      *( Tracer(i-1,j) + (d0*Rj+d1*Rjm) )
116         &  +0.5*(uTrans(i,j)-ABS(uTrans(i,j)))
117         &      *( Tracer( i ,j) - (d0*Rj+d1*Rjp) )
118    #endif /* OLD_DST3_FORMULATION */
119    
120         ENDDO         ENDDO
121        ENDDO        ENDDO

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

  ViewVC Help
Powered by ViewVC 1.1.22