Store NPA particles in npa
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | det | Detector/Channel Number |
||
real(kind=Float64), | intent(in), | dimension(3) | :: | ri | Birth position in beam coordinates [cm] |
|
real(kind=Float64), | intent(in), | dimension(3) | :: | rf | Detector position in beam coordinates [cm] |
|
real(kind=Float64), | intent(in), | dimension(3) | :: | vn | Particle velocity [cm/s] |
|
real(kind=Float64), | intent(in) | :: | flux | Neutral flux [neutrals/s] |
||
integer, | intent(in), | optional | :: | orbit_class | Orbit class ID |
subroutine store_npa(det, ri, rf, vn, flux, orbit_class)
!+ Store NPA particles in [[libfida:npa]]
integer, intent(in) :: det
!+ Detector/Channel Number
real(Float64), dimension(3), intent(in) :: ri
!+ Birth position in beam coordinates [cm]
real(Float64), dimension(3), intent(in) :: rf
!+ Detector position in beam coordinates [cm]
real(Float64), dimension(3), intent(in) :: vn
!+ Particle velocity [cm/s]
real(Float64), intent(in) :: flux
!+ Neutral flux [neutrals/s]
integer, intent(in), optional :: orbit_class
!+ Orbit class ID
integer :: iclass
type(LocalEMFields) :: fields
real(Float64), dimension(3) :: uvw_ri, uvw_rf,vn_norm
real(Float64) :: energy, pitch, dE
integer(Int32), dimension(1) :: ienergy
type(NPAParticle), dimension(:), allocatable :: parts
if(present(orbit_class)) then
iclass = orbit_class
else
iclass = 1
endif
! Convert to machine coordinates
call xyz_to_uvw(ri,uvw_ri)
call xyz_to_uvw(rf,uvw_rf)
! Calculate energy
energy = inputs%ab*v2_to_E_per_amu*dot_product(vn,vn)
dE = npa%energy(2)-npa%energy(1)
! Calculate pitch if distribution actually uses pitch
if(inputs%dist_type.le.2) then
call get_fields(fields, pos = ri)
vn_norm = vn/norm2(vn)
pitch = dot_product(fields%b_norm,vn_norm)
else
pitch = 0.d0
endif
!$OMP CRITICAL(store_npa_1)
npa%npart = npa%npart + 1
if(npa%npart.gt.npa%nmax) then
npa%nmax = int(npa%nmax*2)
allocate(parts(npa%nmax))
parts(1:(npa%npart-1)) = npa%part
deallocate(npa%part)
call move_alloc(parts, npa%part)
endif
npa%part(npa%npart)%detector = det
npa%part(npa%npart)%xi = uvw_ri(1)
npa%part(npa%npart)%yi = uvw_ri(2)
npa%part(npa%npart)%zi = uvw_ri(3)
npa%part(npa%npart)%xf = uvw_rf(1)
npa%part(npa%npart)%yf = uvw_rf(2)
npa%part(npa%npart)%zf = uvw_rf(3)
npa%part(npa%npart)%energy = energy
npa%part(npa%npart)%pitch = pitch
npa%part(npa%npart)%weight = flux
ienergy = minloc(abs(npa%energy - energy))
npa%flux(ienergy(1),det,iclass) = &
npa%flux(ienergy(1),det,iclass) + flux/dE
!$OMP END CRITICAL(store_npa_1)
end subroutine store_npa