]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/paramodulation/inference.mli
some optimizations...
[helm.git] / helm / ocaml / paramodulation / inference.mli
1 type equality =
2     Cic.term *           (* proof *)
3     (Cic.term *          (* type *)
4      Cic.term *          (* left side *)
5      Cic.term *          (* right side *)
6      Utils.comparison) * (* ordering *)  
7     Cic.metasenv *       (* environment for metas *)
8     Cic.term list        (* arguments *)
9 ;;
10
11 type environment = Cic.metasenv * Cic.context * CicUniv.universe_graph;;
12
13
14 exception MatchingFailure
15
16 val matching:
17   Cic.metasenv -> Cic.context -> Cic.term -> Cic.term ->
18   CicUniv.universe_graph ->
19   Cic.substitution * Cic.metasenv * CicUniv.universe_graph
20
21
22 (**
23    Performs the beta expansion of the term "where" w.r.t. "what",
24    i.e. returns the list of all the terms t s.t. "(t what) = where".
25 *)
26 val beta_expand:
27   ?metas_ok:bool -> ?match_only:bool -> Cic.term -> Cic.term -> Cic.term ->
28   Cic.context -> Cic.metasenv -> CicUniv.universe_graph ->
29   (Cic.term * Cic.substitution * Cic.metasenv * CicUniv.universe_graph) list
30
31     
32 (**
33    scans the context to find all Declarations "left = right"; returns a
34    list of tuples (proof, (type, left, right), newmetas). Uses
35    PrimitiveTactics.new_metasenv_for_apply to replace bound variables with
36    fresh metas...
37 *)
38 val find_equalities:
39   ?eq_uri:UriManager.uri -> Cic.context -> ProofEngineTypes.proof ->
40   equality list * int
41
42
43 exception TermIsNotAnEquality;;
44
45 (**
46    raises TermIsNotAnEquality if term is not an equation.
47    The first Cic.term is a proof of the equation
48 *)
49 val equality_of_term: ?eq_uri:UriManager.uri -> Cic.term -> Cic.term ->
50   equality
51
52 (**
53    superposition_left env target source
54    returns a list of new clauses inferred with a left superposition step
55    the negative equation "target" and the positive equation "source"
56 *)
57 val superposition_left: environment -> equality -> equality -> equality list
58
59 (**
60    superposition_right newmeta env target source
61    returns a list of new clauses inferred with a right superposition step
62    the positive equations "target" and "source"
63    "newmeta" is the first free meta index, i.e. the first number above the
64    highest meta index: its updated value is also returned
65 *)
66 val superposition_right:
67   int -> environment -> equality -> equality -> int * equality list
68
69 val demodulation: int -> environment -> equality -> equality -> int * equality
70
71 val meta_convertibility_eq: equality -> equality -> bool
72
73 val is_identity: environment -> equality -> bool
74
75 val string_of_equality: ?env:environment -> equality -> string
76
77 val subsumption: environment -> equality -> equality -> bool
78
79 val metas_of_term: Cic.term -> int list
80
81 val fix_metas: int -> equality -> int * equality
82
83 val extract_differing_subterms:
84   Cic.term -> Cic.term -> (Cic.term * Cic.term) option