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