]> matita.cs.unibo.it Git - helm.git/blob - helm/ocaml/cic/discrimination_tree.ml
added discrimination tree
[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       type elt = A.elt
63       let empty = DiscriminationTree.empty
64
65 (*
66       module OrderedPosEquality = struct
67         type t = Utils.pos * Inference.equality
68         let compare = Pervasives.compare
69       end
70
71       module PosEqSet = Set.Make(OrderedPosEquality);;
72
73       let string_of_discrimination_tree tree =
74         let rec to_string level = function
75           | DiscriminationTree.Node (value, map) ->
76               let s =
77                 match value with
78                   | Some v ->
79                       (String.make (2 * level) ' ') ^
80                         "{" ^ (String.concat "; "
81                                  (List.map
82                                     (fun (p, e) ->
83                                        "(" ^ (Utils.string_of_pos p) ^ ", " ^ 
84                                          (Inference.string_of_equality e) ^ ")")
85                                     (PosEqSet.elements v))) ^ "}"
86                   | None -> "" 
87               in
88               let rest =
89                 String.concat "\n"
90                   (PSMap.fold
91                      (fun k v s ->
92                         let ks = CicPp.ppterm k in
93                         let rs = to_string (level+1) v in
94                           ((String.make (2 * level) ' ') ^ ks ^ "\n" ^ rs)::s)
95                      map [])
96               in
97                 s ^ rest
98         in
99           to_string 0 tree
100       ;;
101 *)
102
103       let index tree term info =
104         let ps = path_string_of_term term in
105         let ps_set =
106           try DiscriminationTree.find ps tree 
107           with Not_found -> A.empty in
108         let tree =
109           DiscriminationTree.add ps (A.add info ps_set) tree in
110         tree
111
112 (*
113       let index tree equality =
114         let _, _, (_, l, r, ordering), _, _ = equality in
115         let psl = path_string_of_term l
116         and psr = path_string_of_term r in
117         let index pos tree ps =
118           let ps_set =
119             try DiscriminationTree.find ps tree with Not_found -> PosEqSet.empty in
120           let tree =
121             DiscriminationTree.add ps (PosEqSet.add (pos, equality) ps_set) tree in
122             tree
123         in
124           match ordering with
125             | Utils.Gt -> index Utils.Left tree psl
126             | Utils.Lt -> index Utils.Right tree psr
127             | _ ->
128                 let tree = index Utils.Left tree psl in
129                   index Utils.Right tree psr
130       ;;
131 *)
132
133       let remove_index tree term info =
134         let ps = path_string_of_term term in
135         try
136           let ps_set =
137             A.remove info (DiscriminationTree.find ps tree) in
138             if A.is_empty ps_set then
139               DiscriminationTree.remove ps tree
140             else
141               DiscriminationTree.add ps ps_set tree
142         with Not_found ->
143           tree
144
145 (*
146 let remove_index tree equality =
147   let _, _, (_, l, r, ordering), _, _ = equality in
148   let psl = path_string_of_term l
149   and psr = path_string_of_term r in
150   let remove_index pos tree ps =
151     try
152       let ps_set =
153         PosEqSet.remove (pos, equality) (DiscriminationTree.find ps tree) in
154       if PosEqSet.is_empty ps_set then
155         DiscriminationTree.remove ps tree
156       else
157         DiscriminationTree.add ps ps_set tree
158     with Not_found ->
159       tree
160   in
161   match ordering with
162   | Utils.Gt -> remove_index Utils.Left tree psl
163   | Utils.Lt -> remove_index Utils.Right tree psr
164   | _ ->
165       let tree = remove_index Utils.Left tree psl in
166       remove_index Utils.Right tree psr
167 ;;
168 *)
169
170
171       let in_index tree term test =
172         let ps = path_string_of_term term in
173         try
174           let ps_set = DiscriminationTree.find ps tree in
175           A.exists test ps_set
176         with Not_found ->
177           false
178
179 (*
180       let in_index tree equality =
181         let _, _, (_, l, r, ordering), _, _ = equality in
182         let psl = path_string_of_term l
183         and psr = path_string_of_term r in
184         let meta_convertibility = Inference.meta_convertibility_eq equality in
185         let ok ps =
186           try
187             let set = DiscriminationTree.find ps tree in
188               PosEqSet.exists (fun (p, e) -> meta_convertibility e) set
189           with Not_found ->
190             false
191         in
192           (ok psl) || (ok psr)
193 ;;
194 *)
195
196
197       let head_of_term = function
198         | Cic.Appl (hd::tl) -> hd
199         | term -> term
200       ;;
201
202
203       let rec subterm_at_pos pos term =
204         match pos with
205           | [] -> term
206           | index::pos ->
207               match term with
208                 | Cic.Appl l ->
209                     (try subterm_at_pos pos (List.nth l index)
210                      with Failure _ -> raise Not_found)
211                 | _ -> raise Not_found
212       ;;
213
214
215       let rec after_t pos term =
216         let pos' =
217           match pos with
218             | [] -> raise Not_found
219             | pos -> List.fold_right (fun i r -> if r = [] then [i+1] else i::r) pos []
220         in
221           try
222             let t = subterm_at_pos pos' term in pos'
223           with Not_found ->
224             let pos, _ =
225               List.fold_right
226                 (fun i (r, b) -> if b then (i::r, true) else (r, true)) pos ([], false)
227             in
228               after_t pos term
229       ;;
230
231
232       let next_t pos term =
233         let t = subterm_at_pos pos term in
234           try
235             let _ = subterm_at_pos [1] t in
236               pos @ [1]
237           with Not_found ->
238             match pos with
239               | [] -> [1]
240               | pos -> after_t pos term
241       ;;     
242
243
244       let retrieve_generalizations tree term =
245         let rec retrieve tree term pos =
246           match tree with
247             | DiscriminationTree.Node (Some s, _) when pos = [] -> s
248             | DiscriminationTree.Node (_, map) ->
249                 let res =
250                   try
251                     let hd_term = head_of_term (subterm_at_pos pos term) in
252                     let n = PSMap.find hd_term map in
253                       match n with
254                         | DiscriminationTree.Node (Some s, _) -> s
255                         | DiscriminationTree.Node (None, _) ->
256                             let newpos = try next_t pos term with Not_found -> [] in
257                               retrieve n term newpos
258                   with Not_found ->
259                     A.empty
260                 in
261                   try
262                     let n = PSMap.find (Cic.Implicit None) map in
263                     let newpos = try after_t pos term with Not_found -> [-1] in
264                       if newpos = [-1] then
265                         match n with
266                           | DiscriminationTree.Node (Some s, _) -> A.union s res
267                           | _ -> res
268                       else
269                         A.union res (retrieve n term newpos)
270                   with Not_found ->
271                     res
272         in
273           retrieve tree term []
274       ;;
275
276
277       let jump_list = function
278         | DiscriminationTree.Node (value, map) ->
279             let rec get n tree =
280               match tree with
281                 | DiscriminationTree.Node (v, m) ->
282                     if n = 0 then
283                       [tree]
284                     else
285                       PSMap.fold
286                         (fun k v res ->
287                            let a = try Hashtbl.find arities k with Not_found -> 0 in
288                              (get (n-1 + a) v) @ res) m []
289             in
290               PSMap.fold
291                 (fun k v res ->
292                    let arity = try Hashtbl.find arities k with Not_found -> 0 in
293                      (get arity v) @ res)
294                 map []
295       ;;
296
297
298       let retrieve_unifiables tree term =
299         let rec retrieve tree term pos =
300           match tree with
301             | DiscriminationTree.Node (Some s, _) when pos = [] -> s
302             | DiscriminationTree.Node (_, map) ->
303                 let subterm =
304                   try Some (subterm_at_pos pos term) with Not_found -> None
305                 in
306                   match subterm with
307                     | None -> A.empty
308                     | Some (Cic.Meta _) ->
309                         let newpos = try next_t pos term with Not_found -> [] in
310                         let jl = jump_list tree in
311                           List.fold_left
312                             (fun r s -> A.union r s)
313                             A.empty
314                             (List.map (fun t -> retrieve t term newpos) jl)
315                     | Some subterm ->
316                         let res = 
317                           try
318                             let hd_term = head_of_term subterm in
319                             let n = PSMap.find hd_term map in
320                               match n with
321                                 | DiscriminationTree.Node (Some s, _) -> s
322                                 | DiscriminationTree.Node (None, _) ->
323                                     retrieve n term (next_t pos term)
324                           with Not_found ->
325                             A.empty
326                         in
327                           try
328                             let n = PSMap.find (Cic.Implicit None) map in
329                             let newpos = try after_t pos term with Not_found -> [-1] in
330                               if newpos = [-1] then
331                                 match n with
332                                   | DiscriminationTree.Node (Some s, _) -> A.union s res
333                                   | _ -> res
334                               else
335                                 A.union res (retrieve n term newpos)
336                           with Not_found ->
337                             res
338         in
339           retrieve tree term []
340     end
341 ;;
342