!+ ! Subroutine track1_preprocess (start_orb, ele, param, err_flag, finished, radiation_included, track) ! ! Dummy routine for pre-processing at the start of the track1 routine. ! ! Also see: ! track1_postprocess ! track1_custom ! ! The radiation_included argument should be set to True if this routine (or a modified version of track1_custom) ! takes into account radiation damping and/or excitation. This will prevent track1 from calling track1_radiation. ! Note: If symp_lie_bmad is being called by this routine, symp_lie_bmad does take into account radiation effects. ! ! General rule: Your code may NOT modify any argument that is not listed as an output agument below. ! ! Modules Needed: ! use bmad ! ! Input: ! start_orb -- coord_struct: Starting position at the beginning of ele. ! ele -- ele_struct: Element. ! param -- lat_param_struct: Lattice parameters. ! ! Output: ! start_orb -- coord_struct: Modified starting position for track1 to use. ! err_flag -- logical: Set true if there is an error. False otherwise. ! finished -- logical: When set True, track1 will halt further processing and use the modified ! start_orb as the final end position of the particle. ! radiation_included ! -- logical: Should be set True if radiation damping/excitation is included in the tracking. ! track -- track_struct, optional: Structure holding the track information if the ! tracking method does tracking step-by-step. !- subroutine track1_preprocess (start_orb, ele, param, err_flag, finished, radiation_included, track) use bmad !, except_dummy => track1_preprocess use quad_scrape_parameters use parameters_bmad use muon_mod use muon_interface implicit none type (coord_struct) :: start_orb, orb type (ele_struct), target :: ele type (ele_struct), pointer :: ele_init type (lat_param_struct) :: param type (track_struct), optional :: track type (ele_struct), pointer :: lord type (em_field_struct) field, xfield_plus, xfield_minus, yfield_plus,yfield_minus logical err_flag, finished, radiation_included, err logical grid logical local_ref_frame/.true./ character(*), parameter :: r_name = 'track1_preprocess' !real(rp) scrape_scale, omega, init_scrape/0.70937/, quad_ramp_start_time/7.e-6/, quad_ramp_end_time/30.e-6/ real(rp) focus_scrape_scale, omega, steer_scrape_scale, tau real(rp) scale real(rp) aperture/0.065/ real(rp) min_lim/-0.08/, max_lim/0.2/, max_ang/0.2/ real(rp) t real(rp) s_pos/0.001/ real(rp) voltage real(rp) q1ltop, q1lbottom real(rp) f_index, v_value real(rp) rf_v_field_scale, rf_h_field_scale real(rp) t0/1.e-6/ !real(rp), save :: t0_h_min(4), t0_h_max(4), t0_v_min(4), t0_v_max(4) real(rp) temp real(rp) dx/0.001/ integer i, igrid/1/ integer state integer quad_number integer, save :: lun logical first/.true./ ! !print *,' TRACK1_PREPROCESS' if(start_orb%species /= positron$)then if(index(ele%branch%name,'INJ') == 0)then if(start_orb%vec(1) < min_lim .or. start_orb%vec(2) < -max_ang) start_orb%state = lost_neg_x_aperture$ if(start_orb%vec(1) > max_lim.or. start_orb%vec(2) > max_ang) start_orb%state = lost_pos_x_aperture$ if(start_orb%vec(3) < min_lim .or. start_orb%vec(4) < -max_ang) start_orb%state = lost_neg_y_aperture$ if(start_orb%vec(3) > max_lim .or. start_orb%vec(4) > max_ang) start_orb%state = lost_pos_y_aperture$ endif endif if(start_orb%state /= alive$)then finished = .true. err_flag = .true. !added 11/25/23 so that track1 returns an err to track_all return endif orb_diff = 0. err_flag=.false. !print '(a,a,l)','TRACK1:preprocess before QUAD ', ele%name, err_flag if(index(ele%name,'QUAD') == 0)return if((start_orb%species /= antimuon$ .and. start_orb%species/= proton$))return grid = .false. if((associated(ele%grid_field)))then grid = .true. lord => ele elseif(ele%field_calc == refer_to_lords$)then do i=1,ele%n_lord lord => pointer_to_lord(ele,i) if(associated(lord%grid_field))then grid = .true. exit endif end do endif if(rfquad_params_reset .and. grid)then do i=1,4 if(rf_quad(i)%freq_h /= 0)then t0_h_min(i) = rf_quad(i)%start_h + rf_quad(i)%phi_h/360. / rf_quad(i)%freq_h t0_h_max(i) = t0_h_min(i) + rf_quad(i)%periods_h/rf_quad(i)%freq_h endif if(rf_quad(i)%freq_v /= 0)then t0_v_min(i) = rf_quad(i)%start_v + rf_quad(i)%phi_v/360. / rf_quad(i)%freq_v t0_v_max(i) = t0_v_min(i) + rf_quad(i)%periods_v/rf_quad(i)%freq_v endif end do endif ! if(.not. fixed_quad_time)quad_time = start_orb%t !if positive, then use the orbit time. If negative use abs quad_time if(grid)then orb_diff = 0. aperture = 0.065 if(abs(start_orb%vec(1)) > aperture .and. start_orb%vec(1)*start_orb%vec(2) > 1.4e-4 .and. start_orb%species /= positron$)then if(start_orb%vec(1) < -aperture)start_orb%state = lost_neg_x_aperture$ if(start_orb%vec(1) > aperture)start_orb%state = lost_pos_x_aperture$ print '(a,1x,6es12.4,1x,a, es12.4,1x,a)',' TRACK1_preprocess: orb,name,ele%s, state ',start_orb%vec, ele%name, ele%s, coord_state_name(start_orb%state) start_orb%state = lost$ finished = .true. err_flag = .true. !set err_flag=.true. 11/25/23 to solve problem with track1 returning ambiguous results after calling this routine return endif if(abs(start_orb%vec(1)) > 0.06)then !shift to edge of map orb_diff = abs(start_orb%vec(1)) - 0.06 start_orb%vec(1)= start_orb%vec(1) - sign(orb_diff, start_orb%vec(1)) !for particles outside range of map, place them right at the edge. This offset will be subtracted in track1_postprocess ! print '(a,a,a,1x,es12.4)','track1_preprocess: ele =',ele%name,' orb_diff = ', orb_diff endif if(rfquad_params_reset)then if(quad_scrape_rf_verbose)then if(first)then lun=91 open(unit=lun, access='sequential', file=trim(directory)//'/rfquad_params.dat', position='append') first=.false. endif write(lun, '(a)')'TRACK1_PREPROCESS: ' write(lun, '(11a12)')'quad','t0_h_min','t0_h_max','t0_v_min','t0_v_max','amp_h','amp_v','phi_h','phi_v','start_h','start_v' do i=1,4 write(lun, '(i12,10es12.4)')i,t0_h_min(i),t0_h_max(i),t0_v_min(i),t0_v_max(i), rf_quad(i)%amp_h, rf_quad(i)%amp_v, rf_quad(i)%phi_h, rf_quad(i)%phi_v, rf_quad(i)%start_h, rf_quad(i)%start_v end do endif ! rfquad_params_reset = .false. endif !rfquad_params_reset endif !grid if(index(ele%name,'QUAD')/=0 .and. scraping_on .and. (ele%field_calc /= fieldmap$) )then if(ele%field_calc == refer_to_lords$)then do i=1,ele%n_lord lord => pointer_to_lord(ele,i) if(lord%field_calc == fieldmap$ .or. lord%field_calc == custom$)cycle print '(/,i10,1x,a10,a16,1x,a15,1x,a)',i,'Element = ',ele%name, ' Lord Element = ', field_calc_name(lord%field_calc) print '(a10,1x,a16,1x,a)', 'Element = ', ele%name, trim(field_calc_name(ele%field_calc)) print *,' SCRAPING_ON = T is not compatible with quad em_field_calc method ' stop enddo endif endif !fringe field at entrance to quad if(quad_fringe_energy_change)then orb = start_orb call em_field_calc(ele, param, s_pos, orb, local_ref_frame, field, err_flag = err_flag) voltage = field%E(1)*orb%vec(1) + field%E(2)*orb%vec(3) start_orb%vec(6) = orb%vec(6) + voltage/ele%value(E_TOT$) endif !print '(a16,1x,es12.4,1x,es12.4,1x,es12.4,4es12.4)',ele%name, scrape_scale, value_of_attribute(ele, 'QUAD_VOLTAGE', err),quad_time, ele%grid_field(2:5)%field_scale err_flag = .false. return end subroutine !Hi David, !It is not very well-documented anywhere, but I can give you the numbers you’re looking for. !Quad / Mode / Frequency (kHz) / Start time (us) / NPeriods / Amplitude (V) / Delay phase (deg) !Q1 HD 320 0 2 0.21 170 !Q1 VD 2060 3.5 6 -0.2 90 !Q2 HD 320 0 2 0.21 260 !Q2 VD 2060 3.5 6 -0.2 90 !Q3 HD 320 0 2 -0.21 170 !Q3 VD 2060 3.5 6 -0.2 90 !Q4 HD 320 0 2 -0.21 260 !Q4 VD 2060 3.5 6 -0.2 90 !HD stands for the horizontal dipole (thus, RF goes to the inner and outer plates with opposite phases), and VD stands for the vertical dipole. !We apply the horizontal dipole on all short and long quads and the vertical dipole on only the long quads. !The start time is with respect to the CCC trigger, which is ~1 us earlier than the beam injection (IBMS3 trigger). !The amplitudes are obviously not the actual voltage on the plates, but they are voltages at the signal generator output and will be amplified via the RF amplifiers. !The gain varies quad plate by plate, but this 0.2 V roughly corresponds to 1 kV amplitude at the plate for the HD and 0.3 kV for the VD. !The Quad group plans to map the RF voltage on the plates in January, so I can keep you posted if you are interested in more accurate RF amplitudes. !The delay phase shifts the start time according to the given value. !For instance, the delay phase 170 degrees for 320 kHz HD at start time 0 us is actually firing at 1/0.32 * 170/360 = 1.476 us instead of 0 us. !The reason behind this is that we want the RF to be “gated” and the beginning of the RF to be at 0 voltage to avoid an “abrupt” rise. !Likewise, the end time is decided by NPeriods, which are given to be integers to ensure the RF ends at 0 voltage. !Please let me know if you have any questions or need any clarifications. !Best regards, !On !From: David L. Rubin !Date: Sunday, December 10, 2023 at 4:20 PM !To: On Kim !Subject: Rf quad parameters ! my interpretation of On's note. Sin( 2 pi f t + phi)