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