store_fw_photons_at_chan Subroutine

public subroutine store_fw_photons_at_chan(ichan, eind, pind, vp, vi, fields, dlength, sigma_pi, denf, photons)

Store FIDA weight photons in fweight for a specific channel

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: ichan

Channel index

integer, intent(in) :: eind

Energy index

integer, intent(in) :: pind

Pitch index

real(kind=Float64), intent(in), dimension(3):: vp

Vector pointing toward optical head

real(kind=Float64), intent(in), dimension(3):: vi

Velocity of neutral [cm/s]

type(LocalEMFields), intent(in) :: fields

Electro-magnetic fields

real(kind=Float64), intent(in) :: dlength

LOS intersection length with beam_grid cell particle is in

real(kind=Float64), intent(in) :: sigma_pi

Sigma-pi ratio for channel

real(kind=Float64), intent(in) :: denf

Fast-ion density [cm^-3]

real(kind=Float64), intent(in) :: photons

Photons from colrad [Ph/(s*cm^3)]


Calls

proc~~store_fw_photons_at_chan~~CallsGraph proc~store_fw_photons_at_chan store_fw_photons_at_chan proc~spectrum spectrum proc~store_fw_photons_at_chan->proc~spectrum

Called by

proc~~store_fw_photons_at_chan~~CalledByGraph proc~store_fw_photons_at_chan store_fw_photons_at_chan proc~fida_weights_los fida_weights_los proc~fida_weights_los->proc~store_fw_photons_at_chan proc~store_fw_photons store_fw_photons proc~store_fw_photons->proc~store_fw_photons_at_chan program~fidasim fidasim program~fidasim->proc~fida_weights_los

Contents


Source Code

subroutine store_fw_photons_at_chan(ichan,eind,pind,vp,vi,fields,dlength,sigma_pi,denf,photons)
    !+ Store FIDA weight photons in [[libfida:fweight]] for a specific channel
    integer, intent(in)                     :: ichan
        !+ Channel index
    integer, intent(in)                     :: eind
        !+ Energy index
    integer, intent(in)                     :: pind
        !+ Pitch index
    real(Float64), dimension(3), intent(in) :: vp
        !+ Vector pointing toward optical head
    real(Float64), dimension(3), intent(in) :: vi
        !+ Velocity of neutral [cm/s]
    type(LocalEMFields), intent(in)         :: fields
        !+ Electro-magnetic fields
    real(Float64), intent(in)               :: dlength
        !+ LOS intersection length with [[libfida:beam_grid]] cell particle is in
    real(Float64), intent(in)               :: sigma_pi
        !+ Sigma-pi ratio for channel
    real(Float64), intent(in)               :: denf
        !+ Fast-ion density [cm^-3]
    real(Float64), intent(in)               :: photons
        !+ Photons from [[libfida:colrad]] [Ph/(s*cm^3)]

    real(Float64), dimension(n_stark) :: lambda,intensity
    real(Float64) :: dlambda,intens_fac
    integer :: i,bin


    dlambda=(inputs%lambdamax_wght-inputs%lambdamin_wght)/inputs%nlambda_wght
    intens_fac = (1.d0)/(4.d0*pi*dlambda)
    call spectrum(vp,vi,fields,sigma_pi,photons, &
                  dlength,lambda,intensity)

    !$OMP CRITICAL(fida_wght)
    loop_over_stark: do i=1,n_stark
        bin=floor((lambda(i) - inputs%lambdamin_wght)/dlambda) + 1
        if (bin.lt.1)                   cycle loop_over_stark
        if (bin.gt.inputs%nlambda_wght) cycle loop_over_stark
        !fida(bin,ichan)= fida(bin,ichan) + &
        !  (denf*intens_fac*1.d4)*intensity(i) !ph/(s*nm*sr*m^2)
        fweight%weight(bin,eind,pind,ichan) = &
          fweight%weight(bin,eind,pind,ichan) + intensity(i)*intens_fac !(ph*cm)/(s*nm*sr*fast-ion*dE*dp)
    enddo loop_over_stark
    if(denf.gt.0.d0) then
        fweight%mean_f(eind,pind,ichan) = fweight%mean_f(eind,pind,ichan) + &
                                          (denf*intens_fac)*sum(intensity)
    endif
    !$OMP END CRITICAL(fida_wght)

end subroutine store_fw_photons_at_chan