Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer | :: | pp | ||||
type(SPECIES), | intent(in) | :: | spp | An instance of the derived type SPECIES containing all the parameters and simulation variables of the different species in the simulation. |
||
real(kind=rp), | intent(inout), | DIMENSION(3) | :: | gradB | ||
real(kind=rp), | intent(inout), | DIMENSION(3) | :: | curlb | ||
real(kind=rp), | intent(in) | :: | Bmag |
subroutine aux_fields(pp,spp,gradB,curlb,Bmag)
TYPE(SPECIES), INTENT(IN) :: spp
!! An instance of the derived type SPECIES containing all the parameters
!! and simulation variables of the different species in the simulation.
REAL(rp),DIMENSION(3),INTENT(INOUT) :: gradB
REAL(rp),DIMENSION(3),INTENT(INOUT) :: curlb
REAL(rp),INTENT(IN) :: Bmag
REAL(rp) :: dRB
REAL(rp) :: dPHIB
REAL(rp) :: dZB
INTEGER :: pp
dRB=(spp%vars%B(pp,1)*spp%vars%BR(pp,1)+ &
spp%vars%B(pp,2)*spp%vars%BPHI(pp,1)+ &
spp%vars%B(pp,3)*spp%vars%BZ(pp,1))/Bmag
dPHIB=(spp%vars%B(pp,1)*spp%vars%BR(pp,2)+ &
spp%vars%B(pp,2)*spp%vars%BPHI(pp,2)+ &
spp%vars%B(pp,3)*spp%vars%BZ(pp,2))/Bmag
dZB=(spp%vars%B(pp,1)*spp%vars%BR(pp,3)+ &
spp%vars%B(pp,2)*spp%vars%BPHI(pp,3)+ &
spp%vars%B(pp,3)*spp%vars%BZ(pp,3))/Bmag
gradB(1)=dRB
gradB(2)=dPHIB/spp%vars%Y(pp,1)
gradB(3)=dZB
curlb(1)=((Bmag*spp%vars%BZ(pp,2)-spp%vars%B(pp,3)*dPHIB)/spp%vars%Y(pp,1)- &
(Bmag*spp%vars%BPHI(pp,3)-spp%vars%B(pp,2)*dZB))/Bmag**2
curlb(2)=((Bmag*spp%vars%BR(pp,3)-spp%vars%B(pp,1)*dZB)- &
(Bmag*spp%vars%BZ(pp,1)-spp%vars%B(pp,3)*dRB))/Bmag**2
curlb(3)=((Bmag*spp%vars%BPHI(pp,1)-spp%vars%B(pp,2)*dRB) - &
(Bmag*spp%vars%BPHI(pp,1)-spp%vars%B(pp,1)*dPHIB)/ &
spp%vars%Y(pp,1))/Bmag**2+ &
spp%vars%B(pp,2)/(Bmag*spp%vars%Y(pp,1))
end subroutine aux_fields