8 subroutine rbsl(ixI^L,ixO^L,np,a,F_flx,positive_helicity,x,x_axis,Atotal,Bfr)
12 integer,
intent(in) :: ixI^L,ixO^L
14 integer,
intent(in) :: np
15 double precision,
intent(in) :: x(ixI^S,1:ndim)
17 double precision,
intent(in) :: x_axis(np,1:ndim)
19 double precision,
intent(in) :: a
21 double precision,
intent(in) :: F_flx
23 logical,
intent(in) :: positive_helicity
25 double precision,
intent(out) :: Atotal(ixI^S,1:ndim)
27 double precision,
optional,
intent(out) :: Bfr(ixI^S,1:ndir)
30 double precision :: I_cur
32 double precision :: AIx(ixI^S,1:ndim)
34 double precision :: AFx(ixI^S,1:ndim)
35 integer :: ix^D, ixp, idirmin
36 double precision :: r_mag, KIr, KFr, dl, re_pi, sqrt1r, f52r,fsqrt6
37 double precision :: Rpl(1:ndim), r_vec(1:ndim), Rcr(1:ndim)
39 if(positive_helicity)
then
40 i_cur = 5.d0*sqrt(2.d0)*f_flx/(3.d0*4.d0*dpi*a)
42 i_cur =-5.d0*sqrt(2.d0)*f_flx/(3.d0*4.d0*dpi*a)
48 fsqrt6=1.d0/sqrt(6.d0)
49 {
do ix^db=ixomin^db,ixomax^db\}
52 r_vec(:) = (x(ix^d,:) - x_axis(ixp,:))/a
53 r_mag = sqrt(sum(r_vec(:)**2))
56 rpl(:) = 0.5d0*(x_axis(ixp+1,:)-x_axis(np,:))
57 else if (ixp==np)
then
58 rpl(:) = 0.5d0*(x_axis(1,:)-x_axis(ixp-1,:))
60 rpl(:) = 0.5d0*(x_axis(ixp+1,:)-x_axis(ixp-1,:))
63 rcr(1) = rpl(2)*r_vec(3) - rpl(3)*r_vec(2)
64 rcr(2) = rpl(3)*r_vec(1) - rpl(1)*r_vec(3)
65 rcr(3) = rpl(1)*r_vec(2) - rpl(2)*r_vec(1)
66 if (r_mag < 1.d0)
then
67 sqrt1r=sqrt(1.d0-r_mag**2)
68 f52r=5.d0-2.d0*r_mag**2
69 kir = 2.d0*re_pi*(asin(r_mag)/r_mag + f52r*third*sqrt1r)
70 kfr = 2.d0*re_pi/r_mag**2*(asin(r_mag)/r_mag-sqrt1r) + &
71 2.d0*re_pi*sqrt1r + f52r*0.5d0*fsqrt6*(1.d0 - &
72 2.d0*re_pi*asin((1.d0+2.d0*r_mag**2)/f52r))
77 aix(ix^d,:) = aix(ix^d,:) + kir*rpl(:)
78 afx(ix^d,:) = afx(ix^d,:) + kfr*rcr(:)
80 aix(ix^d,:) = aix(ix^d,:)*i_cur/a
81 afx(ix^d,:) = afx(ix^d,:)*f_flx*0.25d0*re_pi/a**2
84 if(
present(bfr))
call curlvector(atotal,ixi^l,ixo^l,bfr,idirmin,1,ndir)
Module with geometry-related routines (e.g., divergence, curl)
This module contains definitions of global parameters and variables and some generic functions/subrou...
To get a RBSL magnetic flux rope in 3D (Titov 2018 ApJL 852, L21)
subroutine rbsl(ixIL, ixOL, np, a, F_flx, positive_helicity, x, x_axis, Atotal, Bfr)