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 | Constant of UriManager.uri
34 | Bound of int | Variable | Proposition | Datatype | Dead;;
35 type path_string = path_string_elem list;;
38 (* needed by the retrieve_* functions, to know the arities of the
42 | Constant uri -> UriManager.name_of_uri uri
43 | Bound i -> string_of_int i
45 | Proposition -> "Prop"
49 let pppath l = String.concat "::" (List.map ppelem l) ;;
50 let elem_of_cic = function
51 | Cic.Meta _ | Cic.Implicit _ -> Variable
52 | Cic.Rel i -> Bound i
53 | Cic.Sort (Cic.Prop) -> Proposition
54 | Cic.Sort _ -> Datatype
55 | Cic.Const _ | Cic.Var _ | Cic.MutInd _ | Cic.MutConstruct _ as t ->
56 (try Constant (CicUtil.uri_of_term t)
57 with Invalid_argument _ -> assert false)
59 assert false (* should not happen *)
60 | Cic.LetIn _ | Cic.Lambda _ | Cic.Prod _ | Cic.Cast _
61 | Cic.MutCase _ | Cic.Fix _ | Cic.CoFix _ ->
62 HLog.debug "FIXME: the trie receives an invalid term";
64 (* assert false universe.ml removes these *)
66 let path_string_of_term arities =
67 let set_arity arities k n =
68 (assert (k<>Variable || n=0);
69 if k = Dead then arities else (k,n)::(List.remove_assoc k arities))
71 let rec aux arities = function
72 | Cic.Appl ((hd::tl) as l) ->
74 set_arity arities (elem_of_cic hd) (List.length tl) in
76 (fun (arities,path) t ->
77 let arities,tpath = aux arities t in
80 | t -> arities, [elem_of_cic t]
84 let compare_elem e1 e2 =
86 | Constant u1,Constant u2 -> UriManager.compare u1 u2
87 | e1,e2 -> Pervasives.compare e1 e2
90 module OrderedPathStringElement = struct
91 type t = path_string_elem
92 let compare = compare_elem
95 module PSMap = Map.Make(OrderedPathStringElement);;
99 module DiscriminationTree = Trie.Make(PSMap);;
101 type t = A.t DiscriminationTree.t * (path_string_elem*int) list
102 let empty = DiscriminationTree.empty, [] ;;
104 let index (tree,arity) term info =
105 let arity,ps = path_string_of_term arity term in
107 try DiscriminationTree.find ps tree
108 with Not_found -> A.empty in
109 let tree = DiscriminationTree.add ps (A.add info ps_set) tree in
113 let remove_index (tree,arity) term info =
114 let arity,ps = path_string_of_term arity term in
116 let ps_set = A.remove info (DiscriminationTree.find ps tree) in
117 if A.is_empty ps_set then
118 DiscriminationTree.remove ps tree,arity
120 DiscriminationTree.add ps ps_set tree,arity
125 let in_index (tree,arity) term test =
126 let arity,ps = path_string_of_term arity term in
128 let ps_set = DiscriminationTree.find ps tree in
134 let head_of_term = function
135 | Cic.Appl (hd::tl) -> hd
139 let rec skip_prods = function
140 | Cic.Prod (_,_,t) -> skip_prods t
144 let rec subterm_at_pos pos term =
150 (try subterm_at_pos pos (List.nth l index)
151 with Failure _ -> raise Not_found)
152 | _ -> raise Not_found
156 let rec after_t pos term =
159 | [] -> raise Not_found
162 (fun i r -> if r = [] then [i+1] else i::r) pos []
165 ignore(subterm_at_pos pos' term ); pos'
169 (fun i (r, b) -> if b then (i::r, true) else (r, true))
176 let next_t pos term =
177 let t = subterm_at_pos pos term in
179 let _ = subterm_at_pos [1] t in
184 | pos -> after_t pos term
187 let retrieve_generalizations (tree,arity) term =
188 let term = skip_prods term in
189 let rec retrieve tree term pos =
191 | DiscriminationTree.Node (Some s, _) when pos = [] -> s
192 | DiscriminationTree.Node (_, map) ->
195 elem_of_cic (head_of_term (subterm_at_pos pos term))
197 if hd_term = Variable then A.empty else
199 let n = PSMap.find hd_term map in
201 | DiscriminationTree.Node (Some s, _) -> s
202 | DiscriminationTree.Node (None, _) ->
207 retrieve n term newpos
212 let n = PSMap.find Variable map in
213 let newpos = try after_t pos term with Not_found -> [-1] in
214 if newpos = [-1] then
216 | DiscriminationTree.Node (Some s, _) -> A.union s res
219 A.union res (retrieve n term newpos)
223 retrieve tree term []
227 let jump_list arities = function
228 | DiscriminationTree.Node (value, map) ->
231 | DiscriminationTree.Node (v, m) ->
238 try List.assoc k arities
241 (get (n-1 + a) v) @ res) m []
248 with Not_found -> 0 in
254 let retrieve_unifiables (tree,arities) term =
255 let term = skip_prods term in
256 let rec retrieve tree term pos =
258 | DiscriminationTree.Node (Some s, _) when pos = [] -> s
259 | DiscriminationTree.Node (_, map) ->
261 try Some (subterm_at_pos pos term) with Not_found -> None
265 | Some (Cic.Meta _) ->
266 let newpos = try next_t pos term with Not_found -> [] in
267 let jl = jump_list arities tree in
269 (fun r s -> A.union r s)
271 (List.map (fun t -> retrieve t term newpos) jl)
274 let hd_term = elem_of_cic (head_of_term subterm) in
275 if hd_term = Variable then
278 let n = PSMap.find hd_term map in
280 | DiscriminationTree.Node (Some s, _) -> s
281 | DiscriminationTree.Node (None, _) ->
282 retrieve n term (next_t pos term)
287 let n = PSMap.find Variable map in
290 with Not_found -> [-1]
292 if newpos = [-1] then
294 | DiscriminationTree.Node (Some s, _) ->
298 A.union res (retrieve n term newpos)
302 retrieve tree term []