12 double precision :: dust_dtpar = 0.5d0
15 double precision :: gas_vtherm_factor = 3.0d0
18 double precision :: dust_temperature = -1.0d0
21 double precision :: dust_K_lineardrag = -1.0d0
25 double precision :: dust_stellar_luminosity = -1.0d0
31 double precision,
allocatable,
public ::
dust_size(:)
39 integer,
protected :: gas_rho_ = -1
40 integer,
allocatable,
protected :: gas_mom(:)
41 integer,
protected :: gas_e_ = -1
44 integer,
allocatable,
public,
protected ::
dust_rho(:)
47 integer,
allocatable,
public,
protected ::
dust_mom(:, :)
53 logical :: dust_source_split = .false.
56 logical :: dust_backreaction = .true.
60 logical :: dust_implicit_second_order = .true.
63 logical :: dust_backreaction_fh = .false.
66 character(len=std_len),
public,
protected ::
dust_method =
'Kwok'
69 character(len=std_len) :: dust_species =
'graphite'
72 character(len=std_len) :: dust_temperature_type =
'constant'
97 integer,
intent(in) :: g_rho
98 integer,
intent(in) :: g_mom(
ndir)
99 integer,
intent(in) :: g_energy
101 character(len=2) :: dim
106 allocate(gas_mom(
ndir))
121 dust_rho(n) = var_set_fluxvar(
"rhod",
"rhod", n)
126 write(dim,
"(I0,A)") idir,
"d"
128 dust_mom(idir, n) = var_set_fluxvar(
"m"//dim,
"v"//dim, n)
137 character(len=*),
intent(in) :: files(:)
142 dust_temperature_type, dust_backreaction, dust_dtpar, gas_vtherm_factor, dust_stellar_luminosity,&
143 dust_implicit_second_order, dust_backreaction_fh
145 do n = 1,
size(files)
146 open(
unitpar, file=trim(files(n)), status=
"old")
147 read(
unitpar, dust_list,
end=111)
158 if (
si_unit)
call mpistop(
"Dust error: sticking assumes cgs units")
159 if (dust_temperature_type ==
"constant")
then
160 if (dust_temperature < 0.0d0)
then
161 call mpistop(
"Dust error: dust_temperature (in K) < 0 or not set")
163 else if (dust_temperature_type ==
"stellar")
then
164 if (dust_stellar_luminosity < 0.0d0)
then
165 call mpistop(
"Dust error: dust_stellar_luminosity (in solar) < 0 or not set")
171 if(dust_k_lineardrag<0.0d0)
then
172 call mpistop(
"With dust_method=='linear', you must set a positive dust_K_lineardrag")
177 call mpistop(
"Dust error: any(dust_size < 0) or not set")
179 call mpistop(
"Dust error: any(dust_density < 0) or not set")
183 call mpistop(
"Dust error:usr_get_3d_dragforce and usr_dust_get_dt not defined")
186 if(.not.
use_imex_scheme .and. ((dust_dtpar .ge. 1d0).or.(dust_dtpar.le.0)))
then
187 if(
mype .eq. 0) print*,
"EXPLICIT source for dust requires 0<dt_dustpar < 1, set to 0.8"
196 integer,
intent(in) :: ixi^
l,ixo^
l
197 double precision,
intent(in):: w(ixi^s,1:nw)
198 logical,
intent(inout) :: flag(ixi^s,1:nw)
210 integer,
intent(in) :: ixi^
l, ixo^
l
211 double precision,
intent(inout) :: w(ixi^s, 1:nw)
212 double precision,
intent(in) :: x(ixi^s, 1:
ndim)
230 integer,
intent(in) :: ixi^
l, ixo^
l
231 double precision,
intent(inout) :: w(ixi^s, 1:nw)
232 double precision,
intent(in) :: x(ixi^s, 1:
ndim)
238 where (w(ixo^s,
dust_rho(n)) > 0.0d0)
254 integer,
intent(in) :: ixi^
l, ixo^
l, idim
255 double precision,
intent(in) :: w(ixi^s, 1:nw), x(ixi^s, 1:
ndim)
256 double precision,
intent(inout) :: f(ixi^s, nwflux)
260 where (w(ixo^s,
dust_rho(n)) > 0.0d0)
277 integer,
intent(in) :: ixi^
l, ixo^
l, idim
278 double precision,
intent(in) :: w(ixi^s, 1:nw), x(ixi^s, 1:
ndim)
279 double precision,
intent(inout) :: f(ixi^s, nwflux)
283 where (w(ixo^s,
dust_rho(n)) > 0.0d0)
297 function get_vdust(w, ixI^L, ixO^L, idim, n)
result(vdust)
299 integer,
intent(in) :: ixi^l, ixo^l, idim, n
300 double precision,
intent(in) :: w(ixi^s, nw)
301 double precision :: vdust(ixo^s)
303 where (w(ixo^s,
dust_rho(n)) > 0.0d0)
313 integer,
intent(in) :: ixi^l, ixo^l, idim, n
314 double precision,
intent(in) :: w(ixi^s, nw)
315 double precision :: vdust(ixo^s)
317 where (w(ixo^s,
dust_rho(n)) > 0.0d0)
318 vdust(ixo^s) = w(ixo^s,
dust_mom(idim, n))
329 integer,
intent(in) :: ixi^
l, ixo^
l
330 double precision,
intent(in) :: x(ixi^s, 1:
ndim)
331 double precision,
intent(inout) :: w(ixi^s, 1:nw)
334 logical :: flag(ixi^s)
355 integer,
intent(in) :: ixI^L, ixO^L
356 double precision,
intent(in) :: x(ixI^S, 1:ndim)
357 double precision,
intent(in) :: w(ixI^S, 1:nw)
358 double precision,
intent(out) :: &
359 fdrag(ixI^S, 1:ndir, 1:dust_n_species)
360 double precision,
intent(in) :: ptherm(ixI^S), vgas(ixI^S, 1:ndir)
362 double precision,
dimension(ixI^S) :: vt2, deltav, fd, vdust
363 double precision :: alpha_T(ixI^S, 1:dust_n_species)
366 vt2(ixo^s) = gas_vtherm_factor*ptherm(ixo^s)/w(ixo^s, gas_rho_)
372 do n = 1, dust_n_species
373 where(w(ixo^s,
dust_rho(n)) > 0.0d0)
375 deltav(ixo^s) = vgas(ixo^s, idir)-vdust(ixo^s)
378 fd(ixo^s) = 0.75d0*w(ixo^s,
dust_rho(n))*w(ixo^s, gas_rho_)*deltav(ixo^s) &
382 fd(ixo^s) = -fd(ixo^s)*0.75d0*dsqrt(vt2(ixo^s) + deltav(ixo^s)**2)
386 fdrag(ixo^s, idir, n) = fd(ixo^s)
395 do n = 1, dust_n_species
398 deltav(ixo^s) = vgas(ixo^s, idir)-vdust(ixo^s)
399 fd(ixo^s) = (one-alpha_t(ixo^s,n)) * w(ixo^s,
dust_rho(n))*w(ixo^s, gas_rho_) * &
401 fd(ixo^s) = -fd(ixo^s)*0.75d0*dsqrt(vt2(ixo^s) + deltav(ixo^s)**2)
405 fdrag(ixo^s, idir,n) = fd(ixo^s)
411 do n = 1, dust_n_species
414 deltav(ixo^s) = vgas(ixo^s, idir)-vdust(ixo^s)
416 fd(ixo^s) = -dust_k_lineardrag*deltav(ixo^s)
420 fdrag(ixo^s, idir,n) = fd(ixo^s)
427 fdrag(ixo^s, :, :) = 0.0d0
429 call mpistop(
"=== This dust method has not been implemented===" )
440 integer,
intent(in) :: ixI^L, ixO^L
441 double precision,
intent(in) :: x(ixI^S, 1:ndim)
442 double precision,
intent(in) :: w(ixI^S, 1:nw)
443 double precision,
intent(out) :: alpha_T(ixI^S, 1:dust_n_species)
444 double precision,
intent(in) :: ptherm(ixI^S)
445 double precision :: Tgas(ixI^S)
449 call get_tdust(w, x, ixi^l, ixo^l, alpha_t)
454 do n = 1, dust_n_species
455 alpha_t(ixo^s,n) = 0.35d0 * dexp(-dsqrt((tgas(ixo^s) + &
456 alpha_t(ixo^s,n))/5.0d2))+0.1d0
472 integer,
intent(in) :: ixI^L, ixO^L
473 double precision,
intent(in) :: x(ixI^S, 1:ndim)
474 double precision,
intent(in) :: w(ixI^S, 1:nw)
475 double precision,
intent(out) :: Td(ixI^S, 1:dust_n_species)
476 double precision :: G0(ixO^S)
479 select case( trim(dust_temperature_type) )
481 td(ixo^s, :) = dust_temperature
483 select case( trim(dust_species) )
485 do n = 1, dust_n_species
489 do n = 1, dust_n_species
493 call mpistop(
"=== Dust species undetermined===" )
498 g0(ixo^s) = max(x(ixo^s, 1)*
unit_length, smalldouble)
503 call mpistop(
'stellar case not available in this coordinate system')
506 g0(ixo^s) = 2.1d4*(dust_stellar_luminosity/1.0d8)*((3.0857d17/g0(ixo^s))**2)
508 select case( trim(dust_species) )
510 do n = 1, dust_n_species
512 *(g0(ixo^s)**(one/5.8d0))
515 do n = 1, dust_n_species
517 *(g0(ixo^s)**(one/6.0d0))
520 call mpistop(
"=== Dust species undetermined===" )
523 call mpistop(
"=== Dust temperature undetermined===" )
532 integer,
intent(in) :: ixi^
l, ixo^
l
533 double precision,
intent(in) :: qdt
534 double precision,
intent(in) :: wct(ixi^s, 1:nw), x(ixi^s, 1:
ndim)
535 double precision,
intent(inout) :: w(ixi^s, 1:nw)
536 logical,
intent(in) :: qsourcesplit
537 logical,
intent(inout) :: active
539 double precision :: ptherm(ixi^s), vgas(ixi^s, 1:
ndir)
547 if (qsourcesplit .eqv. dust_source_split)
then
550 call phys_get_pthermal(wct, x, ixi^
l, ixo^
l, ptherm)
552 vgas(ixo^s,idir)=wct(ixo^s,gas_mom(idir))/wct(ixo^s,gas_rho_)
561 if (dust_backreaction)
then
562 w(ixo^s, gas_mom(idir)) = w(ixo^s, gas_mom(idir)) + &
563 fdrag(ixo^s, idir, n)
565 w(ixo^s, gas_e_) = w(ixo^s, gas_e_) + vgas(ixo^s, idir) &
566 * fdrag(ixo^s, idir, n)
572 fdrag(ixo^s, idir, n)
585 double precision,
intent(in) :: qtc
587 integer :: iigrid, igrid, level
592 do iigrid=1,igridstail; igrid=igrids(iigrid);
606 integer,
intent(in) :: ixI^L, ixO^L
607 double precision,
intent(inout) :: w(ixI^S, 1:nw)
608 double precision,
intent(in) :: x(ixI^S,1:ndim)
610 double precision :: tmp(ixI^S), vgas(ixI^S, 1:ndir)
611 double precision :: alpha(ixI^S, 1:ndir, 1:dust_n_species)
615 vgas(ixo^s,idir)=w(ixo^s,gas_mom(idir))/w(ixo^s,gas_rho_)
621 w(ixo^s, gas_mom(idir))=0d0
622 do n = 1, dust_n_species
624 tmp(ixo^s) = alpha(ixo^s, idir,n) * ( &
625 w(ixo^s,
dust_rho(n)) * w(ixo^s, gas_mom(idir)) - &
626 w(ixo^s,gas_rho_) * w(ixo^s,
dust_mom(idir, n)))
627 w(ixo^s,
dust_mom(idir, n)) = -tmp(ixo^s)
628 if (dust_backreaction)
then
629 w(ixo^s, gas_mom(idir)) = w(ixo^s, gas_mom(idir)) + tmp(ixo^s)
631 if(dust_backreaction_fh)
then
633 w(ixo^s, gas_e_) = w(ixo^s, gas_e_) + alpha(ixo^s, idir,n) * &
634 (w(ixo^s,gas_rho_) * (w(ixo^s,
dust_mom(idir,n))**2/w(ixo^s,
dust_rho(n))) - &
635 w(ixo^s,
dust_rho(n)) * (w(ixo^s, gas_mom(idir))**2/w(ixo^s,gas_rho_)))
637 w(ixo^s, gas_e_) = w(ixo^s, gas_e_) + alpha(ixo^s, idir,n) * ( - &
638 w(ixo^s,
dust_rho(n)) * (w(ixo^s, gas_mom(idir))**2/w(ixo^s,gas_rho_)))
641 w(ixo^s, gas_e_) = w(ixo^s, gas_e_) + vgas(ixo^s, idir) &
657 double precision,
intent(in) :: qdt
658 double precision,
intent(in) :: qtc
659 double precision,
intent(in) :: dtfactor
661 integer :: iigrid, igrid
665 do iigrid=1,igridstail; igrid=igrids(iigrid);
676 integer,
intent(in) :: ixI^L, ixO^L
677 double precision,
intent(in) :: qdt
678 double precision,
intent(in) :: dtfactor
679 double precision,
intent(in) :: w(ixI^S,1:nw)
680 double precision,
intent(in) :: x(ixI^S,1:ndim)
681 double precision,
intent(out) :: wout(ixI^S,1:nw)
683 integer :: n, m, idir
684 double precision :: alpha(ixI^S, 1:ndir, 1:dust_n_species)
685 double precision :: tmp(ixI^S),tmp2(ixI^S)
686 double precision :: tmp3(ixI^S)
687 double precision :: vgas(ixI^S, 1:ndir)
691 vgas(ixo^s,idir)=w(ixo^s,gas_mom(idir))/w(ixo^s,gas_rho_)
695 wout(ixo^s,1:nw) = w(ixo^s,1:nw)
700 do n = 1, dust_n_species
701 tmp2(ixo^s) = tmp2(ixo^s) + alpha(ixo^s, idir,n) * &
702 (w(ixo^s,gas_rho_) + w(ixo^s,
dust_rho(n)))
706 tmp(ixo^s) = 1d0 + tmp2(ixo^s) * qdt
707 if(dust_implicit_second_order)
then
710 do n = 1, dust_n_species
711 do m = n+1, dust_n_species
712 tmp2(ixo^s) = tmp3(ixo^s) + alpha(ixo^s, idir,n) * alpha(ixo^s, idir,m) *&
717 tmp(ixo^s) = tmp(ixo^s) + w(ixo^s,gas_rho_)*tmp2(ixo^s) * (qdt**2)
722 do n = 1, dust_n_species
724 tmp2(ixo^s) = alpha(ixo^s, idir,n) * ( &
725 w(ixo^s,
dust_rho(n)) * w(ixo^s, gas_mom(idir)) - &
726 w(ixo^s,gas_rho_) * w(ixo^s,
dust_mom(idir, n))) * qdt
728 if(dust_implicit_second_order)
then
731 do m = n+1, dust_n_species
732 tmp3(ixo^s) = tmp3(ixo^s) + alpha(ixo^s, idir,n) * alpha(ixo^s, idir,m) * &
733 ( w(ixo^s,
dust_rho(n)) * (w(ixo^s,
dust_mom(idir, n)) + w(ixo^s, gas_mom(idir))) - &
737 tmp2(ixo^s) = tmp2(ixo^s) + tmp3(ixo^s) * w(ixo^s,gas_rho_)* (qdt**2)
739 tmp2(ixo^s) = tmp2(ixo^s)/tmp(ixo^s)
743 if (dust_backreaction)
then
746 do n = 1, dust_n_species
747 tmp2(ixo^s) = tmp2(ixo^s) + alpha(ixo^s, idir,n) * &
748 (w(ixo^s,gas_rho_) * w(ixo^s,
dust_mom(idir,n)) - &
749 w(ixo^s,
dust_rho(n)) * w(ixo^s, gas_mom(idir)))
752 tmp2(ixo^s) = qdt * tmp2(ixo^s)
753 if(dust_implicit_second_order)
then
756 do n = 1, dust_n_species
757 do m = n+1, dust_n_species
758 tmp3(ixo^s) = tmp3(ixo^s) + alpha(ixo^s, idir,n) * alpha(ixo^s, idir,m) * &
759 (w(ixo^s,gas_rho_) * (w(ixo^s,
dust_mom(idir, n)) + w(ixo^s,
dust_mom(idir, m))) - &
764 tmp2(ixo^s) = tmp2(ixo^s) + (qdt**2)*tmp3(ixo^s)* w(ixo^s,gas_rho_)
768 tmp2(ixo^s) = tmp2(ixo^s) / tmp(ixo^s)
769 wout(ixo^s, gas_mom(idir)) = w(ixo^s, gas_mom(idir)) + tmp2(ixo^s)
773 if(dust_backreaction_fh)
then
776 do n = 1, dust_n_species
783 tmp2(ixo^s) = tmp2(ixo^s) + alpha(ixo^s, idir,n) * &
784 (w(ixo^s,gas_rho_) * tmp3(ixo^s) - &
785 w(ixo^s,
dust_rho(n)) * (w(ixo^s, gas_mom(idir))**2/w(ixo^s,gas_rho_)))
788 tmp2(ixo^s) = qdt * tmp2(ixo^s)
789 if(dust_implicit_second_order)
then
791 do n = 1, dust_n_species
792 do m = n+1, dust_n_species
793 tmp3(ixo^s) = tmp3(ixo^s) + alpha(ixo^s, idir,n) * alpha(ixo^s, idir,m) * &
795 (w(ixo^s,
dust_rho(n)) + w(ixo^s,
dust_rho(m)))* w(ixo^s, gas_mom(idir))**2/w(ixo^s,gas_rho_))
799 tmp2(ixo^s) = tmp2(ixo^s) + (qdt**2)*tmp3(ixo^s)* w(ixo^s,gas_rho_)
801 wout(ixo^s, gas_e_) = wout(ixo^s, gas_e_) + 0.5d0 * tmp2(ixo^s) / tmp(ixo^s)
805 wout(ixo^s, gas_e_) = wout(ixo^s, gas_e_) + vgas(ixo^s, idir) * tmp2(ixo^s)
818 integer,
intent(in) :: ixI^L, ixO^L
819 double precision,
intent(in) :: x(ixI^S, 1:ndim)
820 double precision,
intent(in) :: w(ixI^S, 1:nw)
821 double precision,
intent(in) :: vgas(ixI^S, 1:ndir)
822 double precision,
intent(out) :: &
823 alpha(ixI^S, 1:ndir, 1:dust_n_species)
825 double precision :: ptherm(ixI^S)
826 double precision,
dimension(ixI^S) :: vt2, deltav, fd, vdust
827 double precision :: alpha_T(ixI^S, 1:dust_n_species)
830 call phys_get_pthermal(w, x, ixi^l, ixo^l, ptherm)
832 vt2(ixo^s) = gas_vtherm_factor*ptherm(ixo^s)/w(ixo^s, gas_rho_)
838 do n = 1, dust_n_species
839 where(w(ixo^s,
dust_rho(n)) > 0.0d0)
846 deltav(ixo^s) = vgas(ixo^s, idir)-vdust(ixo^s)
847 fd(ixo^s) = fd(ixo^s)*0.75d0*dsqrt(vt2(ixo^s) + deltav(ixo^s)**2)
851 alpha(ixo^s, idir, n) = fd(ixo^s)
860 do n = 1, dust_n_species
866 deltav(ixo^s) = vgas(ixo^s, idir)-vdust(ixo^s)
867 fd(ixo^s) = fd(ixo^s)*0.75d0*dsqrt(vt2(ixo^s) + deltav(ixo^s)**2)
871 alpha(ixo^s, idir,n) = fd(ixo^s)
877 do n = 1, dust_n_species
879 fd(ixo^s) = dust_k_lineardrag/(w(ixo^s,gas_rho_)*w(ixo^s,
dust_rho(n)))
883 alpha(ixo^s, idir,n) = fd(ixo^s)
888 alpha(ixo^s, :, :) = 0.0d0
890 call mpistop(
"=== This dust method has not been implemented===" )
901 integer,
intent(in) :: ixi^
l, ixo^
l
902 double precision,
intent(in) ::
dx^
d, x(ixi^s, 1:
ndim)
903 double precision,
intent(in) :: w(ixi^s, 1:nw)
904 double precision,
intent(inout) :: dtnew
906 double precision :: ptherm(ixi^s), vgas(ixi^s, 1:
ndir)
907 double precision,
dimension(1:dust_n_species):: dtdust
908 double precision,
dimension(ixI^S) :: vt2, deltav, tstop, vdust
909 double precision,
dimension(ixI^S, 1:dust_n_species) :: alpha_t
912 if(dust_dtpar .le. 0)
return
914 call phys_get_pthermal(w, x, ixi^
l, ixo^
l, ptherm)
916 vgas(ixo^s,idir)=w(ixo^s,gas_mom(idir))/w(ixo^s,gas_rho_)
922 dtdust(:) = bigdouble
924 vt2(ixo^s) = gas_vtherm_factor*ptherm(ixo^s)/w(ixo^s, gas_rho_)
930 deltav(ixo^s) = vgas(ixo^s, idir)-vdust(ixo^s)
932 (3.0d0*(0.75d0)*dsqrt(vt2(ixo^s) + &
933 deltav(ixo^s)**2)*(w(ixo^s,
dust_rho(n)) + &
936 tstop(ixo^s) = bigdouble
939 dtdust(n) = min(minval(tstop(ixo^s)), dtdust(n))
943 dtnew = min(minval(dust_dtpar*dtdust(:)), dtnew)
946 dtdust(:) = bigdouble
948 vt2(ixo^s) = gas_vtherm_factor*ptherm(ixo^s)/w(ixo^s, gas_rho_)
957 deltav(ixo^s) = vgas(ixo^s, idir)-vdust(ixo^s)
959 (3.0d0*(one-alpha_t(ixo^s,n))*dsqrt(vt2(ixo^s) + &
960 deltav(ixo^s)**2)*(w(ixo^s,
dust_rho(n)) + &
963 tstop(ixo^s) = bigdouble
966 dtdust(n) = min(minval(tstop(ixo^s)), dtdust(n))
970 dtnew = min(minval(dust_dtpar*dtdust(:)), dtnew)
973 dtdust(:) = bigdouble
977 tstop(ixo^s) = (w(ixo^s,
dust_rho(n))*w(ixo^s, gas_rho_))/ &
978 (dust_k_lineardrag*(w(ixo^s,
dust_rho(n)) + w(ixo^s, gas_rho_)))
980 tstop(ixo^s) = bigdouble
983 dtdust(n) = min(minval(tstop(ixo^s)), dtdust(n))
986 dtnew = min(minval(dust_dtpar*dtdust(:)), dtnew)
988 dtdust(:) = bigdouble
990 dtnew = min(minval(dust_dtpar*dtdust(:)), dtnew)
994 call mpistop(
"=== This dust method has not been implemented===" )
997 if (dtnew <
dtmin)
then
998 write(
unitterm,*)
"-------------------------------------"
999 write(
unitterm,*)
"Warning: found DUST related time step too small! dtnew=", dtnew
1002 write(
unitterm,*)
" dtdust =", dtdust(:)
1004 write(
unitterm,*)
"-------------------------------------"
1014 integer,
intent(in) :: ixi^
l, ixo^
l, idim
1015 double precision,
intent(in) :: w(ixi^s, 1:
nw), x(ixi^s, 1:
ndim)
1017 double precision,
intent(inout),
optional :: cmin(ixi^s,1:
number_species)
1018 double precision :: vdust(ixo^s)
1022 vdust(ixo^s) =
get_vdust(w, ixi^
l, ixo^
l, idim, n)
1024 if (
present(cmin))
then
1025 cmin(ixo^s,1) = min(cmin(ixo^s,1), vdust(ixo^s))
1026 cmax(ixo^s,1) = max(cmax(ixo^s,1), vdust(ixo^s))
1028 cmax(ixo^s,1) = max(cmax(ixo^s,1), abs(vdust(ixo^s)))
1037 integer,
intent(in) :: ixi^
l, ixo^
l, idim
1038 double precision,
intent(in) :: w(ixi^s, 1:nw), x(ixi^s, 1:
ndim)
1039 double precision,
intent(inout) :: cmax(ixi^s)
1040 double precision,
intent(inout),
optional :: cmin(ixi^s)
1041 double precision :: vdust(ixo^s)
1047 if (
present(cmin))
then
1048 cmin(ixo^s) = min(cmin(ixo^s), vdust(ixo^s))
1049 cmax(ixo^s) = max(cmax(ixo^s), vdust(ixo^s))
1051 cmax(ixo^s) = max(cmax(ixo^s), abs(vdust(ixo^s)))
subroutine, public mpistop(message)
Exit MPI-AMRVAC with an error message.
Module for including dust species, which interact with the gas through a drag force.
double precision function, dimension(ixo^s) get_vdust_prim(w, ixIL, ixOL, idim, n)
double precision, public, protected dust_min_rho
Minimum dust density as used when dust_small_to_zero=T.
subroutine, public dust_check_w(ixIL, ixOL, w, flag)
subroutine dust_advance_implicit_grid(ixIL, ixOL, w, wout, x, dtfactor, qdt)
subroutine, public dust_get_flux(w, x, ixIL, ixOL, idim, f)
subroutine get_3d_dragforce(ixIL, ixOL, w, x, fdrag, ptherm, vgas)
subroutine, public dust_implicit_update(dtfactor, qdt, qtC, psb, psa)
Implicit solve of psb=psa+dtfactor*dt*F_im(psb)
subroutine, public dust_get_dt(w, ixIL, ixOL, dtnew, dxD, x)
Get dt related to dust and gas stopping time (Laibe 2011)
double precision, dimension(:), allocatable, public dust_size
Size of each dust species, dimensionless expression.
subroutine get_tdust(w, x, ixIL, ixOL, Td)
Returns dust temperature (in K), either as constant or based on equ. 5.41, 5.42 and 5....
character(len=std_len), public, protected dust_method
What type of dust drag force to use. Can be 'Kwok', 'sticking', 'linear', 'usr' or 'none'.
subroutine dust_read_params(files)
Read dust_list module parameters from a file.
subroutine, public dust_add_source(qdt, ixIL, ixOL, wCT, w, x, qsourcesplit, active)
w[iw]= w[iw]+qdt*S[wCT, x] where S is the source based on wCT within ixO
subroutine, public set_dusttozero(ixIL, ixOL, w, x)
subroutine, public dust_to_primitive(ixIL, ixOL, w, x)
subroutine get_sticking(w, x, ixIL, ixOL, alpha_T, ptherm)
Get sticking coefficient alpha_T (always between 0 and 1)
integer, dimension(:, :), allocatable, public, protected dust_mom
Indices of the dust momentum densities.
subroutine, public dust_get_cmax(w, x, ixIL, ixOL, idim, cmax, cmin)
logical, public, protected dust_small_to_zero
Set small dust densities to zero to avoid numerical problems.
integer, public, protected dust_n_species
The number of dust species.
subroutine get_alpha_dust(ixIL, ixOL, w, vgas, x, alpha)
integer, dimension(:), allocatable, public, protected dust_rho
Indices of the dust densities.
double precision function, dimension(ixo^s) get_vdust(w, ixIL, ixOL, idim, n)
subroutine, public dust_get_flux_prim(w, x, ixIL, ixOL, idim, f)
subroutine, public dust_check_params()
subroutine, public dust_evaluate_implicit(qtC, psa)
inplace update of psa==>F_im(psa)
subroutine dust_terms(ixIL, ixOL, w, x)
subroutine, public dust_init(g_rho, g_mom, g_energy)
subroutine, public dust_get_cmax_prim(w, x, ixIL, ixOL, idim, cmax, cmin)
double precision, dimension(:), allocatable, public dust_density
Internal density of each dust species, dimensionless expression.
subroutine, public dust_to_conserved(ixIL, ixOL, w, x)
Module with geometry-related routines (e.g., divergence, curl)
integer, parameter spherical
This module contains definitions of global parameters and variables and some generic functions/subrou...
type(state), pointer block
Block pointer for using one block and its previous state.
integer, parameter unitpar
file handle for IO
logical any_source_split
if any normal source term is added in split fasion
logical use_imex_scheme
whether IMEX in use or not
integer, parameter ndim
Number of spatial dimensions for grid variables.
integer, parameter rpxmin
double precision unit_length
Physical scaling factor for length.
character(len=std_len), dimension(:), allocatable par_files
Which par files are used as input.
integer mype
The rank of the current MPI task.
double precision, dimension(:), allocatable, parameter d
integer ndir
Number of spatial dimensions (components) for vector variables.
integer ixm
the mesh range of a physical block without ghost cells
integer, parameter unitterm
Unit for standard output.
double precision, dimension(:,:), allocatable rnode
Corner coordinates.
double precision unit_temperature
Physical scaling factor for temperature.
logical si_unit
Use SI units (.true.) or use cgs units (.false.)
double precision, dimension(:,:), allocatable dx
logical fix_small_values
fix small values with average or replace methods
double precision, dimension(^nd) dxlevel
store unstretched cell size of current level
integer, parameter rpxmax
double precision dtmin
Stop the simulation when the time step becomes smaller than this value.
integer max_blocks
The maximum number of grid blocks in a processor.
This module defines the procedures of a physics module. It contains function pointers for the various...
Module with all the methods that users can customize in AMRVAC.
procedure(phys_dust_get_dt), pointer usr_dust_get_dt
procedure(phys_dust_get_3d_dragforce), pointer usr_get_3d_dragforce
integer nw
Total number of variables.
integer number_species
number of species: each species has different characterictic speeds and should be used accordingly in...