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

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

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


Revision 1.4 - (hide annotations) (download)
Fri May 11 17:30:06 2007 UTC (17 years, 1 month ago) by adcroft
Branch: MAIN
Changes since 1.3: +12 -11 lines
Bug fix: added "Eps" to expressions deviding by cfl.
 - This singular expression was giving problems in the DOME experiments.

1 adcroft 1.4 C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_os7mp_adv_y.F,v 1.3 2007/04/04 01:39:06 jmc Exp $
2 mlosch 1.2 C $Name: $
3 adcroft 1.1
4     #include "GAD_OPTIONS.h"
5    
6     SUBROUTINE GAD_OS7MP_ADV_Y(
7 jmc 1.3 I bi,bj,k, calcCFL, deltaTloc,
8 adcroft 1.1 I vTrans, vFld,
9     I maskLocS, Q,
10     O vT,
11     I myThid )
12     C /==========================================================\
13     C | SUBROUTINE GAD_OS7MP_ADV_Y |
14     C | o Compute Meridional 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 jmc 1.3 LOGICAL calcCFL
27 adcroft 1.1 _RL deltaTloc
28     _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
29     _RL vFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
30     _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
31     _RL Q (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
32     _RL vT (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
33     INTEGER myThid
34    
35     C == Local variables ==
36     INTEGER i,j
37     _RL cfl,Psi
38 adcroft 1.4 _RL vLoc,Fac,Del,DelIp,DelI,Phi,Eps,rp1h,rp1h_cfl,Msk
39 adcroft 1.1 _RL Qippp,Qipp,Qip,Qi,Qim,Qimm,Qimmm
40     _RL MskIpp,MskIp,MskI,MskIm,MskImm,MskImmm
41     _RL d2,d2p1,d2m1,A,B,C,D
42     _RL dp1h,dm1h,qMD,qUL,qLC,PhiMD,PhiLC,PhiMin,PhiMax
43    
44     Eps = 1. _d -20
45    
46     DO i=1-Olx,sNx+Olx
47     vT(i,1-Oly)=0. _d 0
48     vT(i,2-Oly)=0. _d 0
49     vT(i,3-Oly)=0. _d 0
50     vT(i,4-Oly)=0. _d 0
51     vT(i,sNy+Oly-2)=0. _d 0
52     vT(i,sNy+Oly-1)=0. _d 0
53     vT(i,sNy+Oly)=0. _d 0
54     ENDDO
55     DO j=1-Oly+4,sNy+Oly-3
56     DO i=1-Olx,sNx+Olx
57    
58     vLoc = vFld(i,j)
59 jmc 1.3 cfl = vLoc
60     IF ( calcCFL ) cfl = abs(vLoc*deltaTloc*recip_dyC(i,j,bi,bj))
61 adcroft 1.1
62 adcroft 1.4 IF (vTrans(i,j).gt.0.) THEN
63 adcroft 1.1 Qippp = Q(i,j+2)
64     Qipp = Q(i,j+1)
65     Qip = Q(i,j)
66     Qi = Q(i,j-1)
67     Qim = Q(i,j-2)
68     Qimm = Q(i,j-3)
69     Qimmm = Q(i,j-4)
70    
71     MskIpp = maskLocS(i,j+2)
72     MskIp = maskLocS(i,j+1)
73     MskI = maskLocS(i,j)
74     MskIm = maskLocS(i,j-1)
75     MskImm = maskLocS(i,j-2)
76     MskImmm = maskLocS(i,j-3)
77 adcroft 1.4 ELSEIF (vTrans(i,j).lt.0.) THEN
78 adcroft 1.1 Qippp = Q(i,j-3)
79     Qipp = Q(i,j-2)
80     Qip = Q(i,j-1)
81     Qi = Q(i,j)
82     Qim = Q(i,j+1)
83     Qimm = Q(i,j+2)
84     Qimmm = Q(i,j+3)
85    
86     MskIpp = maskLocS(i,j-2)
87     MskIp = maskLocS(i,j-1)
88     MskI = maskLocS(i,j)
89     MskIm = maskLocS(i,j+1)
90     MskImm = maskLocS(i,j+2)
91     MskImmm = maskLocS(i,j+3)
92     ENDIF
93    
94 adcroft 1.4 IF (vTrans(i,j).ne.0.) THEN
95 adcroft 1.1 C 2nd order correction [i i-1]
96     Fac = 1.
97     Del = Qip-Qi
98     Msk = MskI
99     Phi = Msk * Fac * Del
100     C 3rd order correction [i i-1 i-2]
101     Fac = Fac * ( cfl + 1. )/3.
102     Del = Del - ( Qi-Qim )
103     Msk = Msk * MskIm
104     Phi = Phi - Msk * Fac * Del
105     C 4th order correction [i+1 i i-1 i-2]
106     Fac = Fac * ( cfl - 2. )/4.
107     Del = ( Qipp-2.*Qip+Qi ) - Del
108     Msk = Msk * MskIp
109     Phi = Phi + Msk * Fac * Del
110     C 5th order correction [i+1 i i-1 i-2 i-3]
111     Fac = Fac * ( cfl - 3. )/5.
112     Del = Del - ( Qip-3.*Qi+3.*Qim-Qimm )
113     Msk = Msk * MskImm
114     Phi = Phi + Msk * Fac * Del
115     C 6th order correction [i+2 i+1 i i-1 i-2 i-3]
116     Fac = Fac * ( cfl + 2. )/6.
117     Del = ( Qippp-4.*Qipp+6.*Qip-4.*Qi+Qim ) - Del
118     Msk = Msk * MskIpp
119     Phi = Phi + Msk * Fac * Del
120     C 7th order correction [i+2 i+1 i i-1 i-2 i-3 i-4]
121     Fac = Fac * ( cfl + 2. )/7.
122     Del = Del - ( Qipp-5.*Qip+10.*Qi-10.*Qim+5.*Qimm-Qimmm )
123     Msk = Msk * MskImmm
124     Phi = Phi - Msk * Fac * Del
125    
126     DelIp = ( Qip - Qi ) * MskI
127 mlosch 1.2 Phi = sign(1. _d 0,Phi)*sign(1. _d 0,DelIp)
128     & *abs(Phi+Eps)/abs(DelIp+Eps)
129 adcroft 1.1
130     DelI = ( Qi - Qim ) * MskIm
131 mlosch 1.2 rp1h =sign(1. _d 0,DelI)*sign(1. _d 0,DelIp)
132     & *abs(DelI+Eps)/abs(DelIp+Eps)
133 adcroft 1.4 rp1h_cfl = rp1h/(cfl+Eps)
134 adcroft 1.1
135     C TVD limiter
136 adcroft 1.4 ! Phi = max(0. _d 0, min( 2./(1-cfl), Phi, 2.*rp1h_cfl ) )
137 adcroft 1.1
138     C MP limiter
139     d2 = ( ( Qip + Qim ) - 2.*Qi ) * MskI * MskIm
140     d2p1 = ( ( Qipp + Qi ) - 2.*Qip ) * MskIp * MskI
141     d2m1 = ( ( Qi + Qimm ) - 2.*Qim ) * MskIm * MskImm
142     A = 4.*d2 - d2p1
143     B = 4.*d2p1 - d2
144     C = d2
145     D = d2p1;
146 mlosch 1.2 dp1h = max(min(A,B,C,D),0. _d 0)+min(max(A,B,C,D),0. _d 0)
147 adcroft 1.1 A = 4.*d2m1 - d2
148     B = 4.*d2 - d2m1
149     C = d2m1
150     D = d2;
151 mlosch 1.2 dm1h = max(min(A,B,C,D),0. _d 0)+min(max(A,B,C,D),0. _d 0)
152 adcroft 1.1 qMD = 0.5*( ( Qi + Qip ) - dp1h )
153 adcroft 1.4 qUL = Qi + (1.-cfl)/(cfl+Eps)*( Qi-Qim )
154 adcroft 1.1 qLC = Qi + 0.5*( 1.+dm1h/(Qi-Qim+Eps) )*(qUL-Qi)
155     PhiMD = 2./(1.-cfl)*(qMD-Qi+Eps)/(Qip-Qi+Eps)
156 adcroft 1.4 PhiLC = 2.*rp1h_cfl*(qLC-Qi+Eps)/(qUL-Qi+Eps)
157 mlosch 1.2 PhiMin = max(min(0. _d 0,PhiMD),
158 adcroft 1.4 & min(0. _d 0,2.*rp1h_cfl,PhiLC))
159 mlosch 1.2 PhiMax = min(max(2. _d 0/(1.-cfl),PhiMD),
160 adcroft 1.4 & max(0. _d 0,2.*rp1h_cfl,PhiLC))
161 adcroft 1.1 Phi = max(PhiMin,min(Phi,PhiMax))
162    
163     Psi = Phi * 0.5 * (1. - cfl)
164     vT(i,j) = vTrans(i,j)*( Qi + Psi*DelIp )
165     ELSE
166 adcroft 1.4 vT(i,j) = 0.
167 adcroft 1.1 ENDIF
168    
169     ENDDO
170     ENDDO
171    
172     RETURN
173     END

  ViewVC Help
Powered by ViewVC 1.1.22