MODULE parameters USE nrtype USE precision_def IMPLICIT NONE ! Physical constants: REAL(RP), PARAMETER :: muonmass_MeV = 105.658367 REAL(RP), PARAMETER :: muonmass_kg = 1.883531475e-28 REAL(RP), PARAMETER :: muoncharge_C = 1.602176487e-19 REAL(RP), PARAMETER :: speedoflight = 299792458. ! in meters/second ! Assuming times measured in nanoseconds, here are conversions for the units used in the program ! All inputs must be converted to these units before being used by derivs.f90, because the ! differential equations in that subroutine are written in dimensionless form REAL(RP), PARAMETER :: timeunit_s = 1e-9 REAL(RP), PARAMETER :: lengthunit_m = speedoflight*timeunit_s REAL(RP), PARAMETER :: momentumunit_MeVperc = muonmass_MeV REAL(RP), PARAMETER :: Bfieldunit_T = muonmass_kg/(muoncharge_C*timeunit_s) REAL(RP), PARAMETER :: voltageunit_V = muonmass_kg*speedoflight**2/muoncharge_C ! Coordinates, dimensions and constants, converted to my units: ! Muons enter the ring at theta = 0 ! Time zero is when the center of the muon bunch enters the ring REAL(RP), PARAMETER :: storageradius = 7.112/lengthunit_m REAL(RP), PARAMETER :: magicmomentum = 3094.3/momentumunit_MeVperc REAL(RP), DIMENSION(3), PARAMETER :: dipoleBfield = [0.0_rp, 1.451275843/Bfieldunit_T, 0.0_rp] ! uniform vertical magnetic field ! quadrupole parameters REAL(RP), PARAMETER :: Qangle = 39*pi/180 ! each quadrupole spans 39 degrees of the ring REAL(RP), PARAMETER :: Q1center = pi/4 REAL(RP), PARAMETER :: Q2center = 3*pi/4 REAL(RP), PARAMETER :: Q3center = 5*pi/4 REAL(RP), PARAMETER :: Q4center = 7*pi/4 REAL(RP), PARAMETER :: Q1start = Q1center - 0.5*Qangle REAL(RP), PARAMETER :: Q1end = Q1center + 0.5*Qangle REAL(RP), PARAMETER :: Q2start = Q2center - 0.5*Qangle REAL(RP), PARAMETER :: Q2end = Q2center + 0.5*Qangle REAL(RP), PARAMETER :: Q3start = Q3center - 0.5*Qangle REAL(RP), PARAMETER :: Q3end = Q3center + 0.5*Qangle REAL(RP), PARAMETER :: Q4start = Q4center - 0.5*Qangle REAL(RP), PARAMETER :: Q4end = Q4center + 0.5*Qangle REAL(RP), PARAMETER :: Qplatesep = 0.1/lengthunit_m ! plates are 10 cm apart REAL(RP), PARAMETER :: Q1platethickness = 0.0001/lengthunit_m ! Q1 plate is 0.1 mm thick REAL(RP), PARAMETER :: radlength = 0.08897/lengthunit_m ! radiation length for aluminum, 8.897 cm REAL(RP), PARAMETER :: Qb2 = -20177.8/(voltageunit_V*(0.045/lengthunit_m)**2) REAL(RP), PARAMETER :: Qb4 = -33.0/(voltageunit_V*(0.045/lengthunit_m)**4) REAL(RP), PARAMETER :: Qb6 = 45.9/(voltageunit_V*(0.045/lengthunit_m)**6) ! Kicker parameters... ! ...related to size/location: REAL(RP), PARAMETER :: kickercenter = pio2 ! theta for center of kicker (currently set to 90 degrees) REAL(RP), PARAMETER :: kickerangle = 5.28/7.112 ! storage ring angle filled by kicker REAL(RP), PARAMETER :: kickerstart = kickercenter - 0.5*kickerangle REAL(RP), PARAMETER :: kickerend = kickercenter + 0.5*kickerangle ! ...related to the RLC circuit; derivs.f90 uses these to calculate the time-dependence of the kicker REAL(RP), PARAMETER :: kickerR = 11.5*timeunit_s ! resistance = 11.5 ohms (converted to use nanoseconds) REAL(RP), PARAMETER :: kickerL = 1.6e-6 ! inductance, in henries REAL(RP), PARAMETER :: kickerC = 10.0e-9/(timeunit_s**2) ! capacitance = 10 nanofarads ! Adjustable kicker parameters ! ( Read in with other inputs; defined here so that the derivs subroutine will have access to the values) REAL(RP) :: kickermaxtime ! time when kicker field is at maximum (t=0 when center of muon bunch enters ring) REAL(RP) :: kickermagnitude ! maximum value of kicker B-field (in Bfieldunits) ! logical values to signal whether the muon is in a quadrupole region, a kicker region, or neither ! (defined here so main program and derivs subroutine will both have access to them) LOGICAL :: quad, kick END MODULE parameters