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

Annotation of /MITgcm/pkg/generic_advdiff/gad_os7mp_adv_x.F

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


Revision 1.1 - (hide annotations) (download)
Sat Jan 20 21:20:11 2007 UTC (17 years, 3 months ago) by adcroft
Branch: MAIN
Added new advection scheme, OS7MP, which is seventh order and monotonicity preserving (note: not the same as monotonic!)
 o enabled with advScheme set to "7". (Who chose 77 for Superbee? Oh, that was me ...)
 o scheme requires a halo of 4
   - no error checking for this at the moment
 o scheme is coded for convenience rather than efficiency
   - can easily switch down order or select the TVD limiter by commenting lines
   - the y direction is coded with invert do i; do j loops (for now)

1 adcroft 1.1 C $Header: $
2     C $Name: $
3    
4     #include "GAD_OPTIONS.h"
5    
6     SUBROUTINE GAD_OS7MP_ADV_X(
7     I bi,bj,k,deltaTloc,
8     I uTrans, uFld,
9     I maskLocW, Q,
10     O uT,
11     I myThid )
12     C /==========================================================\
13     C | SUBROUTINE GAD_OS7MP_ADV_X |
14     C | o Compute Zonal advective Flux of tracer Q using |
15     C | 7th Order DST Sceheme with monotone preserving limiter |
16     C |==========================================================|
17     IMPLICIT NONE
18    
19     C == GLobal variables ==
20     #include "SIZE.h"
21     #include "GRID.h"
22     #include "GAD.h"
23    
24     C == Routine arguments ==
25     INTEGER bi,bj,k
26     _RL deltaTloc
27     _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
28     _RL uFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
29     _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
30     _RL Q (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
31     _RL uT (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
32     INTEGER myThid
33    
34     C == Local variables ==
35     INTEGER i,j
36     _RL cfl,Psi
37     _RL uLoc,Fac,Del,DelIp,DelI,Phi,Eps,rp1h,Msk
38     _RL Qippp,Qipp,Qip,Qi,Qim,Qimm,Qimmm
39     _RL MskIpp,MskIp,MskI,MskIm,MskImm,MskImmm
40     _RL d2,d2p1,d2m1,A,B,C,D
41     _RL dp1h,dm1h,qMD,qUL,qLC,PhiMD,PhiLC,PhiMin,PhiMax
42    
43     Eps = 1. _d -20
44    
45     DO j=1-Oly,sNy+Oly
46     uT(1-Olx,j)=0. _d 0
47     uT(2-Olx,j)=0. _d 0
48     uT(3-Olx,j)=0. _d 0
49     uT(4-Olx,j)=0. _d 0
50     uT(sNx+Olx-2,j)=0. _d 0
51     uT(sNx+Olx-1,j)=0. _d 0
52     uT(sNx+Olx,j)=0. _d 0
53     DO i=1-Olx+4,sNx+Olx-3
54    
55     uLoc = uFld(i,j)
56     cfl = abs(uLoc*deltaTloc*recip_dxC(i,j,bi,bj))
57    
58     IF (uLoc.gt.0.) THEN
59     Qippp = Q(i+2,j)
60     Qipp = Q(i+1,j)
61     Qip = Q(i,j)
62     Qi = Q(i-1,j)
63     Qim = Q(i-2,j)
64     Qimm = Q(i-3,j)
65     Qimmm = Q(i-4,j)
66    
67     MskIpp = maskLocW(i+2,j)
68     MskIp = maskLocW(i+1,j)
69     MskI = maskLocW(i,j)
70     MskIm = maskLocW(i-1,j)
71     MskImm = maskLocW(i-2,j)
72     MskImmm = maskLocW(i-3,j)
73     ELSEIF (uLoc.lt.0.) THEN
74     Qippp = Q(i-3,j)
75     Qipp = Q(i-2,j)
76     Qip = Q(i-1,j)
77     Qi = Q(i,j)
78     Qim = Q(i+1,j)
79     Qimm = Q(i+2,j)
80     Qimmm = Q(i+3,j)
81    
82     MskIpp = maskLocW(i-2,j)
83     MskIp = maskLocW(i-1,j)
84     MskI = maskLocW(i,j)
85     MskIm = maskLocW(i+1,j)
86     MskImm = maskLocW(i+2,j)
87     MskImmm = maskLocW(i+3,j)
88     ENDIF
89    
90     IF (uLoc.ne.0.) THEN
91     C 2nd order correction [i i-1]
92     Fac = 1.
93     Del = Qip-Qi
94     Msk = MskI
95     Phi = Msk * Fac * Del
96     C 3rd order correction [i i-1 i-2]
97     Fac = Fac * ( cfl + 1. )/3.
98     Del = Del - ( Qi-Qim )
99     Msk = Msk * MskIm
100     Phi = Phi - Msk * Fac * Del
101     C 4th order correction [i+1 i i-1 i-2]
102     Fac = Fac * ( cfl - 2. )/4.
103     Del = ( Qipp-2.*Qip+Qi ) - Del
104     Msk = Msk * MskIp
105     Phi = Phi + Msk * Fac * Del
106     C 5th order correction [i+1 i i-1 i-2 i-3]
107     Fac = Fac * ( cfl - 3. )/5.
108     Del = Del - ( Qip-3.*Qi+3.*Qim-Qimm )
109     Msk = Msk * MskImm
110     Phi = Phi + Msk * Fac * Del
111     C 6th order correction [i+2 i+1 i i-1 i-2 i-3]
112     Fac = Fac * ( cfl + 2. )/6.
113     Del = ( Qippp-4.*Qipp+6.*Qip-4.*Qi+Qim ) - Del
114     Msk = Msk * MskIpp
115     Phi = Phi + Msk * Fac * Del
116     C 7th order correction [i+2 i+1 i i-1 i-2 i-3 i-4]
117     Fac = Fac * ( cfl + 2. )/7.
118     Del = Del - ( Qipp-5.*Qip+10.*Qi-10.*Qim+5.*Qimm-Qimmm )
119     Msk = Msk * MskImmm
120     Phi = Phi - Msk * Fac * Del
121    
122     DelIp = ( Qip - Qi ) * MskI
123     Phi = sign(1.,Phi)*sign(1.,DelIp)*abs(Phi+Eps)/abs(DelIp+Eps)
124    
125     DelI = ( Qi - Qim ) * MskIm
126     rp1h =sign(1.,DelI)*sign(1.,DelIp)*abs(DelI+Eps)/abs(DelIp+Eps)
127    
128     C TVD limiter
129     ! Phi = max(0., min( 2./(1-cfl), Phi, 2.*rp1h/cfl ) )
130    
131     C MP limiter
132     d2 = ( ( Qip + Qim ) - 2.*Qi ) * MskI * MskIm
133     d2p1 = ( ( Qipp + Qi ) - 2.*Qip ) * MskIp * MskI
134     d2m1 = ( ( Qi + Qimm ) - 2.*Qim ) * MskIm * MskImm
135     A = 4.*d2 - d2p1
136     B = 4.*d2p1 - d2
137     C = d2
138     D = d2p1;
139     dp1h = max(min(A,B,C,D),0.)+min(max(A,B,C,D),0.)
140     A = 4.*d2m1 - d2
141     B = 4.*d2 - d2m1
142     C = d2m1
143     D = d2;
144     dm1h = max(min(A,B,C,D),0.)+min(max(A,B,C,D),0.)
145     qMD = 0.5*( ( Qi + Qip ) - dp1h )
146     qUL = Qi + (1.-cfl)/cfl*( Qi-Qim )
147     qLC = Qi + 0.5*( 1.+dm1h/(Qi-Qim+Eps) )*(qUL-Qi)
148     PhiMD = 2./(1.-cfl)*(qMD-Qi+Eps)/(Qip-Qi+Eps)
149     PhiLC = 2.*rp1h/cfl*(qLC-Qi+Eps)/(qUL-Qi+Eps)
150     PhiMin = max(min(0.,PhiMD),min(0.,2.*rp1h/cfl,PhiLC))
151     PhiMax = min(max(2./(1.-cfl),PhiMD),max(0.,2.*rp1h/cfl,PhiLC))
152     Phi = max(PhiMin,min(Phi,PhiMax))
153    
154     Psi = Phi * 0.5 * (1. - cfl)
155     uT(i,j) = uTrans(i,j)*( Qi + Psi*DelIp )
156     ELSE
157     uT(i,j) = 0.
158     ENDIF
159    
160     ENDDO
161     ENDDO
162    
163     RETURN
164     END

  ViewVC Help
Powered by ViewVC 1.1.22