11 integer,
parameter :: fastRW_ = 3,fastlw_=4,slowrw_=5,slowlw_=6
12 integer,
parameter :: entroW_ = 8,diverw_=7,alfvrw_=1,alfvlw_=2
31 case(fastrw_,fastlw_,slowrw_,slowlw_)
51 integer,
intent(in) :: ix^L, idim
52 double precision,
intent(in) :: wL(ixG^T, nw), wR(ixG^T, nw)
53 double precision,
intent(inout) :: wroe(ixG^T, nw)
54 double precision,
intent(inout) :: workroe(ixG^T, nworkroe)
55 double precision,
intent(in) :: x(ixG^T, 1:^ND)
57 call average2(wl,wr,x,ix^l,idim,wroe,workroe(ixg^t,1),workroe(ixg^t,2), &
58 workroe(ixg^t,3),workroe(ixg^t,4),workroe(ixg^t,5),workroe(ixg^t,6), &
59 workroe(ixg^t,7),workroe(ixg^t,8))
69 subroutine average2(wL,wR,x,ix^L,idim,wroe,cfast,cslow,afast,aslow,csound2,dp, &
72 integer :: ix^L,idim,idir,jdir,iw
73 double precision,
dimension(ixG^T,nw) :: wL,wR,wroe
74 double precision,
intent(in) :: x(ixG^T,1:ndim)
75 double precision,
dimension(ixG^T) :: cfast,cslow,afast,aslow,csound2,dp, &
78 if (
ndir==1)
call mpistop(
"twofl with d=11 is the same as HD")
84 wroe(ix^s,
mag(idir))=half*(wl(ix^s,
mag(idir))+wr(ix^s,
mag(idir)))
91 wroe(ix^s,
e_c_)=half*(afast(ix^s)+aslow(ix^s))
93 dp(ix^s)=aslow(ix^s)-afast(ix^s)
95 dp(ix^s)=aslow(ix^s)-afast(ix^s)
99 rhodv(ix^s)=wr(ix^s,
mom_c(idim))-wl(ix^s,
mom_c(idim))-&
112 cfast(ix^s)=sum(wroe(ix^s,
mag(:))**2,dim=ndim+1)/wroe(ix^s,
rho_c_)+csound2(ix^s)
115 cslow(ix^s)=half*(cfast(ix^s)-dsqrt(cfast(ix^s)**2-&
116 4d0*csound2(ix^s)*wroe(ix^s,
mag(idim))**2/wroe(ix^s,
rho_c_)))
119 cfast(ix^s)=cfast(ix^s)-cslow(ix^s)
122 afast(ix^s)=(csound2(ix^s)-cslow(ix^s))/(cfast(ix^s)-cslow(ix^s))
123 afast(ix^s)=min(one,max(afast(ix^s),zero))
126 aslow(ix^s)=dsqrt(one-afast(ix^s))
129 afast(ix^s)=dsqrt(afast(ix^s))
132 cfast(ix^s)=dsqrt(cfast(ix^s))
135 cslow(ix^s)=dsqrt(cslow(ix^s))
142 where(dabs(wroe(ix^s,
mag(idim)))<smalldouble)&
143 wroe(ix^s,
mag(idim))=smalldouble
147 where(wroe(ix^s,
mag(idir))>=zero)
148 wroe(ix^s,
mag(idir))=one
150 wroe(ix^s,
mag(idir))=-one
155 tmp(ix^s)=dsqrt(wroe(ix^s,
mag(idir))**2+wroe(ix^s,
mag(jdir))**2)
156 where(tmp(ix^s)>smalldouble)
157 wroe(ix^s,
mag(idir))=wroe(ix^s,
mag(idir))/tmp(ix^s)
158 wroe(ix^s,
mag(jdir))=wroe(ix^s,
mag(jdir))/tmp(ix^s)
160 wroe(ix^s,
mag(idir))=dsqrt(half)
161 wroe(ix^s,
mag(jdir))=dsqrt(half)
177 subroutine twofl_get_eigenjump(wL,wR,wroe,x,ix^L,il,idim,smalla,a,jump,workroe)
180 integer,
intent(in) :: ix^L,il,idim
181 double precision,
dimension(ixG^T,nw) :: wL,wR,wroe
182 double precision,
intent(in) :: x(ixG^T,1:ndim)
183 double precision,
dimension(ixG^T) :: smalla,a,jump
184 double precision,
dimension(ixG^T,nworkroe) :: workroe
186 call geteigenjump2(wl,wr,wroe,x,ix^l,il,idim,smalla,a,jump, &
187 workroe(ixg^t,1),workroe(ixg^t,2), &
188 workroe(ixg^t,3),workroe(ixg^t,4),workroe(ixg^t,5),workroe(ixg^t,6), &
189 workroe(ixg^t,7),workroe(ixg^t,8),workroe(ixg^t,9),workroe(ixg^t,10), &
190 workroe(ixg^t,11),workroe(ixg^t,12),workroe(ixg^t,13))
204 subroutine geteigenjump2(wL,wR,wroe,x,ix^L,il,idim,smalla,a,jump, &
205 cfast,cslow,afast,aslow,csound2,dp,rhodv,bdv,bdb,cs2L,cs2R,cs2ca2L,cs2ca2R)
209 integer :: ix^L,il,idim,idir,jdir
210 double precision,
dimension(ixG^T,nw) :: wL,wR,wroe
211 double precision,
intent(in) :: x(ixG^T,1:ndim)
212 double precision,
dimension(ixG^T) :: smalla,a,jump
213 double precision,
dimension(ixG^T) :: cfast,cslow,afast,aslow,csound2,dp,rhodv
214 double precision,
dimension(ixG^T) :: bdv,bdb
215 double precision,
dimension(ixG^T) :: aL,aR,cs2L,cs2R,cs2ca2L,cs2ca2R
223 bdv(ix^s)=wroe(ix^s,
mag(idir))* &
225 if(
ndir==3)bdv(ix^s)=bdv(ix^s)+wroe(ix^s,
mag(jdir))* &
227 bdv(ix^s)=bdv(ix^s)*sign(wroe(ix^s,
rho_c_)**2,wroe(ix^s,
mag(idim)))
229 bdb(ix^s)=wroe(ix^s,
mag(idir))*(wr(ix^s,
mag(idir))-wl(ix^s,
mag(idir)))
230 if(
ndir==3)bdb(ix^s)=bdb(ix^s)+&
231 wroe(ix^s,
mag(jdir))*(wr(ix^s,
mag(jdir))-wl(ix^s,
mag(jdir)))
232 bdb(ix^s)=bdb(ix^s)*dsqrt(csound2(ix^s))*wroe(ix^s,
rho_c_)
238 bdv(ix^s)=wroe(ix^s,
mag(jdir))* &
240 -wroe(ix^s,
mag(idir))* &
242 bdb(ix^s)=wroe(ix^s,
mag(jdir))*(wr(ix^s,
mag(idir))-wl(ix^s,
mag(idir))) &
243 -wroe(ix^s,
mag(idir))*(wr(ix^s,
mag(jdir))-wl(ix^s,
mag(jdir)))
244 bdv(ix^s)=bdv(ix^s)*half*wroe(ix^s,
rho_c_)**2
245 bdb(ix^s)=bdb(ix^s)*half*sign(wroe(ix^s,
rho_c_),wroe(ix^s,
mag(idim)))
250 a(ix^s)=wroe(ix^s,
mom_c(idim))+cfast(ix^s)
251 jump(ix^s)=half/csound2(ix^s)*(&
252 afast(ix^s)*(+cfast(ix^s)*rhodv(ix^s)+dp(ix^s))&
253 +aslow(ix^s)*(-cslow(ix^s)*bdv(ix^s)+bdb(ix^s)))
255 a(ix^s)=wroe(ix^s,
mom_c(idim))-cfast(ix^s)
256 jump(ix^s)=half/csound2(ix^s)*(&
257 afast(ix^s)*(-cfast(ix^s)*rhodv(ix^s)+dp(ix^s))&
258 +aslow(ix^s)*(+cslow(ix^s)*bdv(ix^s)+bdb(ix^s)))
260 a(ix^s)=wroe(ix^s,
mom_c(idim))+cslow(ix^s)
261 jump(ix^s)=half/csound2(ix^s)*(&
262 aslow(ix^s)*(+cslow(ix^s)*rhodv(ix^s)+dp(ix^s))&
263 +afast(ix^s)*(+cfast(ix^s)*bdv(ix^s)-bdb(ix^s)))
265 a(ix^s)=wroe(ix^s,
mom_c(idim))-cslow(ix^s)
266 jump(ix^s)=half/csound2(ix^s)*(&
267 aslow(ix^s)*(-cslow(ix^s)*rhodv(ix^s)+dp(ix^s))&
268 +afast(ix^s)*(-cfast(ix^s)*bdv(ix^s)-bdb(ix^s)))
270 a(ix^s)=wroe(ix^s,
mom_c(idim))
271 jump(ix^s)=wr(ix^s,
rho_c_)-wl(ix^s,
rho_c_)-dp(ix^s)/csound2(ix^s)
274 a(ix^s)=wroe(ix^s,
mom_c(idim))
275 jump(ix^s)=wr(ix^s,
mag(idim))-wl(ix^s,
mag(idim))
281 a(ix^s)=wroe(ix^s,
mom_c(idim))+dabs(wroe(ix^s,
mag(idim)))/wroe(ix^s,
rho_c_)
282 jump(ix^s)=+bdv(ix^s)-bdb(ix^s)
284 a(ix^s)=wroe(ix^s,
mom_c(idim))-dabs(wroe(ix^s,
mag(idim)))/wroe(ix^s,
rho_c_)
285 jump(ix^s)=-bdv(ix^s)-bdb(ix^s)
294 case(
'harten',
'powell',
'ratio')
306 cs2ca2l(ix^s)=cs2l(ix^s)+sum(wl(ix^s,
mag(:))**2,dim=ndim+1)/wl(ix^s,
rho_c_)
307 cs2ca2r(ix^s)=cs2r(ix^s)+sum(wr(ix^s,
mag(:))**2,dim=ndim+1)/wr(ix^s,
rho_c_)
310 dsqrt(cs2ca2l(ix^s)**2-4d0*cs2l(ix^s)*wl(ix^s,
mag(idim))**2/wl(ix^s,
rho_c_))
312 dsqrt(cs2ca2r(ix^s)**2-4d0*cs2r(ix^s)*wr(ix^s,
mag(idim))**2/wr(ix^s,
rho_c_))
315 al(ix^s)=al(ix^s) + dsqrt(half*(cs2ca2l(ix^s) + cs2l(ix^s)))
316 ar(ix^s)=ar(ix^s) + dsqrt(half*(cs2ca2r(ix^s) + cs2r(ix^s)))
318 al(ix^s)=al(ix^s) - dsqrt(half*(cs2ca2l(ix^s) + cs2l(ix^s)))
319 ar(ix^s)=ar(ix^s) - dsqrt(half*(cs2ca2r(ix^s) + cs2r(ix^s)))
321 al(ix^s)=al(ix^s) + dsqrt(half*(cs2ca2l(ix^s) - cs2l(ix^s)))
322 ar(ix^s)=ar(ix^s) + dsqrt(half*(cs2ca2r(ix^s) - cs2r(ix^s)))
324 al(ix^s)=al(ix^s) - dsqrt(half*(cs2ca2l(ix^s) - cs2l(ix^s)))
325 ar(ix^s)=ar(ix^s) - dsqrt(half*(cs2ca2r(ix^s) - cs2r(ix^s)))
326 case(entrow_,diverw_)
330 cs2ca2l(ix^s)=dabs(wl(ix^s,
mag(idim)))/dsqrt(wl(ix^s,
rho_c_))
331 cs2ca2r(ix^s)=dabs(wr(ix^s,
mag(idim)))/dsqrt(wr(ix^s,
rho_c_))
333 al(ix^s)=al(ix^s) + cs2ca2l(ix^s)
334 ar(ix^s)=ar(ix^s) + cs2ca2r(ix^s)
336 al(ix^s)=al(ix^s) - cs2ca2l(ix^s)
337 ar(ix^s)=ar(ix^s) - cs2ca2r(ix^s)
349 integer,
intent(in) :: ix^L, iw, il, idim
350 double precision,
intent(in) :: w(ixG^T, nw), q(ixG^T)
351 double precision,
intent(inout) :: rq(ixG^T)
352 double precision,
intent(inout) :: workroe(ixG^T, nworkroe)
354 call rtimes2(q,w,ix^l,iw,il,idim,rq,&
355 workroe(ixg^t,1),workroe(ixg^t,2), &
356 workroe(ixg^t,3),workroe(ixg^t,4),workroe(ixg^t,5),workroe(ixg^t,6), &
357 workroe(ixg^t,7),workroe(ixg^t,14),workroe(ixg^t,15))
362 subroutine rtimes2(q,wroe,ix^L,iw,il,idim,rq, &
363 cfast,cslow,afast,aslow,csound2,dp,rhodv,bv,v2a2)
366 integer :: ix^L,iw,il,idim,idir,jdir
367 double precision :: wroe(ixG^T,nw)
368 double precision,
dimension(ixG^T) :: q,rq
369 double precision,
dimension(ixG^T) :: cfast,cslow,afast,aslow,csound2,dp,rhodv
370 double precision,
dimension(ixG^T) :: bv,v2a2
377 case(fastrw_,fastlw_)
378 rq(ix^s)=q(ix^s)*afast(ix^s)
379 case(slowrw_,slowlw_)
380 rq(ix^s)=q(ix^s)*aslow(ix^s)
383 case(diverw_,alfvrw_,alfvlw_)
386 else if(iw ==
e_c_)
then
389 v2a2(ix^s)=half*sum(wroe(ix^s,
mom_c(:))**2,dim=
ndim+1)+ &
392 bv(ix^s)=wroe(ix^s,
mag(idir))*wroe(ix^s,
mom_c(idir))
393 if(
ndir==3)bv(ix^s)=bv(ix^s)+wroe(ix^s,
mag(jdir))*wroe(ix^s,
mom_c(jdir))
394 bv(ix^s)=bv(ix^s)*sign(one,wroe(ix^s,
mag(idim)))
395 else if(il==alfvrw_)
then
397 bv(ix^s)=(wroe(ix^s,
mag(jdir))*wroe(ix^s,
mom_c(idir))-&
398 wroe(ix^s,
mag(idir))*wroe(ix^s,
mom_c(jdir)))
403 rq(ix^s)=q(ix^s)*(-aslow(ix^s)*cslow(ix^s)*bv(ix^s)+afast(ix^s)*&
404 (v2a2(ix^s)+cfast(ix^s)*(cfast(ix^s)+wroe(ix^s,
mom_c(idim)))))
406 rq(ix^s)=q(ix^s)*(+aslow(ix^s)*cslow(ix^s)*bv(ix^s)+afast(ix^s)*&
407 (v2a2(ix^s)+cfast(ix^s)*(cfast(ix^s)-wroe(ix^s,
mom_c(idim)))))
409 rq(ix^s)=q(ix^s)*(+afast(ix^s)*cfast(ix^s)*bv(ix^s)+aslow(ix^s)*&
410 (v2a2(ix^s)+cslow(ix^s)*(cslow(ix^s)+wroe(ix^s,
mom_c(idim)))))
412 rq(ix^s)=q(ix^s)*(-afast(ix^s)*cfast(ix^s)*bv(ix^s)+aslow(ix^s)*&
413 (v2a2(ix^s)+cslow(ix^s)*(cslow(ix^s)-wroe(ix^s,
mom_c(idim)))))
415 rq(ix^s)= q(ix^s)*half*sum(wroe(ix^s,
mom_c(:))**2,dim=
ndim+1)
418 rq(ix^s)= q(ix^s)*wroe(ix^s,
mag(idim))
423 rq(ix^s)=+q(ix^s)*bv(ix^s)
425 rq(ix^s)=-q(ix^s)*bv(ix^s)
427 else if(any(
mom_c(:)==iw))
then
428 if(iw==
mom_c(idim))
then
431 rq(ix^s)=q(ix^s)*afast(ix^s)*(wroe(ix^s,iw)+cfast(ix^s))
433 rq(ix^s)=q(ix^s)*afast(ix^s)*(wroe(ix^s,iw)-cfast(ix^s))
435 rq(ix^s)=q(ix^s)*aslow(ix^s)*(wroe(ix^s,iw)+cslow(ix^s))
437 rq(ix^s)=q(ix^s)*aslow(ix^s)*(wroe(ix^s,iw)-cslow(ix^s))
439 rq(ix^s)=q(ix^s)*wroe(ix^s,iw)
440 case(diverw_,alfvlw_,alfvrw_)
446 rq(ix^s)=q(ix^s)*(afast(ix^s)*wroe(ix^s,iw)-aslow(ix^s)*&
447 cslow(ix^s)*wroe(ix^s,
mag(1)-
mom_c(1)+iw)*sign(one,wroe(ix^s,
mag(idim))))
449 rq(ix^s)=q(ix^s)*(afast(ix^s)*wroe(ix^s,iw)+aslow(ix^s)*&
450 cslow(ix^s)*wroe(ix^s,
mag(1)-
mom_c(1)+iw)*sign(one,wroe(ix^s,
mag(idim))))
452 rq(ix^s)=q(ix^s)*(aslow(ix^s)*wroe(ix^s,iw)+afast(ix^s)*&
453 cfast(ix^s)*wroe(ix^s,
mag(1)-
mom_c(1)+iw)*sign(one,wroe(ix^s,
mag(idim))))
455 rq(ix^s)=q(ix^s)*(aslow(ix^s)*wroe(ix^s,iw)-afast(ix^s)*&
456 cfast(ix^s)*wroe(ix^s,
mag(1)-
mom_c(1)+iw)*sign(one,wroe(ix^s,
mag(idim))))
458 rq(ix^s)=q(ix^s)*wroe(ix^s,iw)
462 if(iw==
mom_c(idir))
then
463 rq(ix^s)=+q(ix^s)*wroe(ix^s,
mag(jdir))
465 rq(ix^s)=-q(ix^s)*wroe(ix^s,
mag(idir))
468 if(iw==
mom_c(idir))
then
469 rq(ix^s)=-q(ix^s)*wroe(ix^s,
mag(jdir))
471 rq(ix^s)=+q(ix^s)*wroe(ix^s,
mag(idir))
475 else if(any(
mag(:)==iw))
then
476 if(iw==
mag(idim))
then
484 case(fastrw_,fastlw_)
485 rq(ix^s)=+q(ix^s)*aslow(ix^s)*dsqrt(csound2(ix^s))*wroe(ix^s,iw)&
487 case(slowrw_,slowlw_)
488 rq(ix^s)=-q(ix^s)*afast(ix^s)*dsqrt(csound2(ix^s))*wroe(ix^s,iw)&
490 case(entrow_,diverw_)
492 case(alfvrw_,alfvlw_)
493 if(iw==
mag(idir))
then
494 rq(ix^s)=-q(ix^s)*wroe(ix^s,
mag(jdir))&
495 /sign(wroe(ix^s,
rho_c_),wroe(ix^s,
mag(idim)))
497 rq(ix^s)=+q(ix^s)*wroe(ix^s,
mag(idir))&
498 /sign(wroe(ix^s,
rho_c_),wroe(ix^s,
mag(idim)))
subroutine mpistop(message)
Exit MPI-AMRVAC with an error message.
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.
integer, parameter ndim
Number of spatial dimensions for grid variables.
integer ndir
Number of spatial dimensions (components) for vector variables.
double precision, dimension(:), allocatable entropycoef
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.
subroutine, public entropyfix(ixL, il, aL, aR, a, smalla)
Magneto-hydrodynamics module.
double precision, public twofl_adiab
The adiabatic constant.
subroutine, public twofl_get_csound2_c_from_conserved(w, x, ixIL, ixOL, csound2)
subroutine, public twofl_get_pthermal_c(w, x, ixIL, ixOL, pth)
integer, public e_c_
Index of the energy density (-1 if not present)
integer, dimension(:), allocatable, public mom_c
Indices of the momentum density.
logical, public divbwave
Add divB wave in Roe solver.
integer, dimension(:), allocatable, public mag
Indices of the magnetic field.
integer, public rho_c_
Index of the density (in the w array)
integer, public, protected twofl_eq_energy
double precision, public twofl_gamma
The adiabatic index.
Subroutines for Roe-type Riemann solver for HD.
subroutine average2(wL, wR, x, ixL, idim, wroe, cfast, cslow, afast, aslow, csound2, dp, rhodv, tmp)
subroutine twofl_get_eigenjump(wL, wR, wroe, x, ixL, il, idim, smalla, a, jump, workroe)
subroutine twofl_rtimes(q, w, ixL, iw, il, idim, rq, workroe)
subroutine twofl_average(wL, wR, x, ixL, idim, wroe, workroe)
subroutine geteigenjump2(wL, wR, wroe, x, ixL, il, idim, smalla, a, jump, cfast, cslow, afast, aslow, csound2, dp, rhodv, bdv, bdb, cs2L, cs2R, cs2ca2L, cs2ca2R)
subroutine rtimes2(q, wroe, ixL, iw, il, idim, rq, cfast, cslow, afast, aslow, csound2, dp, rhodv, bv, v2a2)
subroutine, public twofl_roe_init()