]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/paramodulation/saturate_main.ml
entry point of the stand-alone saturate
[helm.git] / helm / ocaml / paramodulation / saturate_main.ml
1 let configuration_file = ref "../../matita/matita.conf.xml";;
2
3 let get_from_user ~(dbd:Mysql.dbd) =
4   let rec get () =
5     match read_line () with
6     | "" -> []
7     | t -> t::(get ())
8   in
9   let term_string = String.concat "\n" (get ()) in
10   let env, metasenv, term, ugraph =
11     List.nth (Disambiguate.Trivial.disambiguate_string dbd term_string) 0
12   in
13   term, metasenv, ugraph
14 ;;
15
16 let _ =
17   let module S = Saturation in
18   let set_ratio v = S.weight_age_ratio := (v+1); S.weight_age_counter := (v+1)
19   and set_sel v = S.symbols_ratio := v; S.symbols_counter := v;
20   and set_conf f = configuration_file := f
21   and set_lpo () = Utils.compare_terms := Utils.lpo
22   and set_kbo () = Utils.compare_terms := Utils.nonrec_kbo
23   and set_fullred b = S.use_fullred := b
24   and set_time_limit v = S.time_limit := float_of_int v
25   in
26   Arg.parse [
27     "-f", Arg.Bool set_fullred,
28     "Enable/disable full-reduction strategy (default: enabled)";
29     
30     "-r", Arg.Int set_ratio, "Weight-Age equality selection ratio (default: 3)";
31
32     "-s", Arg.Int set_sel,
33     "symbols-based selection ratio (relative to the weight ratio, default: 2)";
34
35     "-c", Arg.String set_conf, "Configuration file (for the db connection)";
36
37     "-lpo", Arg.Unit set_lpo, "Use lpo term ordering";
38
39     "-kbo", Arg.Unit set_kbo, "Use (non-recursive) kbo term ordering (default)";
40
41     "-l", Arg.Int set_time_limit, "Time limit (in seconds)";
42   ] (fun a -> ()) "Usage:"
43 in
44 Helm_registry.load_from !configuration_file;
45 let dbd = Mysql.quick_connect
46   ~host:(Helm_registry.get "db.host")
47   ~user:(Helm_registry.get "db.user")
48   ~database:(Helm_registry.get "db.database")
49   ()
50 in
51 let term, metasenv, ugraph = get_from_user ~dbd in
52 Saturation.main dbd term metasenv ugraph;;