/[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.2.6.1 by heimbach, Fri Mar 7 03:55:23 2003 UTC revision 1.14 by jmc, Wed Jul 4 20:22:26 2012 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       I           bi,bj,k,deltaT,  C !ROUTINE: GAD_DST3_ADV_Y
8       I           vTrans, vVel,  
9       I           tracer,  C !INTERFACE: ==========================================================
10          SUBROUTINE GAD_DST3_ADV_Y(
11         I           bi,bj,k, calcCFL, deltaTloc,
12         I           vTrans, vFld,
13         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 ==
24  #include "SIZE.h"  #include "SIZE.h"
25    #ifdef OLD_DST3_FORMULATION
26    #include "EEPARAMS.h"
27    #include "PARAMS.h"
28    #endif
29  #include "GRID.h"  #include "GRID.h"
30  #include "GAD.h"  #include "GAD.h"
31    
32  C     == Routine arguments ==  C     == Routine arguments ==
33    C !INPUT PARAMETERS: ===================================================
34    C  bi,bj             :: tile indices
35    C  k                 :: vertical level
36    C  calcCFL           :: =T: calculate CFL number ; =F: take vFld as CFL
37    C  deltaTloc         :: local time-step (s)
38    C  vTrans            :: meridional volume transport
39    C  vFld              :: meridional flow / CFL number
40    C  tracer            :: tracer field
41    C  myThid            :: thread number
42        INTEGER bi,bj,k        INTEGER bi,bj,k
43        _RL deltaT        LOGICAL calcCFL
44          _RL deltaTloc
45        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
46        _RL vVel(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)        _RL vFld  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
47          _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
48        _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)  
49        INTEGER myThid        INTEGER myThid
50    
51    C !OUTPUT PARAMETERS: ==================================================
52    C  vT                :: meridional advective flux
53          _RL vT    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
54    
55  C     == Local variables ==  C     == Local variables ==
56  C     vFld    :: velocity [m/s], meridional component  C !LOCAL VARIABLES: ====================================================
57    C  i,j               :: loop indices
58    C  vCFL              :: Courant-Friedrich-Levy number
59        INTEGER i,j        INTEGER i,j
60        _RL Rjm,Rj,Rjp,cfl,d0,d1        _RL Rjm,Rj,Rjp,vCFL,d0,d1
61    #ifdef OLD_DST3_FORMULATION
62        _RL psiP,psiM,thetaP,thetaM        _RL psiP,psiM,thetaP,thetaM
63        _RL vFld        _RL smallNo
64    c     _RL Rjjm,Rjjp
65    
66        DO i=1-Olx,sNx+Olx  c     IF (inAdMode) THEN
67         vT(i,1-Oly)=0.  c      smallNo = 1.0D-20
68         vT(i,2-Oly)=0.  c     ELSE
69         vT(i,sNy+Oly)=0.         smallNo = 1.0D-20
70    c     ENDIF
71    #endif
72    
73          DO i=1-OLx,sNx+OLx
74           vT(i,1-OLy)=0.
75           vT(i,2-OLy)=0.
76           vT(i,sNy+OLy)=0.
77        ENDDO        ENDDO
78        DO j=1-Oly+2,sNy+Oly-1        DO j=1-OLy+2,sNy+OLy-1
79         DO i=1-Olx,sNx+Olx         DO i=1-OLx,sNx+OLx
80          Rjp=(tracer(i,j+1)-tracer(i,j))*maskS(i,j+1,k,bi,bj)          Rjp=(tracer(i,j+1)-tracer(i, j ))*maskLocS(i,j+1)
81          Rj =(tracer(i,j)-tracer(i,j-1))*maskS(i,j,k,bi,bj)          Rj =(tracer(i, j )-tracer(i,j-1))*maskLocS(i, j )
82          Rjm=(tracer(i,j-1)-tracer(i,j-2))*maskS(i,j-1,k,bi,bj)          Rjm=(tracer(i,j-1)-tracer(i,j-2))*maskLocS(i,j-1)
83    
84  c       vFld = vVel(i,j,k,bi,bj)          vCFL = vFld(i,j)
85          vFld = vTrans(i,j)*recip_dxG(i,j,bi,bj)          IF ( calcCFL ) vCFL = ABS( vFld(i,j)*deltaTloc
86       &       *recip_drF(k)*recip_hFacS(i,j,k,bi,bj)       &                  *recip_dyC(i,j,bi,bj)*recip_deepFacC(k) )
87          cfl=abs(vFld*deltaT*recip_dyC(i,j,bi,bj))          d0=(2.-vCFL)*(1.-vCFL)*oneSixth
88          d0=(2.-cfl)*(1.-cfl)*oneSixth          d1=(1.-vCFL*vCFL)*oneSixth
89          d1=(1.-cfl*cfl)*oneSixth  #ifdef OLD_DST3_FORMULATION
90  c       thetaP=0.          IF ( ABS(Rj).LT.smallNo .OR.
91  c       IF (Rj.NE.0.) thetaP=Rjm/Rj       &       ABS(Rjm).LT.smallNo ) THEN
92          thetaP=Rjm/(1.D-20+Rj)           thetaP=0.
93          psiP=d0+d1*thetaP           psiP=0.
94  c       psiP=max(0.,min(min(1.,psiP),(1.-cfl)/(1.D-20+cfl)*thetaP))          ELSE
95          thetaM=Rjp/(1.D-20+Rj)           thetaP=(Rjm+smallNo)/(smallNo+Rj)
96  c       thetaM=0.           psiP=d0+d1*thetaP
97  c       IF (Rj.NE.0.) thetaM=Rjp/Rj          ENDIF
98          psiM=d0+d1*thetaM          IF ( ABS(Rj).LT.smallNo .OR.
99  c       psiM=max(0.,min(min(1.,psiM),(1.-cfl)/(1.D-20+cfl)*thetaM))       &       ABS(Rjp).LT.smallNo ) THEN
100             thetaM=0.
101             psiM=0.
102            ELSE
103             thetaM=(Rjp+smallNo)/(smallNo+Rj)
104             psiM=d0+d1*thetaM
105            ENDIF
106          vT(i,j)=          vT(i,j)=
107       &   0.5*(vTrans(i,j)+abs(vTrans(i,j)))       &   0.5*(vTrans(i,j)+ABS(vTrans(i,j)))
108       &      *( Tracer(i,j-1) + psiP*Rj )       &      *( Tracer(i,j-1) + psiP*Rj )
109       &  +0.5*(vTrans(i,j)-abs(vTrans(i,j)))       &  +0.5*(vTrans(i,j)-ABS(vTrans(i,j)))
110       &      *( Tracer(i, j ) - psiM*Rj )       &      *( Tracer(i, j ) - psiM*Rj )
111    #else /* OLD_DST3_FORMULATION */
112            vT(i,j)=
113         &   0.5*(vTrans(i,j)+ABS(vTrans(i,j)))
114         &      *( Tracer(i,j-1) + (d0*Rj+d1*Rjm) )
115         &  +0.5*(vTrans(i,j)-ABS(vTrans(i,j)))
116         &      *( Tracer(i, j ) - (d0*Rj+d1*Rjp) )
117    #endif /* OLD_DST3_FORMULATION */
118    
119         ENDDO         ENDDO
120        ENDDO        ENDDO

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

  ViewVC Help
Powered by ViewVC 1.1.22