1 (* Copyright (C) 2005, HELM Team.
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.
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.
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.
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,
22 * For details, see the HELM World-Wide-Web page,
23 * http://cs.unibo.it/helm/.
28 module DiscriminationTreeIndexing =
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;;
38 (* needed by the retrieve_* functions, to know the arities of the
43 | Constant uri -> UriManager.name_of_uri uri
44 | Bound i -> string_of_int i
46 | Proposition -> "Prop"
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
57 try Constant (CicUtil.uri_of_term term)
58 with Invalid_argument _ -> Variable (* HACK! *)
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
65 let rec aux = function
66 | Cic.Appl ((hd::tl) as l) ->
68 if Hashtbl.mem arities (elem_of_cic hd) then
70 let n = Hashtbl.find arities (elem_of_cic hd) in
71 if n <> List.length tl then
75 (List.map (fun x -> ppelem (elem_of_cic x)) l))
77 assert(n = List.length tl)
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]
87 let compare_elem e1 e2 =
89 | Constant u1,Constant u2 -> UriManager.compare u1 u2
90 | e1,e2 -> Pervasives.compare e1 e2
93 module OrderedPathStringElement = struct
94 type t = path_string_elem
95 let compare = compare_elem
98 module PSMap = Map.Make(OrderedPathStringElement);;
102 module DiscriminationTree = Trie.Make(PSMap);;
104 type t = A.t DiscriminationTree.t * (path_string_elem, int) Hashtbl.t
105 let empty = DiscriminationTree.empty, Hashtbl.create 11;;
108 module OrderedPosEquality = struct
109 type t = Utils.pos * Inference.equality
110 let compare = Pervasives.compare
113 module PosEqSet = Set.Make(OrderedPosEquality);;
115 let string_of_discrimination_tree tree =
116 let rec to_string level = function
117 | DiscriminationTree.Node (value, map) ->
121 (String.make (2 * level) ' ') ^
122 "{" ^ (String.concat "; "
125 "(" ^ (Utils.string_of_pos p) ^ ", " ^
126 (Inference.string_of_equality e) ^ ")")
127 (PosEqSet.elements v))) ^ "}"
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)
145 let index (tree,arity) term info =
146 let ps = path_string_of_term arity term in
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
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 =
161 try DiscriminationTree.find ps tree with Not_found -> PosEqSet.empty in
163 DiscriminationTree.add ps (PosEqSet.add (pos, equality) ps_set) tree in
167 | Utils.Gt -> index Utils.Left tree psl
168 | Utils.Lt -> index Utils.Right tree psr
170 let tree = index Utils.Left tree psl in
171 index Utils.Right tree psr
175 let remove_index (tree,arity) term info =
176 let ps = path_string_of_term arity term in
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
182 DiscriminationTree.add ps ps_set tree,arity
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 =
195 PosEqSet.remove (pos, equality) (DiscriminationTree.find ps tree) in
196 if PosEqSet.is_empty ps_set then
197 DiscriminationTree.remove ps tree
199 DiscriminationTree.add ps ps_set tree
204 | Utils.Gt -> remove_index Utils.Left tree psl
205 | Utils.Lt -> remove_index Utils.Right tree psr
207 let tree = remove_index Utils.Left tree psl in
208 remove_index Utils.Right tree psr
213 let in_index (tree,arity) term test =
214 let ps = path_string_of_term arity term in
216 let ps_set = DiscriminationTree.find ps tree in
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
230 let set = DiscriminationTree.find ps tree in
231 PosEqSet.exists (fun (p, e) -> meta_convertibility e) set
240 let head_of_term = function
241 | Cic.Appl (hd::tl) -> hd
245 let rec skip_prods = function
246 | Cic.Prod (_,_,t) -> skip_prods t
250 let rec subterm_at_pos pos term =
256 (try subterm_at_pos pos (List.nth l index)
257 with Failure _ -> raise Not_found)
258 | _ -> raise Not_found
262 let rec after_t pos term =
265 | [] -> raise Not_found
268 (fun i r -> if r = [] then [i+1] else i::r) pos []
271 ignore(subterm_at_pos pos' term ); pos'
275 (fun i (r, b) -> if b then (i::r, true) else (r, true))
282 let next_t pos term =
283 let t = subterm_at_pos pos term in
285 let _ = subterm_at_pos [1] t in
290 | pos -> after_t pos term
293 let retrieve_generalizations (tree,arity) term =
294 let term = skip_prods term in
295 let rec retrieve tree term pos =
297 | DiscriminationTree.Node (Some s, _) when pos = [] -> s
298 | DiscriminationTree.Node (_, map) ->
301 elem_of_cic (head_of_term (subterm_at_pos pos term))
303 if hd_term = Variable then A.empty else
305 let n = PSMap.find hd_term map in
307 | DiscriminationTree.Node (Some s, _) -> s
308 | DiscriminationTree.Node (None, _) ->
313 retrieve n term newpos
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
322 | DiscriminationTree.Node (Some s, _) -> A.union s res
325 A.union res (retrieve n term newpos)
329 retrieve tree term []
333 let jump_list arities = function
334 | DiscriminationTree.Node (value, map) ->
337 | DiscriminationTree.Node (v, m) ->
344 try Hashtbl.find arities k
347 (get (n-1 + a) v) @ res) m []
351 let arity = try Hashtbl.find arities k with Not_found -> 0 in
357 let retrieve_unifiables (tree,arities) term =
358 let term = skip_prods term in
359 let rec retrieve tree term pos =
361 | DiscriminationTree.Node (Some s, _) when pos = [] -> s
362 | DiscriminationTree.Node (_, map) ->
364 try Some (subterm_at_pos pos term) with Not_found -> None
368 | Some (Cic.Meta _) ->
369 let newpos = try next_t pos term with Not_found -> [] in
370 let jl = jump_list arities tree in
372 (fun r s -> A.union r s)
374 (List.map (fun t -> retrieve t term newpos) jl)
377 let hd_term = elem_of_cic (head_of_term subterm) in
378 if hd_term = Variable then A.empty else
380 let n = PSMap.find hd_term map in
382 | DiscriminationTree.Node (Some s, _) -> s
383 | DiscriminationTree.Node (None, _) ->
384 retrieve n term (next_t pos term)
389 let n = PSMap.find Variable map in
392 with Not_found -> [-1]
394 if newpos = [-1] then
396 | DiscriminationTree.Node (Some s, _) ->
400 A.union res (retrieve n term newpos)
404 retrieve tree term []