MPI-AMRVAC  3.0
The MPI - Adaptive Mesh Refinement - Versatile Advection Code
mod_tvd.t
Go to the documentation of this file.
1 !> Subroutines for TVD-MUSCL schemes
2 module mod_tvd
3 
4  implicit none
5  private
6 
7  public :: tvdlimit
8  public :: tvdlimit2
9  public :: entropyfix
10 
11 contains
12 
13  subroutine tvdlimit(method,qdt,ixI^L,ixO^L,idim^LIM,s,qt,snew,fC,dxs,x)
15 
16  integer, intent(in) :: method
17  double precision, intent(in) :: qdt, qt, dxs(ndim)
18  integer, intent(in) :: ixi^l, ixo^l, idim^lim
19  double precision, dimension(ixI^S,nw) :: w, wnew
20  type(state) :: s, snew
21  double precision, intent(in) :: x(ixi^s,1:ndim)
22  double precision :: fc(ixi^s,1:nwflux,1:ndim)
23 
24  integer :: idims, ixic^l, jxic^l
25  double precision, dimension(ixI^S,nw) :: wr, wl
26 
27  associate(w=>s%w,wnew=>snew%w)
28  do idims= idim^lim
29  ixicmax^d=ixomax^d+kr(idims,^d); ixicmin^d=ixomin^d-2*kr(idims,^d);
30  wl(ixic^s,1:nw)=w(ixic^s,1:nw)
31  jxic^l=ixic^l+kr(idims,^d);
32  wr(ixic^s,1:nw)=w(jxic^s,1:nw)
33  call tvdlimit2(method,qdt,ixi^l,ixic^l,ixo^l,idims,wl,wr,wnew,x,fc,dxs)
34  end do
35  end associate
36  end subroutine tvdlimit
37 
38  subroutine tvdlimit2(method,qdt,ixI^L,ixIC^L,ixO^L,idims,wL,wR,wnew,x,fC,dxs)
39 
40  ! Limit the flow variables in wnew according to typetvd.
41  ! wroeC is based on wL and wR.
42  ! If method=fs_tvd an extra adtdx**2*jumpC is added to phiC for 2nd order
43  ! accuracy in time.
44 
46  use mod_physics_roe
47 
48  integer, intent(in) :: method
49  double precision, intent(in) :: qdt, dxs(ndim)
50  integer, intent(in) :: ixi^l, ixic^l, ixo^l, idims
51  double precision, dimension(ixG^T,nw) :: wl, wr
52  double precision, intent(in) :: x(ixi^s,1:ndim)
53  double precision :: wnew(ixi^s,1:nw)
54  double precision :: fc(ixi^s,1:nwflux,1:ndim)
55 
56  double precision:: workroe(ixg^t,1:nworkroe)
57  double precision, dimension(ixG^T,nw) :: wroec
58  double precision, dimension(ixG^T) :: phic, rphic, jumpc, adtdxc, smallac
59  double precision :: dxinv(1:ndim)
60  integer :: hxo^l, ixc^l, jxc^l, jxic^l, iw, il
61  !-----------------------------------------------------------------------------
62 
63  hxo^l=ixo^l-kr(idims,^d);
64  ixcmax^d=ixomax^d; ixcmin^d=hxomin^d;
65 
66  jxc^l=ixc^l+kr(idims,^d);
67  jxic^l=ixic^l+kr(idims,^d);
68 
69  call phys_average(wl,wr,x,ixic^l,idims,wroec,workroe)
70 
71  dxinv=qdt/dxs
72 
73  ! A loop on characteristic variables to calculate the dissipative flux phiC.
74  do il=1,nwflux
75  !Calculate the jump in the il-th characteristic variable: L(wroe)*dw
76  call phys_get_eigenjump(wl,wr,wroec,x,ixic^l,il,idims,smallac,adtdxc,jumpc,workroe)
77 
78  ! Normalize the eigenvalue "a" (and its limit "smalla" if needed):
79  if (slab_uniform) then
80  adtdxc(ixic^s)=adtdxc(ixic^s)*dxinv(idims)
81  if (typeentropy(il)=='harten' .or. typeentropy(il)=='powell')&
82  smallac(ixic^s)=smallac(ixic^s)*dxinv(idims)
83  else
84  adtdxc(ixic^s)=adtdxc(ixic^s)*qdt*block%surfaceC(ixic^s,idims)*&
85  2.0d0/(block%dvolume(ixic^s)+block%dvolume(jxic^s))
86  if (typeentropy(il)=='harten' .or. typeentropy(il)=='powell')&
87  smallac(ixic^s)=smallac(ixic^s)*qdt*block%surfaceC(ixic^s,idims)*&
88  2.0d0/(block%dvolume(ixic^s)+block%dvolume(jxic^s))
89  endif
90 
91  ! Calculate the flux limiter function phi
92  call getphi(method,jumpc,adtdxc,smallac,ixi^l,ixic^l,ixc^l,il,idims,phic)
93 
94  !Add R(iw,il)*phiC(il) to each variable iw in wnew
95  do iw=1,nwflux
96  call phys_rtimes(phic,wroec,ixc^l,iw,il,idims,rphic,workroe)
97 
98  if (slab_uniform) then
99  rphic(ixc^s)=rphic(ixc^s)*half
100  fc(ixc^s,iw,idims)=fc(ixc^s,iw,idims)+rphic(ixc^s)
101  wnew(ixo^s,iw)=wnew(ixo^s,iw)+rphic(ixo^s)-rphic(hxo^s)
102  else
103  rphic(ixc^s)=rphic(ixc^s)*quarter* &
104  (block%dvolume(ixc^s)+block%dvolume(jxc^s))
105  fc(ixc^s,iw,idims)=fc(ixc^s,iw,idims)+rphic(ixc^s)
106  wnew(ixo^s,iw)=wnew(ixo^s,iw)+(rphic(ixo^s)-rphic(hxo^s)) &
107  /block%dvolume(ixo^s)
108  endif
109  end do !iw
110  end do !il
111 
112  end subroutine tvdlimit2
113 
114  subroutine getphi(method,jumpC,adtdxC,smallaC,ixI^L,ixIC^L,ixC^L,il,idims,phiC)
115 
116  ! Calculate the dissipative flux from jumpC=L*dw and adtdx=eigenvalue*dt/dx.
117  ! Add Lax-Wendroff type correction if method=fs_tvd.
118  ! Limit according to method and typetvd.
119  use mod_limiter
121 
122  integer, intent(in) :: method
123  integer, intent(in) :: ixI^L, ixIC^L, ixC^L, il, idims
124  double precision, dimension(ixG^T) :: jumpC, adtdxC, smallaC, phiC
125 
126  double precision, dimension(ixG^T) :: ljumpC, tmp
127  integer :: jxC^L, ix^L, hx^L, typelimiter
128  !-----------------------------------------------------------------------------
129 
130  typelimiter=type_limiter(block%level)
131  if(method==fs_tvdmu)then
132  ! In the MUSCL scheme phi=|a|*jump, apply entropy fix to it
133  if(typeentropy(il)=='nul'.or.typeentropy(il)=='ratio')then
134  phic(ixc^s)=abs(adtdxc(ixc^s))*jumpc(ixc^s)
135  else
136  where(abs(adtdxc(ixc^s))>=smallac(ixc^s))
137  phic(ixc^s)=abs(adtdxc(ixc^s))*jumpc(ixc^s)
138  elsewhere
139  phic(ixc^s)=half*(smallac(ixc^s)+adtdxc(ixc^s)**2/smallac(ixc^s))&
140  *jumpc(ixc^s)
141  endwhere
142  endif
143  ! That's all for the MUSCL scheme
144  return
145  endif
146 
147  if(method==fs_tvd)then
148  !Entropy fix to |a|-a**2
149  if(typeentropy(il)=='nul'.or.typeentropy(il)=='ratio')then
150  phic(ixic^s)=abs(adtdxc(ixic^s))-adtdxc(ixic^s)**2
151  else
152  where(abs(adtdxc(ixic^s))>=smallac(ixic^s))
153  phic(ixic^s)=abs(adtdxc(ixic^s))-adtdxc(ixic^s)**2
154  elsewhere
155  phic(ixic^s)=half*smallac(ixic^s)+&
156  (half/smallac(ixic^s)-one)*adtdxc(ixic^s)**2
157  endwhere
158  endif
159  else
160  !Entropy fix to |a|
161  if(typeentropy(il)=='nul'.or.typeentropy(il)=='ratio')then
162  phic(ixic^s)=abs(adtdxc(ixic^s))
163  else
164  where(abs(adtdxc(ixic^s))>=smallac(ixic^s))
165  phic(ixic^s)=abs(adtdxc(ixic^s))
166  elsewhere
167  phic(ixic^s)=half*smallac(ixic^s)+&
168  half/smallac(ixic^s)*adtdxc(ixic^s)**2
169  endwhere
170  endif
171  endif
172 
173  jxc^l=ixc^l+kr(idims,^d);
174  hxmin^d=ixicmin^d; hxmax^d=ixicmax^d-kr(idims,^d);
175  ix^l=hx^l+kr(idims,^d);
176 
177  if (.not. limiter_symmetric(typelimiter)) then
178  call mpistop("TVD only supports symmetric limiters")
179  end if
180 
181  select case(typetvd)
182  case('roe')
183  call dwlimiter2(jumpc,ixi^l,ixic^l,idims,typelimiter,ldw=ljumpc)
184  where(adtdxc(ixc^s)<=0)
185  phic(ixc^s)=phic(ixc^s)*(jumpc(ixc^s)-ljumpc(jxc^s))
186  elsewhere
187  phic(ixc^s)=phic(ixc^s)*(jumpc(ixc^s)-ljumpc(ixc^s))
188  end where
189  !extra (a*lambda)**2*delta
190  if(method==fs_tvd)phic(ixc^s)=phic(ixc^s)+adtdxc(ixc^s)**2*jumpc(ixc^s)
191  case('sweby')
192  !Sweby eqs.4.11-4.15, but no 0.5 ?!
193  phic(ixic^s)=phic(ixic^s)*jumpc(ixic^s)
194  call dwlimiter2(phic,ixi^l,ixic^l,idims,typelimiter,ldw=ljumpc)
195  where(adtdxc(ixc^s)<=0)
196  phic(ixc^s)=phic(ixc^s)-ljumpc(jxc^s)
197  elsewhere
198  phic(ixc^s)=phic(ixc^s)-ljumpc(ixc^s)
199  end where
200  !extra (a*lambda)**2*delta
201  if(method==fs_tvd)phic(ixc^s)=phic(ixc^s)+adtdxc(ixc^s)**2*jumpc(ixc^s)
202  case('yee')
203  !eq.3.51 with correction
204  call dwlimiter2(jumpc,ixi^l,ixic^l,idims,typelimiter,ldw=ljumpc)
205 
206  !Use phiC as 0.5*(|nu|-nu**2) eq.3.45e for tvd otherwise 0.5*|nu|
207  phic(ixc^s)=half*phic(ixc^s)
208  !gamma*lambda eq.3.51d, use tmp to store agdtdxC
209  where(abs(jumpc(ixc^s))>smalldouble)
210  tmp(ixc^s)=adtdxc(ixc^s)+phic(ixc^s)*&
211  (ljumpc(jxc^s)-ljumpc(ixc^s))/jumpc(ixc^s)
212  elsewhere
213  tmp(ixc^s)=adtdxc(ixc^s)
214  end where
215 
216  !eq.3.51a
217  if(typeentropy(il)=='nul'.or.typeentropy(il)=='ratio')then
218  phic(ixc^s)=-phic(ixc^s)*(ljumpc(jxc^s)+ljumpc(ixc^s))+&
219  abs(tmp(ixc^s))*jumpc(ixc^s)
220  else
221  where(abs(tmp(ixc^s))>=smallac(ixc^s))
222  phic(ixc^s)=-phic(ixc^s)*(ljumpc(jxc^s)+ljumpc(ixc^s))+&
223  abs(tmp(ixc^s))*jumpc(ixc^s)
224  elsewhere
225  phic(ixc^s)=-phic(ixc^s)*(ljumpc(jxc^s)+ljumpc(ixc^s))+&
226  (half*smallac(ixc^s)+half/smallac(ixc^s)*&
227  tmp(ixc^s)**2)*jumpc(ixc^s)
228  endwhere
229  endif
230  case('harten')
231  !See Ryu, section 2.3
232  !Use phiC as 0.5*(|nu|-nu**2)*jumpC eq.3.45b,e
233  phic(ixic^s)=half*phic(ixic^s)*jumpc(ixic^s)
234  call dwlimiter2(phic,ixi^l,ixic^l,idims,typelimiter,ldw=ljumpc)
235 
236  !gamma*lambda eq.3.45d, use tmp as agdtdxC
237  where(abs(jumpc(ixc^s))>smalldouble)
238  tmp(ixc^s)=adtdxc(ixc^s)+&
239  (ljumpc(jxc^s)-ljumpc(ixc^s))/jumpc(ixc^s)
240  elsewhere
241  tmp(ixc^s)=adtdxc(ixc^s)
242  end where
243  !eq.3.45a with correction
244  if(typeentropy(il)=='nul'.or.typeentropy(il)=='ratio')then
245  phic(ixc^s)=-ljumpc(jxc^s)-ljumpc(ixc^s)+jumpc(ixc^s)*&
246  abs(tmp(ixc^s))
247  else
248  where(abs(tmp(ixc^s))>=smallac(ixc^s))
249  phic(ixc^s)=-ljumpc(jxc^s)-ljumpc(ixc^s)+jumpc(ixc^s)*&
250  abs(tmp(ixc^s))
251  elsewhere
252  phic(ixc^s)=-ljumpc(jxc^s)-ljumpc(ixc^s)+jumpc(ixc^s)*&
253  (half*smallac(ixc^s)+half/smallac(ixc^s)*tmp(ixc^s)**2)
254  endwhere
255  endif
256  !extra -(a*lambda)**2*delta
257  case default
258  call mpistop("Error in TVDLimit: Unknown TVD type")
259  end select
260 
261  end subroutine getphi
262 
263  subroutine entropyfix(ix^L,il,aL,aR,a,smalla)
264 
265  ! Apply entropyfix based on typeentropy(il),aL,aR, and a
266  ! Calculate "smalla" (Harten,Powell) or modify "a" (ratio)
267 
269 
270  integer, intent(in) :: ix^l, il
271  double precision, dimension(ixG^T) :: al, ar, a, smalla
272  !-----------------------------------------------------------------------------
273 
274  select case(typeentropy(il))
275  case('harten')
276  smalla(ix^s)=max(zero,a(ix^s)-al(ix^s),ar(ix^s)-a(ix^s))
277  case('powell')
278  smalla(ix^s)=max(zero,two*(ar(ix^s)-al(ix^s)))
279  !!case('ratio')
280  !! where(aL(ix^S)<zero .and. aR(ix^S)>zero)&
281  !! a(ix^S)=a(ix^S)-2*aR(ix^S)*aL(ix^S)/(aR(ix^S)-aL(ix^S))
282  case('yee')
283  ! This has been done in geteigenjump already
284  case('nul')
285  ! No entropyfix is applied
286  case default
287  call mpistop("No such type of entropy fix")
288  end select
289 
290  end subroutine entropyfix
291 
292 end module mod_tvd
subroutine mpistop(message)
Exit MPI-AMRVAC with an error message.
Definition: comm_lib.t:194
This module contains definitions of global parameters and variables and some generic functions/subrou...
character(len=std_len), dimension(:), allocatable typeentropy
Which type of entropy fix to use with Riemann-type solvers.
type(state), pointer block
Block pointer for using one block and its previous state.
integer, dimension(3, 3) kr
Kronecker delta tensor.
integer, parameter ndim
Number of spatial dimensions for grid variables.
integer, parameter fs_tvdmu
integer, dimension(:), allocatable, parameter d
integer, dimension(:), allocatable type_limiter
Type of slope limiter used for reconstructing variables on cell edges.
character(len=std_len) typetvd
Which type of TVD method to use.
logical slab_uniform
uniform Cartesian geometry or not (stretched Cartesian)
Module with slope/flux limiters.
Definition: mod_limiter.t:2
pure logical function limiter_symmetric(typelim)
Definition: mod_limiter.t:109
subroutine dwlimiter2(dwC, ixIL, ixCL, idims, typelim, ldw, rdw, a2max)
Limit the centered dwC differences within ixC for iw in direction idim. The limiter is chosen accordi...
Definition: mod_limiter.t:128
procedure(sub_rtimes), pointer phys_rtimes
procedure(sub_get_eigenjump), pointer phys_get_eigenjump
procedure(sub_average), pointer phys_average
Subroutines for TVD-MUSCL schemes.
Definition: mod_tvd.t:2
subroutine, public tvdlimit2(method, qdt, ixIL, ixICL, ixOL, idims, wL, wR, wnew, x, fC, dxs)
Definition: mod_tvd.t:39
subroutine getphi(method, jumpC, adtdxC, smallaC, ixIL, ixICL, ixCL, il, idims, phiC)
Definition: mod_tvd.t:115
subroutine, public entropyfix(ixL, il, aL, aR, a, smalla)
Definition: mod_tvd.t:264
subroutine, public tvdlimit(method, qdt, ixIL, ixOL, idimLIM, s, qt, snew, fC, dxs, x)
Definition: mod_tvd.t:14