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

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

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

revision 1.4 by jmc, Wed Mar 6 01:29:36 2002 UTC revision 1.12 by mlosch, Fri Feb 29 01:30:59 2008 UTC
# Line 7  CBOP Line 7  CBOP
7  C !ROUTINE: GAD_FLUXLIMIT_ADV_X  C !ROUTINE: GAD_FLUXLIMIT_ADV_X
8    
9  C !INTERFACE: ==========================================================  C !INTERFACE: ==========================================================
10        SUBROUTINE GAD_FLUXLIMIT_ADV_X(        SUBROUTINE GAD_FLUXLIMIT_ADV_X(
11       I           bi,bj,k,deltaT,       I           bi,bj,k, calcCFL, deltaTloc,
12       I           uTrans, uVel,       I           uTrans, uFld,
13       I           tracer,       I           maskLocW, tracer,
14       O           uT,       O           uT,
15       I           myThid )       I           myThid )
16    
# Line 18  C !DESCRIPTION: Line 18  C !DESCRIPTION:
18  C Calculates the area integrated zonal flux due to advection of a tracer  C Calculates the area integrated zonal flux due to advection of a tracer
19  C using second-order interpolation with a flux limiter:  C using second-order interpolation with a flux limiter:
20  C \begin{equation*}  C \begin{equation*}
21  C F^x_{adv} = U \overline{ \theta }^i  C F^x_{adv} = U \overline{ \theta }^i
22  C - \frac{1}{2} \left(  C - \frac{1}{2} \left(
23  C     [ 1 - \psi(C_r) ] |U|  C     [ 1 - \psi(C_r) ] |U|
24  C    + U \frac{u \Delta t}{\Delta x_c} \psi(C_r)  C    + U \frac{u \Delta t}{\Delta x_c} \psi(C_r)
# Line 33  C !USES: =============================== Line 33  C !USES: ===============================
33  #include "GRID.h"  #include "GRID.h"
34    
35  C !INPUT PARAMETERS: ===================================================  C !INPUT PARAMETERS: ===================================================
36  C  bi,bj                :: tile indices  C  bi,bj             :: tile indices
37  C  k                    :: vertical level  C  k                 :: vertical level
38  C  uTrans               :: zonal volume transport  C  calcCFL           :: =T: calculate CFL number ; =F: take uFld as CFL
39  C  uVel                 :: zonal flow  C  deltaTloc         :: local time-step (s)
40  C  tracer               :: tracer field  C  uTrans            :: zonal volume transport
41  C  myThid               :: thread number  C  uFld              :: zonal flow / CFL number
42    C  tracer            :: tracer field
43    C  myThid            :: thread number
44        INTEGER bi,bj,k        INTEGER bi,bj,k
45        _RL deltaT        LOGICAL calcCFL
46          _RL deltaTloc
47        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
48        _RL uVel  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)        _RL uFld  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
49          _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
50        _RL tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
51        INTEGER myThid        INTEGER myThid
52    
53  C !OUTPUT PARAMETERS: ==================================================  C !OUTPUT PARAMETERS: ==================================================
54  C  uT                   :: zonal advective flux  C  uT                :: zonal advective flux
55        _RL uT    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uT    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
56    
57  C !LOCAL VARIABLES: ====================================================  C !LOCAL VARIABLES: ====================================================
58  C  i,j                  :: loop indices  C  i,j               :: loop indices
59  C  Cr                   :: slope ratio  C  Cr                :: slope ratio
60  C  Rjm,Rj,Rjp           :: differences at i-1,i,i+1  C  Rjm,Rj,Rjp        :: differences at i-1,i,i+1
 C  uFld                 :: velocity [m/s], zonal component  
61        INTEGER i,j        INTEGER i,j
62        _RL Cr,Rjm,Rj,Rjp        _RL Cr,Rjm,Rj,Rjp
63        _RL uFld        _RL uCFL
64  C Statement function provides Limiter(Cr)  C Statement function provides Limiter(Cr)
65  #include "GAD_FLUX_LIMITER.h"  #include "GAD_FLUX_LIMITER.h"
66  CEOP  CEOP
# Line 66  CEOP Line 69  CEOP
69         uT(1-Olx,j)=0.         uT(1-Olx,j)=0.
70         uT(2-Olx,j)=0.         uT(2-Olx,j)=0.
71         uT(sNx+Olx,j)=0.         uT(sNx+Olx,j)=0.
72          ENDDO
73          DO j=1-Oly,sNy+Oly
74         DO i=1-Olx+2,sNx+Olx-1         DO i=1-Olx+2,sNx+Olx-1
75    
76  c       uFld = uVel(i,j,k,bi,bj)          uCFL = uFld(i,j)
77          uFld = uTrans(i,j)*recip_dyG(i,j,bi,bj)          IF ( calcCFL ) uCFL = ABS( uFld(i,j)*deltaTloc
78       &       *recip_drF(k)*recip_hFacW(i,j,k,bi,bj)       &                  *recip_dxC(i,j,bi,bj)*recip_deepFacC(k) )
79          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)
80          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)
81          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)
82    
83          IF (Rj.NE.0.) THEN          IF (Rj.NE.0.) THEN
84           IF (uTrans(i,j).GT.0) THEN           IF (uTrans(i,j).GT.0) THEN
# Line 89  c       uFld = uVel(i,j,k,bi,bj) Line 94  c       uFld = uVel(i,j,k,bi,bj)
94           ENDIF           ENDIF
95          ENDIF          ENDIF
96          Cr=Limiter(Cr)          Cr=Limiter(Cr)
97          uT(i,j) =          uT(i,j) =
98       &   uTrans(i,j)*(Tracer(i,j)+Tracer(i-1,j))*0.5 _d 0       &   uTrans(i,j)*(Tracer(i,j)+Tracer(i-1,j))*0.5 _d 0
99       &   -0.5*(       &   -ABS(uTrans(i,j))*((1.-Cr)+uCFL*Cr)
100       &        (1-Cr)*ABS(uTrans(i,j))       &                    *Rj*0.5 _d 0
      &        +uTrans(i,j)*uFld*deltaT  
      &         *recip_dxC(i,j,bi,bj)*Cr  
      &        )*Rj  
101         ENDDO         ENDDO
102        ENDDO        ENDDO
103    

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

  ViewVC Help
Powered by ViewVC 1.1.22