module magfield_interface interface subroutine read_field(fringe_or_inflector, map, xmin) use magfield use parameters_bmad implicit none type(magfield_struct), allocatable :: position(:), map(:,:,:) type(magfield_struct) x0,xmin integer fringe_or_inflector end subroutine end interface interface subroutine quadratic_fit(dxyz,fringe_or_inflector,b1,b2) use magfield use parameters_bmad implicit none real(rp) dx type(magfield_struct) dxyz(-1:1) real(rp) b0(3), b1(3), b2(3) integer fringe_or_inflector end subroutine end interface interface subroutine compute_derivatives(fringe_or_inflector,map) use magfield use parameters_bmad implicit none type(magfield_struct), allocatable :: map(:,:,:) type(magfield_struct) x0, xmax, xmin, dxyz(-1:1) integer fringe_or_inflector integer i,j,k,l, ntot(3), ix,jx end subroutine end interface interface subroutine sum_fields(map_inj,map_inf, xmin_inj, xmin_inf,map, xmin) use magfield implicit none type(magfield_struct), allocatable :: map_inj(:,:,:), map_inf(:,:,:) type(magfield_struct), allocatable :: map(:,:,:) type(magfield_struct) x0, xmax, xmin, dxyz(-1:1), xmin_inj, xmin_inf integer ntot(3), ntot_inf(3), idif(3) end subroutine end interface interface subroutine get_g2_fields(x,B,b1,b2, out_of_range) use magfield use parameters_bmad implicit none logical out_of_range real(rp) x(3), B(3) ,b1(3,3),b2(3,3) end subroutine end interface interface subroutine get_field(fringe_or_inflector,y,map,B,b1,b2,out_of_range) use magfield use parameters_bmad implicit none logical out_of_range type(magfield_struct), allocatable :: map(:,:,:) real(rp) B(3) ,b1(3,3),b2(3,3) real(rp) y(3) integer ind(3) integer fringe_or_inflector end subroutine end interface interface subroutine interpolate_field(fringe_or_inflector,x,xgrid_point,B,b1,b2) use bmad use magfield use parameters_bmad implicit none integer fringe_or_inflector real(rp) x(3), B(3),z, b1(3,3),b2(3,3), xgrid_point(3) end subroutine end interface end module