module compile_interface interface subroutine get_tunes(dir, qx,qy,betax,betay,eta) use sim_utils implicit none character(*) dir real(rp) twiss(1:5), qx,qy,betax,betay,eta end subroutine get_tunes end interface interface subroutine fft_x_y(time_bin, tbin_max, moments_sum, q_horz, q_vert, data_fft_n, data_fft_x, data_fft_y) use compile_mod implicit none TYPE (g2moment_struct), allocatable :: moments_sum(:) !moment structure for each time bin, 1000 turns => an array with 1000*149e-9/bin_width real(rp) q_horz, q_vert, f_rev complex(rp), allocatable ::data_fft_n(:), data_fft_x(:), data_fft_y(:) real(rp) time_bin integer tbin_max end subroutine fft_x_y end interface interface subroutine fit_fft_peak(data_fft,peak_bin, mrev_fit) use precision_def implicit none complex(rp), allocatable :: data_fft(:) integer peak_bin real(rp) mrev_fit end subroutine fit_fft_peak end interface interface subroutine get_column_data(long_string, column) use precision_def implicit none real(rp), allocatable :: column(:) character(*) long_string end subroutine get_column_data end interface interface subroutine create_2D_histogram_array(column,ix,iy,iz,xmin, xmax, ix_bins,ymin,ymax,iy_bins,ix_0, iy_0, sum, number, at_limit, xcolumn, ycolumn) use precision_def implicit none real(rp), allocatable:: column(:) real(rp), allocatable :: sum(:,:) real(rp) xmin, xmax, ymin, ymax real(rp) ix_0, iy_0 real(rp), optional :: xcolumn, ycolumn integer ix,iy, ixx, iyy,iz integer ix_bins, iy_bins integer number integer at_limit(3) end subroutine create_2D_histogram_array end interface interface subroutine create_2D_special_histogram_array(column,ix,iy,xmin, xmax, ix_bins,ymin,ymax,iy_bins,ix_0, iy_0, sum) use precision_def implicit none real(rp), allocatable:: column(:) real(rp), allocatable :: sum(:,:) real(rp) xmin, xmax, ymin, ymax real(rp) ix_0, iy_0 integer ix,iy, ixx, iyy integer ix_bins, iy_bins end subroutine create_2D_special_histogram_array end interface interface subroutine create_1D_histogram_array(column,ix,xmin, xmax, ix_bins,ix_0, sum, average, rms2 ) use precision_def implicit none real(rp), allocatable:: column(:) real(rp), allocatable :: sum(:) real(rp) xmin, xmax real(rp) ix_0 real(rp) average, x2_avg, rms2 integer ix, ixx integer ix_bins end subroutine create_1D_histogram_array end interface interface subroutine compress_2D(ix_bins,iy_bins,twod_sum,xmin,xmax,ymin,ymax,number, file) use precision_def use sim_utils implicit none character*300 file real(rp), allocatable :: twod_sum(:,:) real(rp) xmin, xmax, ymin, ymax integer ix_bins, iy_bins, ixx,iyy integer number end subroutine compress_2D end interface interface subroutine funcs(x,coef,yfit,dydcoef) use precision_def use nrtype implicit none real(rp), dimension(:), intent(in) :: x, coef real(rp), dimension(:), intent(out) :: yfit real(rp), dimension(:,:), intent(out) :: dydcoef end subroutine funcs end interface interface subroutine fit_2D_array(x, y, kx,order, number) use precision_def use nr implicit none real(rp) chisq, alambda real(rp) old_chisq real(rp), allocatable :: x(:), y(:), sig(:), coef(:) real(rp), allocatable :: covar(:,:), alpha(:,:) logical, allocatable :: maskcoef(:) integer kx,i integer number integer order end subroutine fit_2D_array end interface interface subroutine get_errors(dspin_dx, dspin_dxp,dx_dp, dxp_dp,delta1, delta2, do0_err, do1_err, do2_err) use precision_def use muon_mod implicit none ! type deriv_struct ! real(rp) coef(4), coef_err(4), chisq ! integer norder ! end type type (deriv_struct) dspin_dx, dspin_dxp, dx_dp, dxp_dp, dp_dt real(rp) delta1, delta2 real(rp) do0_err, do1_err, do2_err real(rp) delta1_err, delta2_err end subroutine get_errors end interface interface subroutine bin_data(c1, c2, numbins, xmin, xmax, count, binsum, p, out_of_range) use precision_def implicit none integer numbins integer, allocatable :: count(:) integer out_of_range real(rp) xmin, xmax real(rp), allocatable :: binsum(:), p(:) real(rp) c1, c2 end subroutine bin_data end interface end module compile_interface