Calculate Passive NPA flux using a fast-ion distribution function F(E,p,r,z)
subroutine pnpa_f
!+ Calculate Passive NPA flux using a fast-ion distribution function F(E,p,r,z)
integer :: i,j,k,det,ic
integer(Int64) :: iion
real(Float64), dimension(3) :: rg,ri,rf,vi,ri_uvw
integer, dimension(3) :: ind
real(Float64) :: denf,r
type(LocalProfiles) :: plasma
type(LocalEMFields) :: fields
type(GyroSurface) :: gs
real(Float64), dimension(2,4) :: gyrange
real(Float64), dimension(nlevs) :: rates
real(Float64), dimension(nlevs) :: states
real(Float64) :: flux, theta, dtheta, eb, ptch,max_papprox
integer :: inpa,ichan,nrange,ir,npart,ncell
integer, dimension(pass_grid%ngrid) :: cell_ind
real(Float64), dimension(pass_grid%nr,pass_grid%nz,pass_grid%nphi) :: papprox
integer(Int32), dimension(pass_grid%nr,pass_grid%nz,pass_grid%nphi) :: nlaunch
papprox=0.d0
do ic=1,pass_grid%ngrid
call ind2sub(pass_grid%dims,ic,ind)
i = ind(1) ; j = ind(2) ; k = ind(3)
call get_plasma(plasma,ind=ind,input_coords=2)
if(.not.plasma%in_plasma) cycle
papprox(i,j,k) = sum(plasma%denn)*plasma%denf
enddo
max_papprox = maxval(papprox)
where (papprox.lt.(max_papprox*1.d-6))
papprox = 0.0
endwhere
ncell = 0
do ic=1,pass_grid%ngrid
call ind2sub(pass_grid%dims,ic,ind)
i = ind(1) ; j = ind(2) ; k = ind(3)
if(papprox(i,j,k).gt.0.0) then
ncell = ncell + 1
cell_ind(ncell) = ic
endif
enddo
call get_nlaunch_pass_grid(inputs%n_pnpa, papprox, nlaunch)
if(inputs%verbose.ge.1) then
write(*,'(T6,"# of markers: ",i12)') sum(nlaunch)
endif
!! Loop over all cells that can contribute to NPA signal
!$OMP PARALLEL DO schedule(dynamic,1) private(ic,i,j,k,ind,iion,ichan,fields,nrange,gyrange, &
!$OMP& vi,ri,rf,det,plasma,rates,states,flux,denf,eb,ptch,gs,ir,theta,dtheta,r,ri_uvw)
loop_over_cells: do ic = istart, ncell, istep
call ind2sub(pass_grid%dims,cell_ind(ic),ind)
i = ind(1) ; j = ind(2) ; k = ind(3)
loop_over_fast_ions: do iion=1, nlaunch(i, j, k)
!! Sample fast ion distribution for energy and pitch
call mc_fastion_pass_grid(ind, fields, eb, ptch, denf)
if(denf.le.0.0) cycle loop_over_fast_ions
call gyro_surface(fields, eb, ptch, gs)
detector_loop: do ichan=1,npa_chords%nchan
call npa_gyro_range(ichan, gs, gyrange, nrange)
if(nrange.eq.0) cycle detector_loop
gyro_range_loop: do ir=1,nrange
dtheta = gyrange(2,ir)
theta = gyrange(1,ir) + 0.5*dtheta
call gyro_trajectory(gs, theta, ri, vi)
!! Check if particle hits a NPA detector
call hit_npa_detector(ri, vi ,det, rf, ichan)
if(det.ne.ichan) then
if (inputs%verbose.ge.0)then
write(*,*) "PNPA_F: Missed Detector ",ichan
endif
cycle gyro_range_loop
endif
!! Calculate CX probability with beam and halo neutrals
call get_plasma(plasma, pos=ri)
call bt_cx_rates(plasma, plasma%denn, vi, beam_ion, rates)
if(sum(rates).le.0.) cycle gyro_range_loop
!! Weight CX rates by ion source density
states=rates*denf
!! Attenuate states as the particle move through plasma
call attenuate(ri,rf,vi,states)
!! Store NPA Flux
flux = (dtheta/(2*pi))*sum(states)*pass_grid%r(i)*pass_grid%dv/nlaunch(i,j,k)
call store_npa(det,ri,rf,vi,flux,passive=.True.)
enddo gyro_range_loop
enddo detector_loop
enddo loop_over_fast_ions
enddo loop_over_cells
!$OMP END PARALLEL DO
npart = pnpa%npart
#ifdef _MPI
call parallel_sum(npart)
call parallel_sum(pnpa%flux)
#endif
if(inputs%verbose.ge.1) then
write(*,'(T4,"Number of Passive NPA particles that hit a detector: ",i8)') npart
endif
end subroutine pnpa_f