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