module muon_interface interface subroutine create_phase_space(nmuons, create_new_distribution, new_file, muon_file, & epsdistr, epsx, epsy, tdistr, tlength, tsigma, pzdistr, pz, pzsigma, twiss2, inf_aperture, inf_end_us, inf_end_ds, energyloss, muons, mat_inv) USE nr ! use bmad use muon_mod IMPLICIT NONE integer nmuons character*16 epsdistr, tdistr, pzdistr, inf_aperture character*120 new_file, muon_file real(rp) tlength, tsigma, pz, pzsigma, epsx, epsy real(rp), optional :: mat_inv(6,6) logical inf_end_us, inf_end_ds, create_new_distribution logical energyloss type (muon_struct), allocatable :: muons(:) type (g2twiss_struct) twiss2 end subroutine end interface interface subroutine compute_moments(muons, turn,moment, nmuons, nmu, unit, ele_name, ix) use muon_mod implicit none real(rp) turn integer n,i,nmuons, nmu, ix integer unit type (muon_struct), allocatable :: muons(:) type (g2moment_struct) moment character*(*) ele_name end subroutine end interface INTERFACE SUBROUTINE compute_beam_params(muons,verbosity, where) USE muon_mod IMPLICIT NONE ! Subroutine arguments TYPE (muon_struct), ALLOCATABLE, INTENT(IN) :: muons(:) INTEGER, OPTIONAL :: verbosity ! controls how much information is printed character*(*), optional:: where END SUBROUTINE compute_beam_params END INTERFACE interface subroutine collect_times(muons, nturns, NN, bin_max) use muon_mod use parameters_bmad implicit none real(rp), allocatable :: NN(:) integer nturns, bin_max type (muon_struct), allocatable :: muons(:) end subroutine end interface interface subroutine write_phase_space(unit, nmuons, muons, string, tot) use muon_mod implicit none integer unit, nmuons integer i integer tot character*(*) string type (muon_struct), allocatable :: muons(:) end subroutine end interface interface subroutine inflector_end_scatter(nmuons, muons) use muon_mod use parameters_bmad implicit none integer unit, nmuons integer i, tot type (muon_struct), allocatable :: muons(:) end subroutine end interface interface function fnalw(center,width) USE parameters_bmad ! fnalw_integral table IMPLICIT NONE REAL(rp) :: fnalw ! quantity to determine REAL(rp), INTENT(IN) :: center, width ! center and width of distribution [a.u.] INTEGER, PARAMETER :: nbins=100 ! number of bins in fnalw_integral table REAL(rp) rand, di, frac_low, frac_high, i_interp ! helper variables INTEGER i end function fnalw end interface interface subroutine read_phase_space(unit, nmuons, muons, string, tot) use muon_mod implicit none integer unit, nmuons integer i, tot character*(*) string type (muon_struct), allocatable :: muons(:) end subroutine end interface interface subroutine twiss_propagate_cm(lat, nbranch) use bmad implicit none type (lat_struct) lat integer nbranch end subroutine end interface interface subroutine read_Vmuons(unit, nmuons, muons,toff, string, tot) use muon_mod implicit none integer unit, nmuons integer i, tot character*(*) string type (muon_struct), allocatable :: muons(:) real(rp) toff end subroutine end interface interface subroutine inflector_scatter(nmuons, muons, inf_end_us, inf_end_ds,energy_loss) use parameters_bmad use muon_mod use materials_mod IMPLICIT NONE type (muon_struct), allocatable :: muons(:) integer i,nmuons logical inf_end_us, inf_end_ds, energy_loss end subroutine end interface interface subroutine check_inflector_aperture(nmuons,muons, inf_aperture, lost_at_inflector) use parameters_bmad use muon_mod use materials_mod IMPLICIT NONE type (muon_struct), allocatable :: muons(:) integer i,nmuons, lost_at_inflector logical withinInflectorAperture character*16 inf_aperture end subroutine end interface interface subroutine create_inv_taylor_ele(ele) use bmad implicit none type (ele_struct) ele real(rp) m(6,6) end subroutine end interface interface subroutine compute_emittance_beta(nmuons,muons, twiss1, epsx,epsy,averages) use bmad use muon_mod implicit none type (muon_struct), allocatable :: muons(:) type (averages_struct) averages type (g2twiss_struct) twiss1 real(rp) epsx, epsy integer nmuons, i end subroutine end interface interface SUBROUTINE fields(ele,x,y,s,t,field) use bmad use parameters_bmad IMPLICIT NONE type (ele_struct) ele type (em_field_struct) field real(rp) x,y,s,t end subroutine fields end interface interface subroutine get_field(y,map,B,b1,b2,out_of_range) use magfield implicit none logical out_of_range type(magfield_struct), allocatable :: map(:,:,:) real(rp) x(3), B(3) ,b1(3,3),b2(3,3) real(rp) y(3) end subroutine end interface interface subroutine optimize_incident(start_orb,lat, opt_orb) use bmad implicit none type (lat_struct) lat type (coord_struct) start_orb, opt_orb end subroutine end interface interface subroutine optimize_twiss(lat, twiss, twiss_opt) use bmad use muon_mod implicit none type (lat_struct) lat type (g2twiss_struct) twiss, twiss_opt end subroutine end interface end module