module cesrv_interface use cesrv_struct interface subroutine cesrv_logic_get (yes, no, prompt, logic_got) implicit none character(*) yes, no, prompt logical logic_got end subroutine subroutine cesrv_next_switch (line, switch_list, switch, err, ix_word) implicit none character(*) line, switch, switch_list(:) logical err integer ix_word end subroutine cesrv_next_switch subroutine check_current (ok, current) import implicit none logical ok real(rp), optional :: current end subroutine subroutine chop_string (long_string, lines, nl) implicit none character(*) long_string character(*) lines(:) integer nl end subroutine subroutine cu_transfer_db_to_cesrv (v1, db_array, to_where) import implicit none type (v1_var_struct) v1 type (db_element_struct) db_array(:) character(*) to_where end subroutine subroutine cesrv_command (line, u, graph, err_flag) import implicit none type (universe_struct), pointer :: u type (graph_struct) :: graph character(*) line logical err_flag end subroutine subroutine do_synrad (walls, u, ring, gen_params, window, auto) import implicit none type (universe_struct), target :: u type (lat_struct) ring type (walls_struct) walls type (synrad_param_struct) gen_params type (crotch_window_struct) window(:) logical, optional :: auto end subroutine subroutine get_tracker_lock_status (h_tracker_locked, v_tracker_locked) import implicit none logical h_tracker_locked, v_tracker_locked, lstat(3) end subroutine subroutine init_init(u, graph, in_line) import implicit none type (universe_struct), pointer :: u type (graph_struct) :: graph character(*) in_line end subroutine subroutine init_lattice (u, read_lat_file, make_groups) import implicit none type (universe_struct) :: u logical read_lat_file integer make_groups end subroutine subroutine match_word2 (string, names, ix, match_name) implicit none character(*) string, names(:) character(*), optional :: match_name integer ix end subroutine subroutine orbmon (u, graph, err_flag) import implicit none type (universe_struct) :: u type (graph_struct) graph logical err_flag end subroutine orbmon subroutine pretzel_set (what, factor, u) import implicit none real(rp) factor integer what type (universe_struct) :: u end subroutine subroutine reinit_lat_pointers (u) import implicit none type (universe_struct) :: u end subroutine subroutine rotate_cbar(ele, tilt, cbar,data_in) import implicit none type (ele_struct) ele real(rp) tilt, cbar(2,2) logical, optional, intent(in) :: data_in end subroutine subroutine run_optimizer (hit_limit) implicit none logical, optional :: hit_limit end subroutine subroutine showit (what, u, file_name) import implicit none character(*) what character(*), optional :: file_name type (universe_struct) :: u end subroutine subroutine set_params(line, do_all_universe, u, graph, err_flag) import implicit none character(*) line logical do_all_universe type (universe_struct) :: u type (graph_struct) graph logical err_flag end subroutine subroutine synrad_init (u) import type (universe_struct) :: u end subroutine synrad_init subroutine opt_vars_set (switch, do_set, fname) implicit none integer switch logical do_set character(50), optional :: fname end subroutine subroutine opt_data_set (switch, u) import implicit none integer switch type (universe_struct) :: u end subroutine subroutine waveit (u, error) import implicit none type (universe_struct) :: u logical error end subroutine subroutine var_bookkeeper(this_var, ring, orb_) import implicit none type (var_struct) this_var type (lat_struct) :: ring type (coord_struct) :: orb_(0:) end subroutine subroutine fletcher_reeves (i_loop, i_cyc, finished, u) import implicit none integer i_loop, i_cyc logical finished type (universe_struct) :: u end subroutine subroutine merit_calc (merit) import implicit none real(rp) merit end subroutine subroutine top10_type (u, lines, nl) import implicit none type (universe_struct), target :: u character(*) lines(:) integer nl end subroutine subroutine steer_ave (steer, ave, rms, n) import implicit none type (v1_var_struct) :: steer real(rp) ave, rms integer n end subroutine subroutine transfer (from, to, factor, u) import implicit none character(*) from, to real(rp) factor type (universe_struct), target :: u end subroutine subroutine twiss_propagate_many (lat, ix_start, ix_end, direction, ix_branch, err_flag) import implicit none type (lat_struct) :: lat integer, intent(in) :: ix_start integer, intent(in) :: ix_end integer, intent(in) :: direction integer, optional :: ix_branch logical, optional :: err_flag end subroutine subroutine transfer_data_from_db_to_cesrv (d1, db_array, factor, to_where) import implicit none type (d1_data_struct) d1 type (db_element_struct) db_array(:) real(rp) factor character(*) to_where end subroutine subroutine wave_orbit(orbit_z, phase_z, tune_z, ring, wave) import implicit none type (d1_data_struct), target :: orbit_z, phase_z, tune_z type (wave_struct) wave type (lat_struct) :: ring end subroutine subroutine wave_phase (phase_z, tune_z, wave) import implicit none type (d1_data_struct), target :: phase_z, tune_z type (wave_struct) wave end subroutine subroutine wave_cbar (phase, tune, wave) import implicit none type (d2_data_struct) phase type (d2_data_struct) tune type (wave_struct) wave end subroutine subroutine wave_region_setup (wave, i_a1, i_b1, n_a, n_b) import implicit none type (wave_struct) wave integer i_a1, i_b1, n_a, n_b end subroutine subroutine wave_anal (y_in, f1, f2, f3, f4, n_f, n_data, coef_in, rms) import implicit none real(rp) y_in(:) real(rp) f1(:), f2(:), f3(:), f4(:), coef_in(:), rms(:) integer n_data, n_f end subroutine subroutine setup_data_plot (plot, u) import implicit none type (p2_plot_struct), target :: plot, other_plot type (universe_struct) u end subroutine subroutine limit_calc (limited) implicit none logical limited end subroutine subroutine read_header (iu, data_or_ref, d2_data, u) import implicit none integer data_or_ref, iu type (d2_data_struct) d2_data type (universe_struct) :: u type (graph_struct) :: graph end subroutine subroutine plotdo (plot_type, graph, hardcopy_flag, u, no_close) import implicit none character(*) plot_type logical hardcopy_flag type (universe_struct), target :: u type (graph_struct) :: graph logical, optional :: no_close end subroutine subroutine ring_calc (u) import implicit none type (universe_struct) :: u end subroutine subroutine plotting_data_calc (p1_plot, phase_z, tune_z) import implicit none type (p1_plot_struct) p1_plot type (d1_data_struct), optional :: phase_z type (d1_data_struct), optional :: tune_z end subroutine subroutine strip_special (line, ele_name, listing) implicit none character(*) ele_name, line logical listing end subroutine subroutine to_top10 (top10, value, top_name, indx, order) import implicit none type (top10s) top10(:) integer indx real(rp) value character(*) top_name, order end subroutine subroutine veto_restore_data (switch, line, do_all_universe, & d1_data, d1_data2, d1_data3) import implicit none type (d1_data_struct) :: d1_data type (d1_data_struct), optional :: d1_data2, d1_data3 character(*) line, switch logical do_all_universe character use_list*200, set_string*3 logical useit_setto end subroutine subroutine veto_restore_var (switch, line, u, gvar) import implicit none type (v1_var_struct) :: gvar character(*) line, switch type (universe_struct) :: u end subroutine subroutine veto_restore_slave (switch, line, u) import implicit none character(*) line, switch type (universe_struct) :: u end subroutine subroutine help_on_tap (what) implicit none character(*) what end subroutine subroutine data_type_useit (d2_data, lines, nl) import implicit none type (d2_data_struct) :: d2_data character(*), optional :: lines(:) integer, optional :: nl end subroutine subroutine x_axis_set (axis_type, x_axis, u) import implicit none type (universe_struct) u type (qp_axis_struct) x_axis character(*) axis_type end subroutine subroutine var_type_useit (gvar, ew_encode, lines, nl) import implicit none type (v1_var_struct) gvar logical ew_encode character(*), optional :: lines(:) integer, optional :: nl end subroutine subroutine set_var_useit (u) import implicit none type (universe_struct) :: u end subroutine subroutine type_bumps implicit none end subroutine subroutine cu_target_calc (var, u, frac) import implicit none type (var_struct) var(:) type (universe_struct) u real(rp) frac end subroutine subroutine clip_data (maxim, p2, use_plot1, use_plot2, use_plot3) import implicit none type (p2_plot_struct) :: p2 logical use_plot1, use_plot2, use_plot3 real(rp) maxim end subroutine subroutine draw_one_graph (how, p1_plot, ixn, iyn, ix_tot, iy_tot) import implicit none character(*) how type (p1_plot_struct) p1_plot integer ix_tot, iy_tot, ixn, iyn end subroutine draw_one_graph subroutine var_plot (how, gvar, u) import implicit none type (v1_var_struct) :: gvar type (universe_struct) u character(*) how end subroutine subroutine read_steerings (u) import implicit none type (universe_struct) :: u end subroutine subroutine load_steerings (u, frac, load_golden) import implicit none type (universe_struct) :: u real(rp) frac logical, optional :: load_golden end subroutine subroutine match_var_name (line, this_var, ix_var, u, err_flag) import implicit none type (var_struct), pointer :: this_var type (universe_struct) u integer ix_var character(*) line logical err_flag end subroutine subroutine match_var_type (line, var1, u, err_flag) import implicit none type (v1_var_struct), pointer :: var1 type (universe_struct) u character(*) line logical err_flag end subroutine subroutine change_var (line, do_all_universe, u) import implicit none character(*) line logical do_all_universe type (universe_struct), target :: u end subroutine subroutine scale_data (maxim, p1_plot1, save, p1_plot2, p1_plot3) import implicit none type (p1_plot_struct) :: p1_plot1 type (p1_plot_struct), optional :: p1_plot2, p1_plot3 real(rp) maxim logical save end subroutine subroutine set_data_useit_opt (data) import implicit none type (data_struct) data(:) end subroutine subroutine set_useit_plot (p1_plot) import implicit none type (p1_plot_struct) p1_plot end subroutine subroutine data_ptr_set (data_ptr, data, n) import implicit none integer n type (data_struct), pointer :: data_ptr(:) type (data_struct), target :: data(n:) end subroutine subroutine register_data (u, data_type, plane, data2, d1_data, data, i, n, n_last) import implicit none integer n, i, data_type, plane, n_last type (d2_data_struct), target :: data2 type (d1_data_struct), target :: d1_data type (data_struct), target :: data(n:) type (universe_struct) u end subroutine subroutine register_var (var_type, gvar, units, var, n1, n2, n_last) import integer :: n1, n2, var_type, units, n_last type (var_struct), target :: var(:) type (v1_var_struct), target :: gvar end subroutine subroutine read_model (num, u, err_flag) import integer num type (universe_struct) :: u logical err_flag end subroutine subroutine dmerit_calc (what) character(*) what end subroutine subroutine init_plotting (open_window, graph, u) import logical open_window type (universe_struct) :: u type (graph_struct) :: graph end subroutine subroutine var_ptr_set (var_ptr, var, n) import integer n type (var_struct), pointer :: var_ptr(:) type (var_struct), target :: var(n:) end subroutine subroutine p1_plot_init (p1_plot, title, factor, y_label, div, places, min, max, zero_at_end, log_type) import implicit none type (p1_plot_struct) p1_plot real(rp) factor, min, max integer div, places character(*) title, y_label logical, optional :: zero_at_end, log_type end subroutine subroutine plot_y_axis_min_max_transfer (axis1, axis2) import implicit none type (qp_axis_struct) axis1, axis2 end subroutine subroutine read_save_set_cu (set_name, set, data_or_ref, u, err_flag) import implicit none type (universe_struct) u character(*) set_name integer set, data_or_ref logical err_flag end subroutine subroutine init_var_info (var1, db_array, ring, ix_attrib, in_db) import implicit none type (v1_var_struct) var1 type (db_element_struct) db_array(:) type (lat_struct) ring integer, optional :: ix_attrib logical, optional :: in_db end subroutine integer function ix_db_ele (grp, k_node, num, var) import implicit none type (var_struct) :: var(:) type (group_info_struct) grp integer num, k_node end function subroutine take_orbit (data_or_ref, u, graph, & get_comment, err_flag, setup_string) import implicit none type (universe_struct) :: u type (graph_struct) graph integer data_or_ref logical err_flag, get_comment character(*), optional :: setup_string end subroutine subroutine read_orbit(data_or_ref, num_in, u, graph, err_flag) import implicit none type (universe_struct) :: u type (graph_struct) graph integer data_or_ref, num_in logical err_flag end subroutine subroutine read_phase (data_or_ref, num_in, u, graph, err_flag, reanal) import implicit none type (universe_struct) :: u type (graph_struct) graph integer data_or_ref, num_in logical err_flag logical reanal end subroutine subroutine read_ac_eta (data_or_ref, num_in, u, graph, err_flag, reanal) import implicit none type (universe_struct) :: u type (graph_struct) graph integer data_or_ref, num_in logical err_flag logical reanal end subroutine subroutine read_beta (data_or_ref, num_in, u, graph, err_flag) import implicit none type (universe_struct) :: u type (graph_struct) graph integer data_or_ref, num_in logical err_flag end subroutine subroutine read_tbt (data_or_ref, num_in, u, graph, err_flag) import implicit none type (universe_struct) :: u type (graph_struct) graph integer data_or_ref, num_in logical err_flag end subroutine subroutine read_eta (data_or_ref, num_in, u, graph, err_flag, reanal) import implicit none type (universe_struct) :: u type (graph_struct) graph integer data_or_ref, num_in logical err_flag logical reanal end subroutine subroutine read_fake_data (data_or_ref, filename, u, graph, err_flag) import implicit none type (universe_struct), target :: u type (graph_struct) graph integer data_or_ref character(50) filename logical err_flag end subroutine subroutine do_var_transfer (var1, factor, from_what, u, typeout) import implicit none type (v1_var_struct) :: var1 type (universe_struct) :: u character(*) from_what real(rp) factor logical typeout end subroutine function on_off (logic) logical logic character(4) on_off end function function on_off_int (logic) logical logic integer on_off_int end function subroutine spline_beta_calc (plot, phase_plot, quad_twiss_z) import type (p1_plot_struct) :: plot, phase_plot type (twiss_struct) quad_twiss_z(0:120) end subroutine subroutine type_bad_data_line (iunit, what, filename) integer iunit character(*) what, filename end subroutine subroutine load_quads (u, frac) import type (universe_struct), target :: u real(rp) frac end subroutine subroutine load_sex (u, frac) import type (universe_struct), target :: u real(rp) frac end subroutine subroutine load_skew_sex (u, frac) import type (universe_struct), target :: u real(rp) frac end subroutine subroutine set_lattice (lattice, u) import type (universe_struct), target :: u character(40) lattice end subroutine subroutine get_cesrv_command (str_out, cmd_line, cmd_logic, init) import character(*) str_out character(*), optional :: cmd_line logical, optional :: cmd_logic logical, optional :: init end subroutine subroutine get_twiss (ix_ele, ring, twiss_x, twiss_y) import type (lat_struct) ring integer ix_ele type (twiss_struct) :: twiss_x, twiss_y end subroutine subroutine saved_and_lim_calc (var) import type (var_struct) var(:) end subroutine subroutine init_universe (u) import type (universe_struct), target :: u end subroutine subroutine take_phase (data_or_ref, u, graph, err_flag, auto_meas, comment) import type (universe_struct), target :: u type (graph_struct) graph integer data_or_ref logical err_flag, auto_meas character(*), optional :: comment end subroutine subroutine take_ac_eta (data_or_ref, u, graph, err_flag, auto_meas, comment) import type (universe_struct), target :: u type (graph_struct) graph integer data_or_ref logical err_flag, auto_meas character(*), optional :: comment end subroutine subroutine take_tbt (n_turn, data_or_ref, u, graph, err_flag) import type (universe_struct), target :: u type (graph_struct) graph integer data_or_ref, n_turn logical err_flag, auto_meas end subroutine subroutine take_eta (data_or_ref, u, graph, err_flag) import type (universe_struct), target :: u type (graph_struct) graph integer data_or_ref logical err_flag, auto_meas end subroutine subroutine raw_plot (raw1, raw2) import type (raw_struct) raw1 type (raw_struct), optional :: raw2 end subroutine subroutine special_procedure (u, graph, line_in) import type (universe_struct), target :: u type (graph_struct) graph character(*) line_in end subroutine subroutine single_corrector_calc (steer_kick, top_steer, plane, u) import type (v1_var_struct) steer_kick type (universe_struct), target :: u type (top10s) :: top_steer(:) character(*) plane end subroutine subroutine type_energy_shift (u, lines, nl) import type (universe_struct) u character(*) lines(:) integer nl end subroutine subroutine change_cesr_rf_freq (i_target, rf_step) integer i_target integer, optional :: rf_step end subroutine subroutine baseline_set (what_base, action, plot_a, plot_b, do_set) import type (p2_plot_struct) plot_a type (p2_plot_struct), optional :: plot_b integer what_base, action logical, optional :: do_set end subroutine subroutine draw_data_plots (plot, u, only_xy) import type (p2_plot_struct), target :: plot type (universe_struct) u integer, optional :: only_xy end subroutine subroutine set_plot (plot, data, do_set) import type (p2_plot_struct), target :: plot type (d2_data_struct) data logical, optional :: do_set end subroutine subroutine set_plot1 (plot1, data1) import type (p1_plot_struct) plot1 type (d1_data_struct) data1 end subroutine subroutine set_plot2 (plot, ix, u) import type (p2_plot_struct) plot type (universe_struct) u integer ix end subroutine function plot_type_has (datum, plot_type) implicit none logical plot_type_has integer plot_type, datum end function subroutine data_plot_init (data, data1, data2, data3, gang_scale) import implicit none type (d2_data_struct) data type (d1_data_struct) data1 type (d1_data_struct), optional :: data2 type (d1_data_struct), optional :: data3 logical, optional :: gang_scale end subroutine subroutine plot_data_set (plot, action, doit) import implicit none type (p2_plot_struct) plot integer action logical, optional :: doit end subroutine subroutine calibrate_steering (ix_var, how, cu_in, & u, graph, err_flag) import implicit none type (universe_struct), target :: u type (graph_struct) graph character(*) how integer cu_in(2), ix_var logical err_flag end subroutine subroutine calibrate_quad (ix_var, how, cu_in, u, graph, err_flag) import implicit none type (universe_struct), target :: u type (graph_struct) graph character(*) how integer cu_in(2), ix_var logical err_flag end subroutine subroutine calibrate_bpm (ix_bpm, ix_var, how, cu_in, u, graph, err_flag, ix_loop, finished) import implicit none type (universe_struct), target :: u type (graph_struct) graph character(*) how integer cu_in(2), ix_var, ix_bpm, ix_loop logical err_flag logical, optional :: finished end subroutine subroutine calibrate_skew_quad (ix_var, how, cu_in, u, graph, err_flag) import implicit none type (universe_struct), target :: u type (graph_struct) graph character(*) how integer cu_in(2), ix_var logical err_flag end subroutine subroutine close_bump (ing_name, ix_ing, cu_delta_in, & u, graph, err_flag) import implicit none character(12) ing_name type (universe_struct) u type (graph_struct) graph type (group_info_struct) grp integer cu_delta_in integer ix_ing logical err_flag end subroutine subroutine set_and_meas (node_name, node_num, cu_set, meas_type, & ix_var, n_var, data_or_ref, u, graph, err_flag, comment_in) import implicit none type (universe_struct) u type (graph_struct) graph integer node_num integer data_or_ref, meas_type integer cu_set, ix_var(:), n_var character(*) node_name character(*), optional :: comment_in logical err_flag end subroutine subroutine zero_kicks_in_ring (ring) import implicit none type (lat_struct) ring end subroutine subroutine show_tune (u, lines, nl) import implicit none type (universe_struct) u character(*) lines(:) integer nl end subroutine subroutine get_input_string (query_str, string, do_upcase) implicit none character(*) query_str, string logical, optional :: do_upcase end subroutine subroutine marquardt (i_loop, a_lambda, finished, u, at_limit) import implicit none type (universe_struct), target :: u real(rp) a_lambda logical finished, at_limit integer i_loop end subroutine subroutine mrq_func (x, a, y_fit, dy_da) import implicit none real(rp), intent(in) :: x(:) real(rp), intent(in) :: a(:) real(rp), intent(out) :: y_fit(:) real(rp), intent(out) :: dy_da(:, :) end subroutine subroutine locate_element (ring, str, loc, err_flag) import implicit none type (lat_struct) ring integer loc character(*) :: str logical err_flag end subroutine subroutine get_gain(gain) import implicit none type (but_value_struct) gain(0:120) end subroutine subroutine get_tilt(tilt) import implicit none real(rp) tilt(0:120) end subroutine subroutine xbsm_calc (u, line) import implicit none character(*) line type (universe_struct) :: u end subroutine subroutine write_model (num, u, comment) import implicit none integer num character(*) comment type (universe_struct) :: u end subroutine subroutine ac_eta_relative_xy_calc(ele, rel_amp_cos, rel_amp_sin) import implicit none type (ele_struct) ele real(rp) rel_amp_cos, rel_amp_sin, v(6,6) end subroutine end interface end module