]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/cic/discrimination_tree.ml
moved term indexing (in both discrimination and path tree forms) from paramodulation...
[helm.git] / helm / ocaml / cic / discrimination_tree.ml
1 (* Copyright (C) 2005, HELM Team.
2  * 
3  * This file is part of HELM, an Hypertextual, Electronic
4  * Library of Mathematics, developed at the Computer Science
5  * Department, University of Bologna, Italy.
6  * 
7  * HELM is free software; you can redistribute it and/or
8  * modify it under the terms of the GNU General Public License
9  * as published by the Free Software Foundation; either version 2
10  * of the License, or (at your option) any later version.
11  * 
12  * HELM is distributed in the hope that it will be useful,
13  * but WITHOUT ANY WARRANTY; without even the implied warranty of
14  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15  * GNU General Public License for more details.
16  *
17  * You should have received a copy of the GNU General Public License
18  * along with HELM; if not, write to the Free Software
19  * Foundation, Inc., 59 Temple Place - Suite 330, Boston,
20  * MA  02111-1307, USA.
21  * 
22  * For details, see the HELM World-Wide-Web page,
23  * http://cs.unibo.it/helm/.
24  *)
25
26 module DiscriminationTreeIndexing =  
27   functor (A:Set.S) -> 
28     struct
29
30       type path_string_elem = Cic.term;;
31       type path_string = path_string_elem list;;
32
33
34       (* needed by the retrieve_* functions, to know the arities of the "functions" *)
35       
36       let arities = Hashtbl.create 11;;
37
38
39       let rec path_string_of_term = function
40         | Cic.Meta _ -> [Cic.Implicit None]
41         | Cic.Appl ((hd::tl) as l) ->
42             if not (Hashtbl.mem arities hd) then
43               Hashtbl.add arities hd (List.length tl);
44             List.concat (List.map path_string_of_term l)
45         | term -> [term]
46       ;;
47
48
49       module OrderedPathStringElement = struct
50         type t = path_string_elem
51
52         let compare = Pervasives.compare
53       end
54
55       module PSMap = Map.Make(OrderedPathStringElement);;
56
57       type key = PSMap.key
58
59       module DiscriminationTree = Trie.Make(PSMap);;
60
61       type t = A.t DiscriminationTree.t
62       let empty = DiscriminationTree.empty
63
64 (*
65       module OrderedPosEquality = struct
66         type t = Utils.pos * Inference.equality
67         let compare = Pervasives.compare
68       end
69
70       module PosEqSet = Set.Make(OrderedPosEquality);;
71
72       let string_of_discrimination_tree tree =
73         let rec to_string level = function
74           | DiscriminationTree.Node (value, map) ->
75               let s =
76                 match value with
77                   | Some v ->
78                       (String.make (2 * level) ' ') ^
79                         "{" ^ (String.concat "; "
80                                  (List.map
81                                     (fun (p, e) ->
82                                        "(" ^ (Utils.string_of_pos p) ^ ", " ^ 
83                                          (Inference.string_of_equality e) ^ ")")
84                                     (PosEqSet.elements v))) ^ "}"
85                   | None -> "" 
86               in
87               let rest =
88                 String.concat "\n"
89                   (PSMap.fold
90                      (fun k v s ->
91                         let ks = CicPp.ppterm k in
92                         let rs = to_string (level+1) v in
93                           ((String.make (2 * level) ' ') ^ ks ^ "\n" ^ rs)::s)
94                      map [])
95               in
96                 s ^ rest
97         in
98           to_string 0 tree
99       ;;
100 *)
101
102       let index tree term info =
103         let ps = path_string_of_term term in
104         let ps_set =
105           try DiscriminationTree.find ps tree 
106           with Not_found -> A.empty in
107         let tree =
108           DiscriminationTree.add ps (A.add info ps_set) tree in
109         tree
110
111 (*
112       let index tree equality =
113         let _, _, (_, l, r, ordering), _, _ = equality in
114         let psl = path_string_of_term l
115         and psr = path_string_of_term r in
116         let index pos tree ps =
117           let ps_set =
118             try DiscriminationTree.find ps tree with Not_found -> PosEqSet.empty in
119           let tree =
120             DiscriminationTree.add ps (PosEqSet.add (pos, equality) ps_set) tree in
121             tree
122         in
123           match ordering with
124             | Utils.Gt -> index Utils.Left tree psl
125             | Utils.Lt -> index Utils.Right tree psr
126             | _ ->
127                 let tree = index Utils.Left tree psl in
128                   index Utils.Right tree psr
129       ;;
130 *)
131
132       let remove_index tree term info =
133         let ps = path_string_of_term term in
134         try
135           let ps_set =
136             A.remove info (DiscriminationTree.find ps tree) in
137             if A.is_empty ps_set then
138               DiscriminationTree.remove ps tree
139             else
140               DiscriminationTree.add ps ps_set tree
141         with Not_found ->
142           tree
143
144 (*
145 let remove_index tree equality =
146   let _, _, (_, l, r, ordering), _, _ = equality in
147   let psl = path_string_of_term l
148   and psr = path_string_of_term r in
149   let remove_index pos tree ps =
150     try
151       let ps_set =
152         PosEqSet.remove (pos, equality) (DiscriminationTree.find ps tree) in
153       if PosEqSet.is_empty ps_set then
154         DiscriminationTree.remove ps tree
155       else
156         DiscriminationTree.add ps ps_set tree
157     with Not_found ->
158       tree
159   in
160   match ordering with
161   | Utils.Gt -> remove_index Utils.Left tree psl
162   | Utils.Lt -> remove_index Utils.Right tree psr
163   | _ ->
164       let tree = remove_index Utils.Left tree psl in
165       remove_index Utils.Right tree psr
166 ;;
167 *)
168
169
170       let in_index tree term test =
171         let ps = path_string_of_term term in
172         try
173           let ps_set = DiscriminationTree.find ps tree in
174           A.exists test ps_set
175         with Not_found ->
176           false
177
178 (*
179       let in_index tree equality =
180         let _, _, (_, l, r, ordering), _, _ = equality in
181         let psl = path_string_of_term l
182         and psr = path_string_of_term r in
183         let meta_convertibility = Inference.meta_convertibility_eq equality in
184         let ok ps =
185           try
186             let set = DiscriminationTree.find ps tree in
187               PosEqSet.exists (fun (p, e) -> meta_convertibility e) set
188           with Not_found ->
189             false
190         in
191           (ok psl) || (ok psr)
192 ;;
193 *)
194
195
196       let head_of_term = function
197         | Cic.Appl (hd::tl) -> hd
198         | term -> term
199       ;;
200
201
202       let rec subterm_at_pos pos term =
203         match pos with
204           | [] -> term
205           | index::pos ->
206               match term with
207                 | Cic.Appl l ->
208                     (try subterm_at_pos pos (List.nth l index)
209                      with Failure _ -> raise Not_found)
210                 | _ -> raise Not_found
211       ;;
212
213
214       let rec after_t pos term =
215         let pos' =
216           match pos with
217             | [] -> raise Not_found
218             | pos -> List.fold_right (fun i r -> if r = [] then [i+1] else i::r) pos []
219         in
220           try
221             let t = subterm_at_pos pos' term in pos'
222           with Not_found ->
223             let pos, _ =
224               List.fold_right
225                 (fun i (r, b) -> if b then (i::r, true) else (r, true)) pos ([], false)
226             in
227               after_t pos term
228       ;;
229
230
231       let next_t pos term =
232         let t = subterm_at_pos pos term in
233           try
234             let _ = subterm_at_pos [1] t in
235               pos @ [1]
236           with Not_found ->
237             match pos with
238               | [] -> [1]
239               | pos -> after_t pos term
240       ;;     
241
242
243       let retrieve_generalizations tree term =
244         let rec retrieve tree term pos =
245           match tree with
246             | DiscriminationTree.Node (Some s, _) when pos = [] -> s
247             | DiscriminationTree.Node (_, map) ->
248                 let res =
249                   try
250                     let hd_term = head_of_term (subterm_at_pos pos term) in
251                     let n = PSMap.find hd_term map in
252                       match n with
253                         | DiscriminationTree.Node (Some s, _) -> s
254                         | DiscriminationTree.Node (None, _) ->
255                             let newpos = try next_t pos term with Not_found -> [] in
256                               retrieve n term newpos
257                   with Not_found ->
258                     A.empty
259                 in
260                   try
261                     let n = PSMap.find (Cic.Implicit None) map in
262                     let newpos = try after_t pos term with Not_found -> [-1] in
263                       if newpos = [-1] then
264                         match n with
265                           | DiscriminationTree.Node (Some s, _) -> A.union s res
266                           | _ -> res
267                       else
268                         A.union res (retrieve n term newpos)
269                   with Not_found ->
270                     res
271         in
272           retrieve tree term []
273       ;;
274
275
276       let jump_list = function
277         | DiscriminationTree.Node (value, map) ->
278             let rec get n tree =
279               match tree with
280                 | DiscriminationTree.Node (v, m) ->
281                     if n = 0 then
282                       [tree]
283                     else
284                       PSMap.fold
285                         (fun k v res ->
286                            let a = try Hashtbl.find arities k with Not_found -> 0 in
287                              (get (n-1 + a) v) @ res) m []
288             in
289               PSMap.fold
290                 (fun k v res ->
291                    let arity = try Hashtbl.find arities k with Not_found -> 0 in
292                      (get arity v) @ res)
293                 map []
294       ;;
295
296
297       let retrieve_unifiables tree term =
298         let rec retrieve tree term pos =
299           match tree with
300             | DiscriminationTree.Node (Some s, _) when pos = [] -> s
301             | DiscriminationTree.Node (_, map) ->
302                 let subterm =
303                   try Some (subterm_at_pos pos term) with Not_found -> None
304                 in
305                   match subterm with
306                     | None -> A.empty
307                     | Some (Cic.Meta _) ->
308                         let newpos = try next_t pos term with Not_found -> [] in
309                         let jl = jump_list tree in
310                           List.fold_left
311                             (fun r s -> A.union r s)
312                             A.empty
313                             (List.map (fun t -> retrieve t term newpos) jl)
314                     | Some subterm ->
315                         let res = 
316                           try
317                             let hd_term = head_of_term subterm in
318                             let n = PSMap.find hd_term map in
319                               match n with
320                                 | DiscriminationTree.Node (Some s, _) -> s
321                                 | DiscriminationTree.Node (None, _) ->
322                                     retrieve n term (next_t pos term)
323                           with Not_found ->
324                             A.empty
325                         in
326                           try
327                             let n = PSMap.find (Cic.Implicit None) map in
328                             let newpos = try after_t pos term with Not_found -> [-1] in
329                               if newpos = [-1] then
330                                 match n with
331                                   | DiscriminationTree.Node (Some s, _) -> A.union s res
332                                   | _ -> res
333                               else
334                                 A.union res (retrieve n term newpos)
335                           with Not_found ->
336                             res
337         in
338           retrieve tree term []
339     end
340 ;;
341