]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/paramodulation/discrimination_tree.ml
- better exception handling
[helm.git] / helm / ocaml / paramodulation / discrimination_tree.ml
1 type path_string_elem = Cic.term;;
2 type path_string = path_string_elem list;;
3
4
5 (* needed by the retrieve_* functions, to know the arities of the "functions" *)
6 let arities = Hashtbl.create 11;;
7
8
9 let rec path_string_of_term = function
10   | Cic.Meta _ -> [Cic.Implicit None]
11   | Cic.Appl ((hd::tl) as l) ->
12       if not (Hashtbl.mem arities hd) then
13         Hashtbl.add arities hd (List.length tl);
14       List.concat (List.map path_string_of_term l)
15   | term -> [term]
16 ;;
17
18
19 let string_of_path_string ps =
20   String.concat "." (List.map CicPp.ppterm ps)
21 ;;
22
23
24 module OrderedPathStringElement = struct
25   type t = path_string_elem
26
27   let compare = Pervasives.compare
28 end
29
30 module PSMap = Map.Make(OrderedPathStringElement);;
31
32
33 module OrderedPosEquality = struct
34   type t = Utils.pos * Inference.equality
35
36   let compare = Pervasives.compare
37 end
38
39 module PosEqSet = Set.Make(OrderedPosEquality);;
40
41
42 module DiscriminationTree = Trie.Make(PSMap);;
43
44   
45 let string_of_discrimination_tree tree =
46   let rec to_string level = function
47     | DiscriminationTree.Node (value, map) ->
48         let s =
49           match value with
50           | Some v ->
51               (String.make (2 * level) ' ') ^
52                 "{" ^ (String.concat "; "
53                          (List.map
54                             (fun (p, e) ->
55                                "(" ^ (Utils.string_of_pos p) ^ ", " ^ 
56                                  (Inference.string_of_equality e) ^ ")")
57                             (PosEqSet.elements v))) ^ "}"
58           | None -> "" 
59         in
60         let rest =
61           String.concat "\n"
62             (PSMap.fold
63                (fun k v s ->
64                   let ks = CicPp.ppterm k in
65                   let rs = to_string (level+1) v in
66                   ((String.make (2 * level) ' ') ^ ks ^ "\n" ^ rs)::s)
67                map [])
68         in
69         s ^ rest
70   in
71   to_string 0 tree
72 ;;
73
74
75 let index tree equality =
76   let _, _, (_, l, r, ordering), _, _ = equality in
77   let psl = path_string_of_term l
78   and psr = path_string_of_term r in
79   let index pos tree ps =
80     let ps_set =
81       try DiscriminationTree.find ps tree with Not_found -> PosEqSet.empty in
82     let tree =
83       DiscriminationTree.add ps (PosEqSet.add (pos, equality) ps_set) tree in
84     tree
85   in
86   match ordering with
87   | Utils.Gt -> index Utils.Left tree psl
88   | Utils.Lt -> index Utils.Right tree psr
89   | _ ->
90       let tree = index Utils.Left tree psl in
91       index Utils.Right tree psr
92 ;;
93
94
95 let remove_index tree equality =
96   let _, _, (_, l, r, ordering), _, _ = equality in
97   let psl = path_string_of_term l
98   and psr = path_string_of_term r in
99   let remove_index pos tree ps =
100     try
101       let ps_set =
102         PosEqSet.remove (pos, equality) (DiscriminationTree.find ps tree) in
103       if PosEqSet.is_empty ps_set then
104         DiscriminationTree.remove ps tree
105       else
106         DiscriminationTree.add ps ps_set tree
107     with Not_found ->
108       tree
109   in
110   match ordering with
111   | Utils.Gt -> remove_index Utils.Left tree psl
112   | Utils.Lt -> remove_index Utils.Right tree psr
113   | _ ->
114       let tree = remove_index Utils.Left tree psl in
115       remove_index Utils.Right tree psr
116 ;;
117
118
119 let in_index tree equality =
120   let _, _, (_, l, r, ordering), _, _ = equality in
121   let psl = path_string_of_term l
122   and psr = path_string_of_term r in
123   let meta_convertibility = Inference.meta_convertibility_eq equality in
124   let ok ps =
125     try
126       let set = DiscriminationTree.find ps tree in
127       PosEqSet.exists (fun (p, e) -> meta_convertibility e) set
128     with Not_found ->
129       false
130   in
131   (ok psl) || (ok psr)
132 ;;
133
134
135 let head_of_term = function
136   | Cic.Appl (hd::tl) -> hd
137 (*   | Cic.Meta _ -> Cic.Implicit None *)
138   | term -> term
139 ;;
140
141
142 let rec subterm_at_pos pos term =
143   match pos with
144   | [] -> term
145   | index::pos ->
146       match term with
147       | Cic.Appl l ->
148           (try subterm_at_pos pos (List.nth l index)
149            with Failure _ -> raise Not_found)
150       | _ -> raise Not_found
151 ;;
152
153
154 let rec after_t pos term =
155   let pos' =
156     match pos with
157     | [] -> raise Not_found
158     | pos -> List.fold_right (fun i r -> if r = [] then [i+1] else i::r) pos []
159   in
160   try
161     let t = subterm_at_pos pos' term in pos'
162   with Not_found ->
163     let pos, _ =
164       List.fold_right
165         (fun i (r, b) -> if b then (i::r, true) else (r, true)) pos ([], false)
166     in
167     after_t pos term
168 ;;
169
170
171 let next_t pos term =
172   let t = subterm_at_pos pos term in
173   try
174     let _ = subterm_at_pos [1] t in
175     pos @ [1]
176   with Not_found ->
177     match pos with
178     | [] -> [1]
179     | pos -> after_t pos term
180 ;;     
181
182
183 let retrieve_generalizations tree term =
184   let rec retrieve tree term pos =
185     match tree with
186     | DiscriminationTree.Node (Some s, _) when pos = [] -> s
187     | DiscriminationTree.Node (_, map) ->
188         let res =
189           try
190             let hd_term = head_of_term (subterm_at_pos pos term) in
191             let n = PSMap.find hd_term map in
192             match n with
193             | DiscriminationTree.Node (Some s, _) -> s
194             | DiscriminationTree.Node (None, _) ->
195                 let newpos = try next_t pos term with Not_found -> [] in
196                 retrieve n term newpos
197           with Not_found ->
198             PosEqSet.empty
199         in
200         try
201           let n = PSMap.find (Cic.Implicit None) map in
202           let newpos = try after_t pos term with Not_found -> [-1] in
203           if newpos = [-1] then
204             match n with
205             | DiscriminationTree.Node (Some s, _) -> PosEqSet.union s res
206             | _ -> res
207           else
208             PosEqSet.union res (retrieve n term newpos)
209         with Not_found ->
210           res
211   in
212   retrieve tree term []
213 ;;
214
215
216 let jump_list = function
217   | DiscriminationTree.Node (value, map) ->
218       let rec get n tree =
219         match tree with
220         | DiscriminationTree.Node (v, m) ->
221             if n = 0 then
222               [tree]
223             else
224               PSMap.fold
225                 (fun k v res ->
226                    let a = try Hashtbl.find arities k with Not_found -> 0 in
227                    (get (n-1 + a) v) @ res) m []
228       in
229       PSMap.fold
230         (fun k v res ->
231            let arity = try Hashtbl.find arities k with Not_found -> 0 in
232            (get arity v) @ res)
233         map []
234 ;;
235
236
237 let retrieve_unifiables tree term =
238   let rec retrieve tree term pos =
239     match tree with
240     | DiscriminationTree.Node (Some s, _) when pos = [] -> s
241     | DiscriminationTree.Node (_, map) ->
242         let subterm =
243           try Some (subterm_at_pos pos term) with Not_found -> None
244         in
245         match subterm with
246         | None -> PosEqSet.empty
247         | Some (Cic.Meta _) ->
248             let newpos = try next_t pos term with Not_found -> [] in
249             let jl = jump_list tree in
250             List.fold_left
251               (fun r s -> PosEqSet.union r s)
252               PosEqSet.empty
253               (List.map (fun t -> retrieve t term newpos) jl)
254         | Some subterm ->
255             let res = 
256               try
257                 let hd_term = head_of_term subterm in
258                 let n = PSMap.find hd_term map in
259                 match n with
260                 | DiscriminationTree.Node (Some s, _) -> s
261                 | DiscriminationTree.Node (None, _) ->
262                     retrieve n term (next_t pos term)
263               with Not_found ->
264                 PosEqSet.empty
265             in
266             try
267               let n = PSMap.find (Cic.Implicit None) map in
268               let newpos = try after_t pos term with Not_found -> [-1] in
269               if newpos = [-1] then
270                 match n with
271                 | DiscriminationTree.Node (Some s, _) -> PosEqSet.union s res
272                 | _ -> res
273               else
274                 PosEqSet.union res (retrieve n term newpos)
275             with Not_found ->
276               res
277   in
278   retrieve tree term []
279 ;;