module bmadz_interface use bmad_struct ! This is to suppress the ranlib "has no symbols" message integer, private :: private_dummy interface subroutine choose_quads(lat, dk1, regex_mask_in) import implicit none type (lat_struct) lat real(rp), allocatable :: dk1(:) character(40), optional :: regex_mask_in end subroutine subroutine curly_d(lat, co, quad, synch_int2, curlyd) use zquad_lens_mod, only: lat_struct, coord_struct, zquad_struct, rp implicit none type (lat_struct) lat type (coord_struct), allocatable :: co(:) type (zquad_struct) quad real(rp) synch_int2, curlyd end subroutine curly_d subroutine custom_set_tune (phi_x_set, phi_y_set, dk1, lat, orb, ok, match) import implicit none type (lat_struct) lat type (coord_struct), allocatable :: orb(:) real(rp) phi_x_set real(rp) phi_y_set real(rp), allocatable :: dk1(:) logical ok logical, optional :: match end subroutine subroutine dx_dpretz1_calc ( lat, prz1_diff) import implicit none type (lat_struct) lat type (coord_struct), allocatable :: prz1_diff(:) end subroutine dx_dpretz1_calc subroutine dx_dpretz13_calc ( lat, prz13_diff) import implicit none type (lat_struct) lat type (coord_struct), allocatable :: prz13_diff(:) end subroutine dx_dpretz13_calc subroutine dx_dvcros5_calc ( lat, vc_diff) import implicit none type (lat_struct) lat type (coord_struct), allocatable :: vc_diff(:) end subroutine dx_dvcros5_calc subroutine dx_dvcros7_calc ( lat, vc7_diff) import implicit none type (lat_struct) lat type (coord_struct), allocatable :: vc7_diff(:) end subroutine dx_dvcros7_calc subroutine emit_calc (lat, what, mode) import implicit none type (lat_struct) lat type (normal_modes_struct) mode integer what end subroutine subroutine get_cl_input (con_file, con) use constraints_mod, only: constraint_struct implicit none character*(*), intent(out) :: con_file type (constraint_struct), intent(out) :: con end subroutine get_cl_input subroutine max_or_min_disp(con, co, i_con, value, location) use constraints_mod, only: coord_struct, constraint_struct, rp implicit none type (coord_struct), allocatable :: co(:) type (constraint_struct) con integer i_con, location real(rp) value end subroutine max_or_min_disp subroutine electron_positron (lat_1, lat_pos, lat_ele, co_positron, co_electron, con, global ) use constraints_mod, only: lat_struct, coord_struct, constraint_struct use bmadz_struct, only: global_struct implicit none type (lat_struct) lat_pos, lat_ele, lat_1 type (coord_struct), allocatable :: co_positron(:), co_electron(:) type (global_struct) global type (constraint_struct) con end subroutine electron_positron subroutine name_to_list (lat, ele_names) import implicit none type (lat_struct), target :: lat character(*) ele_names(:) end subroutine subroutine lrbbi_setup (lat_in, lat_out, particle, i_train, j_car, n_trains_tot, n_cars, current, rec_taylor, bbiwt, custom_pat) use bmad implicit none type ( lat_struct ) lat_in, lat_out integer particle integer i_train, j_car, n_trains_tot, n_cars real(rp) current logical rec_taylor real(rp), dimension(:,:), optional :: bbiwt logical, optional :: custom_pat end subroutine subroutine beambeam_separation (lat, delta_ip, i_dim, diff_co) import implicit none type ( lat_struct ) lat type (coord_struct) delta_ip type (coord_struct), optional :: diff_co(0:) integer i_dim end subroutine subroutine transfer_line_matrix_calc(lat, start_name, end_name, mat, detmn_dag) use bmad implicit none type (lat_struct) lat real(rp) mat(6,6) real(rp) mn_dag(2,2), detmn_dag character*12 start_name, end_name end subroutine subroutine quad_beta_ave (ele, beta_a_ave, beta_b_ave) import implicit none type (ele_struct), target :: ele real(rp) beta_a_ave real(rp) beta_b_ave end subroutine subroutine qp_tune(lat, qpx,qpy, ok, element1, element2) import implicit none type (lat_struct) lat real(rp) qpx, qpy character*16, optional :: element1, element2 logical ok end subroutine ! subroutine osc_parameters(lat, ix_start,ix_end, co, osc_param, verbose) ! use bmad ! use mode3_mod ! implicit none ! type (lat_struct) lat ! type (coord_struct), allocatable :: co(:) ! type osc_param_struct ! real(rp) Tmat(6,6), tilde_m56, delta_s, wavelength ! real(rp) osc_emit_max, osc_dp_max ! real(rp) t5mat(6,6) ! end type ! type (osc_param_struct) osc_param ! integer ix_start, ix_end ! logical verbose ! end subroutine end interface end module