Store photons in spectra
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=Float64), | intent(in), | dimension(3) | :: | pos | Position of neutral in beam coordinates [machine coordinates for passive case] |
|
real(kind=Float64), | intent(in), | dimension(3) | :: | vi | Velocitiy of neutral in beam coordinates [cm/s] |
|
real(kind=Float64), | intent(in) | :: | lambda0 | Reference wavelength [nm] |
||
real(kind=Float64), | intent(in) | :: | photons | Photons from colrad [Ph/(s*cm^3)] |
||
real(kind=Float64), | intent(inout), | dimension(:,:,:) | :: | spectra | Stark split |
|
real(kind=Float64), | intent(inout), | dimension(:,:,:,:) | :: | stokevec | Stark split |
|
logical, | intent(in), | optional | :: | passive | Indicates whether photon is passive FIDA |
subroutine store_photons(pos, vi, lambda0, photons, spectra, stokevec, passive)
!+ Store photons in `spectra`
real(Float64), dimension(3), intent(in) :: pos
!+ Position of neutral in beam coordinates [machine coordinates for passive case]
real(Float64), dimension(3), intent(in) :: vi
!+ Velocitiy of neutral in beam coordinates [cm/s]
real(Float64), intent(in) :: lambda0
!+ Reference wavelength [nm]
real(Float64), intent(in) :: photons
!+ Photons from [[libfida:colrad]] [Ph/(s*cm^3)]
real(Float64), dimension(:,:,:), intent(inout) :: spectra
!+ Stark split `spectra`
real(Float64), dimension(:,:,:,:), intent(inout) :: stokevec
!+ Stark split `stokes vector`
logical, intent(in), optional :: passive
!+ Indicates whether photon is passive FIDA
real(Float64), dimension(n_stark) :: lambda, intensity
real(Float64), dimension(n_stark,4) :: stokes
real(Float64) :: dlength, sigma_pi
type(LocalEMFields) :: fields
integer(Int32), dimension(3) :: ind
real(Float64), dimension(3) :: pos_xyz, lens_xyz, cyl, vp
type(LOSinters) :: inter
integer :: ichan,i,j,bin,nchan, k
logical :: pas = .False.
if(present(passive)) pas = passive
if(pas) then
cyl(1) = sqrt(pos(1)*pos(1) + pos(2)*pos(2))
cyl(2) = pos(3)
cyl(3) = atan2(pos(2), pos(1))
call get_passive_grid_indices(cyl,ind)
inter = spec_chords%cyl_inter(ind(1),ind(2),ind(3))
call uvw_to_xyz(pos, pos_xyz)
else
call get_indices(pos,ind)
inter = spec_chords%inter(ind(1),ind(2),ind(3))
pos_xyz = pos
endif
nchan = inter%nchan
if(nchan.eq.0) return
call get_fields(fields,pos=pos_xyz)
loop_over_channels: do j=1,nchan
ichan = inter%los_elem(j)%id
dlength = inter%los_elem(j)%length
sigma_pi = spec_chords%los(ichan)%sigma_pi
if(pas) then
call uvw_to_xyz(spec_chords%los(ichan)%lens_uvw,lens_xyz)
else
lens_xyz = spec_chords%los(ichan)%lens
endif
vp = pos_xyz - lens_xyz
call spectrum(vp,vi,fields,lambda0,sigma_pi,photons, &
dlength,lambda,intensity, stokes)
loop_over_stark: do i=1,n_stark
bin=floor((lambda(i)-inputs%lambdamin)/inputs%dlambda) + 1
if (bin.lt.1) cycle loop_over_stark
if (bin.gt.inputs%nlambda) cycle loop_over_stark
!$OMP CRITICAL(spec_stokes)
spectra(i,bin,ichan) = spectra(i,bin,ichan) + intensity(i)
stokevec(i,:,bin,ichan) = stokevec(i,:,bin,ichan) + stokes(i,:)
!$OMP END CRITICAL(spec_stokes)
enddo loop_over_stark
enddo loop_over_channels
end subroutine store_photons