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

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

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

revision 1.2 by mlosch, Sun Jan 21 17:25:31 2007 UTC revision 1.7 by mlosch, Fri Oct 5 10:50:47 2007 UTC
# Line 4  C $Name$ Line 4  C $Name$
4  #include "GAD_OPTIONS.h"  #include "GAD_OPTIONS.h"
5    
6        SUBROUTINE GAD_OS7MP_ADV_X(        SUBROUTINE GAD_OS7MP_ADV_X(
7       I           bi,bj,k,deltaTloc,       I           bi,bj,k, calcCFL, deltaTloc,
8       I           uTrans, uFld,       I           uTrans, uFld,
9       I           maskLocW, Q,       I           maskLocW, Q,
10       O           uT,       O           uT,
# Line 23  C     == GLobal variables == Line 23  C     == GLobal variables ==
23    
24  C     == Routine arguments ==  C     == Routine arguments ==
25        INTEGER bi,bj,k        INTEGER bi,bj,k
26          LOGICAL calcCFL
27        _RL deltaTloc        _RL deltaTloc
28        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
29        _RL uFld  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uFld  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 34  C     == Routine arguments == Line 35  C     == Routine arguments ==
35  C     == Local variables ==  C     == Local variables ==
36        INTEGER i,j        INTEGER i,j
37        _RL cfl,Psi        _RL cfl,Psi
38        _RL uLoc,Fac,Del,DelIp,DelI,Phi,Eps,rp1h,Msk        _RL uLoc,Fac,DelIp,DelI,Phi,Eps,rp1h,rp1h_cfl
39        _RL Qippp,Qipp,Qip,Qi,Qim,Qimm,Qimmm        _RL Qippp,Qipp,Qip,Qi,Qim,Qimm,Qimmm
40        _RL MskIpp,MskIp,MskI,MskIm,MskImm,MskImmm        _RL MskIpp,MskIp,MskI,MskIm,MskImm,MskImmm
41        _RL d2,d2p1,d2m1,A,B,C,D        _RL d2,d2p1,d2m1,A,B,C,D
42        _RL dp1h,dm1h,qMD,qUL,qLC,PhiMD,PhiLC,PhiMin,PhiMax        _RL dp1h,dm1h,qMD,qUL,qLC,PhiMD,PhiLC,PhiMin,PhiMax
43          _RL DelM,DelP,DelMM,DelPP,DelMMM,DelPPP
44          _RL Del2MM,Del2M,Del2,Del2P,Del2PP
45          _RL Del3MM,Del3M,Del3P,Del3PP
46          _RL Del4M,Del4,Del4P
47          _RL Del5M,Del5P
48          _RL Del6
49    
50        Eps = 1. _d -20        Eps = 1. _d -20
51    
# Line 53  C     == Local variables == Line 60  C     == Local variables ==
60         DO i=1-Olx+4,sNx+Olx-3         DO i=1-Olx+4,sNx+Olx-3
61    
62          uLoc = uFld(i,j)          uLoc = uFld(i,j)
63          cfl = abs(uLoc*deltaTloc*recip_dxC(i,j,bi,bj))          cfl = uLoc
64            IF ( calcCFL ) cfl = abs(uLoc*deltaTloc*recip_dxC(i,j,bi,bj))
65    
66          IF (uLoc.gt.0.) THEN          IF (uTrans(i,j).gt.0.) THEN
67           Qippp = Q(i+2,j)           Qippp = Q(i+2,j)
68           Qipp  = Q(i+1,j)           Qipp  = Q(i+1,j)
69           Qip   = Q(i,j)           Qip   = Q(i,j)
# Line 70  C     == Local variables == Line 78  C     == Local variables ==
78           MskIm   = maskLocW(i-1,j)           MskIm   = maskLocW(i-1,j)
79           MskImm  = maskLocW(i-2,j)           MskImm  = maskLocW(i-2,j)
80           MskImmm = maskLocW(i-3,j)           MskImmm = maskLocW(i-3,j)
81          ELSEIF (uLoc.lt.0.) THEN          ELSEIF (uTrans(i,j).lt.0.) THEN
82           Qippp = Q(i-3,j)           Qippp = Q(i-3,j)
83           Qipp  = Q(i-2,j)           Qipp  = Q(i-2,j)
84           Qip   = Q(i-1,j)           Qip   = Q(i-1,j)
# Line 85  C     == Local variables == Line 93  C     == Local variables ==
93           MskIm   = maskLocW(i+1,j)           MskIm   = maskLocW(i+1,j)
94           MskImm  = maskLocW(i+2,j)           MskImm  = maskLocW(i+2,j)
95           MskImmm = maskLocW(i+3,j)           MskImmm = maskLocW(i+3,j)
96            ELSE
97             Qippp = 0. _d 0
98             Qipp  = 0. _d 0
99             Qip   = 0. _d 0
100             Qi    = 0. _d 0
101             Qim   = 0. _d 0
102             Qimm  = 0. _d 0
103             Qimmm = 0. _d 0
104    
105             MskIpp  = 0. _d 0
106             MskIp   = 0. _d 0
107             MskI    = 0. _d 0
108             MskIm   = 0. _d 0
109             MskImm  = 0. _d 0
110             MskImmm = 0. _d 0
111          ENDIF          ENDIF
112    
113          IF (uLoc.ne.0.) THEN          IF (uTrans(i,j).ne.0.) THEN
114  C        2nd order correction [i i-1]  C        2nd order correction [i i-1]
115           Fac = 1.           Fac = 1.
116           Del = Qip-Qi           DelP = (Qip-Qi)*MskI
117           Msk = MskI           Phi = Fac * DelP
          Phi = Msk * Fac * Del  
118  C        3rd order correction [i i-1 i-2]  C        3rd order correction [i i-1 i-2]
119           Fac = Fac * ( cfl + 1. )/3.           Fac = Fac * ( cfl + 1. )/3.
120           Del = Del - ( Qi-Qim )           DelM = (Qi-Qim)*MskIm
121           Msk = Msk * MskIm           Del2 = DelP - DelM
122           Phi = Phi - Msk * Fac * Del           Phi = Phi - Fac * Del2
123  C        4th order correction [i+1 i i-1 i-2]  C        4th order correction [i+1 i i-1 i-2]
124           Fac = Fac * ( cfl - 2. )/4.           Fac = Fac * ( cfl - 2. )/4.
125           Del = ( Qipp-2.*Qip+Qi ) - Del           DelPP = (Qipp-Qip)*MskIp*MskI
126           Msk = Msk * MskIp           Del2P = DelPP - DelP
127           Phi = Phi + Msk * Fac * Del           Del3P = Del2P - Del2
128             Phi = Phi + Fac * Del3p
129  C        5th order correction [i+1 i i-1 i-2 i-3]  C        5th order correction [i+1 i i-1 i-2 i-3]
130           Fac = Fac * ( cfl - 3. )/5.           Fac = Fac * ( cfl - 3. )/5.
131           Del = Del - ( Qip-3.*Qi+3.*Qim-Qimm )           DelMM = (Qim-Qimm)*MskImm*MskIm
132           Msk = Msk * MskImm           Del2M = DelM - DelMM
133           Phi = Phi + Msk * Fac * Del           Del3M = Del2 - Del2M
134             Del4 = Del3P - Del3M
135             Phi = Phi + Fac * Del4
136  C        6th order correction [i+2 i+1 i i-1 i-2 i-3]  C        6th order correction [i+2 i+1 i i-1 i-2 i-3]
137           Fac = Fac * ( cfl + 2. )/6.           Fac = Fac * ( cfl + 2. )/6.
138           Del = ( Qippp-4.*Qipp+6.*Qip-4.*Qi+Qim ) - Del           DelPPP = (Qippp-Qipp)*MskIpp*MskIp*MskI
139           Msk = Msk * MskIpp           Del2PP = DelPP - DelP
140           Phi = Phi + Msk * Fac * Del           Del3PP = Del2PP - Del2P
141             Del4P = Del3PP - Del3P
142             Del5P = Del4P - Del4
143             Phi = Phi + Fac * Del5P
144  C        7th order correction [i+2 i+1 i i-1 i-2 i-3 i-4]  C        7th order correction [i+2 i+1 i i-1 i-2 i-3 i-4]
145           Fac = Fac * ( cfl + 2. )/7.           Fac = Fac * ( cfl + 2. )/7.
146           Del = Del - ( Qipp-5.*Qip+10.*Qi-10.*Qim+5.*Qimm-Qimmm )           DelMMM = (Qimm-Qimmm)*MskImmm*MskImm*MskIm
147           Msk = Msk * MskImmm           Del2MM = DelMM - DelMMM
148           Phi = Phi - Msk * Fac * Del           Del3MM = Del2M - Del2MM
149             Del4M = Del3M - Del3MM
150             Del5M = Del4 - Del4M
151             Del6 = Del5P - Del5M
152             Phi = Phi - Fac * Del6
153    
154           DelIp = ( Qip - Qi ) * MskI           DelIp = ( Qip - Qi ) * MskI
155           Phi = sign(1. _d 0,Phi)*sign(1. _d 0,DelIp)           Phi = sign(1. _d 0,Phi)*sign(1. _d 0,DelIp)
# Line 126  C        7th order correction [i+2 i+1 i Line 158  C        7th order correction [i+2 i+1 i
158           DelI = ( Qi - Qim ) * MskIm           DelI = ( Qi - Qim ) * MskIm
159           rp1h =sign(1. _d 0,DelI)*sign(1. _d 0,DelIp)           rp1h =sign(1. _d 0,DelI)*sign(1. _d 0,DelIp)
160       &        *abs(DelI+Eps)/abs(DelIp+Eps)       &        *abs(DelI+Eps)/abs(DelIp+Eps)
161             rp1h_cfl = rp1h/(cfl+Eps)
162    
163  C        TVD limiter  C        TVD limiter
164  !        Phi = max(0. _d 0, min( 2./(1-cfl), Phi, 2.*rp1h/cfl ) )  !        Phi = max(0. _d 0, min( 2./(1-cfl), Phi, 2.*rp1h_cfl ) )
165    
166  C        MP limiter  C        MP limiter
167           d2   = ( ( Qip + Qim ) - 2.*Qi  ) * MskI * MskIm           d2   = Del2 !( ( Qip + Qim ) - 2.*Qi  ) * MskI * MskIm
168           d2p1 = ( ( Qipp + Qi ) - 2.*Qip ) * MskIp * MskI           d2p1 = Del2P !( ( Qipp + Qi ) - 2.*Qip ) * MskIp * MskI
169           d2m1 = ( ( Qi + Qimm ) - 2.*Qim ) * MskIm * MskImm           d2m1 = Del2M !( ( Qi + Qimm ) - 2.*Qim ) * MskIm * MskImm
170           A = 4.*d2 - d2p1           A = 4.*d2 - d2p1
171           B = 4.*d2p1 - d2           B = 4.*d2p1 - d2
172           C = d2           C = d2
173           D = d2p1;           D = d2p1
174           dp1h = max(min(A,B,C,D),0. _d 0)+min(max(A,B,C,D),0. _d 0)           dp1h = max(min(A,B,C,D),0. _d 0)+min(max(A,B,C,D),0. _d 0)
175           A = 4.*d2m1 - d2           A = 4.*d2m1 - d2
176           B = 4.*d2 - d2m1           B = 4.*d2 - d2m1
177           C = d2m1           C = d2m1
178           D = d2;           D = d2
179           dm1h = max(min(A,B,C,D),0. _d 0)+min(max(A,B,C,D),0. _d 0)           dm1h = max(min(A,B,C,D),0. _d 0)+min(max(A,B,C,D),0. _d 0)
180           qMD = 0.5*( ( Qi + Qip ) - dp1h )          !qMD = 0.5*( ( Qi + Qip ) - dp1h )
181           qUL = Qi + (1.-cfl)/cfl*( Qi-Qim )           qMD = 0.5*( ( 2.*Qi + DelIp ) - dp1h )
182           qLC = Qi + 0.5*( 1.+dm1h/(Qi-Qim+Eps) )*(qUL-Qi)           qUL = Qi + (1.-cfl)/(cfl+Eps)*DelI
183           PhiMD = 2./(1.-cfl)*(qMD-Qi+Eps)/(Qip-Qi+Eps)           qLC = Qi + 0.5*( 1.+dm1h/(DelI+Eps) )*(qUL-Qi)
184           PhiLC = 2.*rp1h/cfl*(qLC-Qi+Eps)/(qUL-Qi+Eps)           PhiMD = 2./(1.-cfl)*(qMD-Qi+Eps)/(DelIp+Eps)
185             PhiLC = 2.*rp1h_cfl*(qLC-Qi+Eps)/(qUL-Qi+Eps)
186           PhiMin = max(min(0. _d 0,PhiMD),           PhiMin = max(min(0. _d 0,PhiMD),
187       &        min(0. _d 0,2.*rp1h/cfl,PhiLC))       &        min(0. _d 0,2.*rp1h_cfl,PhiLC))
188           PhiMax = min(max(2. _d 0/(1.-cfl),PhiMD),           PhiMax = min(max(2. _d 0/(1.-cfl),PhiMD),
189       &        max(0. _d 0,2.*rp1h/cfl,PhiLC))       &        max(0. _d 0,2.*rp1h_cfl,PhiLC))
190           Phi = max(PhiMin,min(Phi,PhiMax))           Phi = max(PhiMin,min(Phi,PhiMax))
191    
192           Psi = Phi * 0.5 * (1. - cfl)           Psi = Phi * 0.5 * (1. - cfl)

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

  ViewVC Help
Powered by ViewVC 1.1.22