module em_field_interface interface recursive SUBROUTINE em_field_custom_ring(ele, param, s_rel, t_rel, orb, local_ref, field, calcd, err_flag, & calc_potential, use_overlap, grid_allow_s_out_of_bounds, rf_time, used_eles) USE bmad_struct USE bmad_interface !, except_dummy => em_field_custom IMPLICIT NONE type(ele_struct) :: ele type(lat_param_struct) param type(coord_struct) orb type(em_field_struct) field type (ele_pointer_struct), allocatable, optional :: used_eles(:) real(rp), intent(in) :: s_rel, t_rel real(rp) x,y,s,t real(rp), optional :: rf_time logical out_of_range,local_ref logical, optional :: calcd, err_flag, calc_potential, grid_allow_s_out_of_bounds, use_overlap end subroutine end interface interface recursive subroutine em_field_custom_inj(ele, param, s_rel,t_rel, orb, local_ref,field, calcd, err_flag, & calc_potential, use_overlap, grid_allow_s_out_of_bounds, rf_time, used_eles) use bmad_struct ! use bmad_interface, except_dummy => em_field_custom ! use muon_interface implicit none type(ele_struct) :: ele type(lat_param_struct) param type(coord_struct) orb type(em_field_struct) field type (ele_struct), pointer :: slave type (ele_pointer_struct), allocatable, optional :: used_eles(:) real(rp), intent(in) :: s_rel, t_rel real(rp) xx(3), BB(3),zz, b1(3,3),b2(3,3) real(rp), optional :: rf_time logical out_of_range,local_ref logical, optional :: calcd, err_flag, calc_potential, grid_allow_s_out_of_bounds, use_overlap end subroutine end interface interface SUBROUTINE field_errors(ele,param,s_rel,orb, field_error) USE bmad implicit none type(ele_struct), target :: ele type(lat_param_struct) param type(coord_struct) orb type(em_field_struct) field_error, field real(rp) s_rel end subroutine end interface end module