! interfaces for bsim_cesr subroutines module bsim_cesr_interface use bmad interface subroutine assign_unique_ele_ids(lat) import implicit none type(lat_struct) lat end subroutine SUBROUTINE make_sigma_mat(canonical_dist,sigma_mat,sigma_beta_mat) import IMPLICIT none TYPE(coord_struct) canonical_dist(:) REAL(rp) sigma_mat(:,:), sigma_beta_mat(:,:) end subroutine make_sigma_mat SUBROUTINE normal_sigma_mat(sigma_mat,normal) import IMPLICIT none REAL(rp) sigma_mat(1:6,1:6) REAL(rp) normal(1:3) REAL(rp) eval_r(1:6), eval_i(1:6) REAL(rp) evec_r(1:6,1:6), evec_i(1:6,1:6) REAL(rp) sigmaS(1:6,1:6) REAL(rp) S(1:6,1:6) REAL(rp), PARAMETER :: S2(1:2,1:2) = reshape([0, -1, 1, 0], [2,2]) LOGICAL error end SUBROUTINE normal_sigma_mat subroutine find_steerings(cesr,hkick_ix,vkick_ix) use cesr_basic_mod, only: db_struct import implicit none type(db_struct) :: cesr integer, allocatable :: hkick_ix(:), vkick_ix(:) integer :: i, n_steering_h, n_steering_v, steering_index end subroutine find_steerings subroutine gain_cbar(ring, bpm, phi, cbar) use sim_bpm_mod import implicit none type(lat_struct), target :: ring type(det_struct) bpm(:) real(rp), allocatable :: phi(:,:,:), cbar(:,:,:) end subroutine gain_cbar subroutine rotate_cbar(ele, tilt, cbar) import implicit none type(ele_struct) ele real(rp) :: cbar(2,2) real(rp) :: tilt end subroutine rotate_cbar function set_tune3(lat, target_tunes, verbose_in, write_out_in, regex_in) result (everything_ok) use bmad_struct, only: lat_struct, rp implicit none type(lat_struct), target :: lat real(rp) target_tunes(3) logical everything_ok logical, optional :: verbose_in integer, optional :: write_out_in character(40), optional :: regex_in end function set_tune3 subroutine sim_tbt_data(ring, bpm, n_turns, track6x6, n_TTs, tt_params, id, n_damping, init_vec, bpm_save, tt_tunes, ele_noise) use sim_bpm_mod, only: det_struct, det_data_struct use ele_noise_mod, only: ele_noise_struct use tune_tracker_mod, only: tt_param_struct import implicit none type(lat_struct) :: ring type(det_data_struct), allocatable :: bpm_save(:,:) type(det_struct) :: bpm(:) type(tt_param_struct), optional :: tt_params(:) type(ele_noise_struct), optional :: ele_noise(:) integer, intent(in), optional :: id(:) integer, optional :: n_TTs logical, intent(in) :: track6x6 integer, intent(in) :: n_turns real(rp), intent(in) :: init_vec(6) integer, intent(in), optional :: n_damping real(rp), allocatable, optional :: tt_tunes(:,:) end subroutine sim_tbt_data end interface end module bsim_cesr_interface