]> matita.cs.unibo.it Git - helm.git/blob - helm/software/components/cic/discrimination_tree.ml
f5d61463024e3efe957406e6621cbb869de4816a
[helm.git] / helm / software / 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         | Constant of UriManager.uri 
34         | Bound of int | Variable | Proposition | Datatype | Dead;;
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         | Constant uri -> UriManager.name_of_uri uri
43         | Bound i -> string_of_int i
44         | Variable -> "?"
45         | Proposition -> "Prop"
46         | Datatype -> "Type"
47         | Dead -> "DEAD"
48       ;;
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)
58         | Cic.Appl _ -> 
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";
63             Dead
64             (* assert false universe.ml removes these *)
65       ;;
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))
70         in
71         let rec aux arities = function
72           | Cic.Appl ((hd::tl) as l) ->
73               let arities = 
74                 set_arity arities (elem_of_cic hd) (List.length tl) in
75               List.fold_left 
76                 (fun (arities,path) t -> 
77                    let arities,tpath = aux arities t in
78                      arities,path@tpath)
79                 (arities,[]) l
80           | t -> arities, [elem_of_cic t]
81         in 
82           aux arities
83       ;;
84       let compare_elem e1 e2 =
85         match e1,e2 with
86         | Constant u1,Constant u2 -> UriManager.compare u1 u2
87         | e1,e2 -> Pervasives.compare e1 e2
88       ;;
89
90       module OrderedPathStringElement = struct
91         type t = path_string_elem
92         let compare = compare_elem
93       end
94
95       module PSMap = Map.Make(OrderedPathStringElement);;
96
97       type key = PSMap.key
98
99       module DiscriminationTree = Trie.Make(PSMap);;
100
101       type t = A.t DiscriminationTree.t * (path_string_elem*int) list
102       let empty = DiscriminationTree.empty, [] ;;
103
104       let iter (dt, _ ) f =
105         DiscriminationTree.iter (fun _ x -> f x) dt
106       ;;
107
108       let index (tree,arity) term info =
109         let arity,ps = path_string_of_term arity term in
110         let ps_set =
111           try DiscriminationTree.find ps tree 
112           with Not_found -> A.empty in
113         let tree = DiscriminationTree.add ps (A.add info ps_set) tree in
114         tree,arity
115       ;;
116
117       let remove_index (tree,arity) term info =
118         let arity,ps = path_string_of_term arity term in
119         try
120           let ps_set = A.remove info (DiscriminationTree.find ps tree) in
121           if A.is_empty ps_set then
122             DiscriminationTree.remove ps tree,arity
123           else
124             DiscriminationTree.add ps ps_set tree,arity
125         with Not_found ->
126           tree,arity
127       ;;
128
129       let in_index (tree,arity) term test =
130         let arity,ps = path_string_of_term arity term in
131         try
132           let ps_set = DiscriminationTree.find ps tree in
133           A.exists test ps_set
134         with Not_found ->
135           false
136       ;;
137
138       let head_of_term = function
139         | Cic.Appl (hd::tl) -> hd
140         | term -> term
141       ;;
142
143       let rec skip_prods = function
144         | Cic.Prod (_,_,t) -> skip_prods t
145         | term -> term
146       ;;
147
148       let rec subterm_at_pos pos term =
149         match pos with
150           | [] -> term
151           | index::pos ->
152               match term with
153                 | Cic.Appl l ->
154                     (try subterm_at_pos pos (List.nth l index)
155                      with Failure _ -> raise Not_found)
156                 | _ -> raise Not_found
157       ;;
158
159
160       let rec after_t pos term =
161         let pos' =
162           match pos with
163             | [] -> raise Not_found
164             | pos -> 
165                 List.fold_right 
166                   (fun i r -> if r = [] then [i+1] else i::r) pos []
167         in
168           try
169             ignore(subterm_at_pos pos' term ); pos'
170           with Not_found ->
171             let pos, _ =
172               List.fold_right
173                 (fun i (r, b) -> if b then (i::r, true) else (r, true))
174                 pos ([], false)
175             in
176               after_t pos term
177       ;;
178
179
180       let next_t pos term =
181         let t = subterm_at_pos pos term in
182           try
183             let _ = subterm_at_pos [1] t in
184               pos @ [1]
185           with Not_found ->
186             match pos with
187               | [] -> [1]
188               | pos -> after_t pos term
189       ;;     
190
191       let retrieve_generalizations (tree,arity) term =
192         let term = skip_prods term in
193         let rec retrieve tree term pos =
194           match tree with
195             | DiscriminationTree.Node (Some s, _) when pos = [] -> s
196             | DiscriminationTree.Node (_, map) ->
197                 let res =
198                   let hd_term = 
199                     elem_of_cic (head_of_term (subterm_at_pos pos term)) 
200                   in
201                   if hd_term = Variable then A.empty else 
202                   try
203                     let n = PSMap.find hd_term map in
204                       match n with
205                         | DiscriminationTree.Node (Some s, _) -> s
206                         | DiscriminationTree.Node (None, _) ->
207                             let newpos = 
208                               try next_t pos term 
209                               with Not_found -> [] 
210                             in
211                               retrieve n term newpos
212                   with Not_found ->
213                     A.empty
214                 in
215                   try
216                     let n = PSMap.find Variable map in
217                     let newpos = try after_t pos term with Not_found -> [-1] in
218                       if newpos = [-1] then
219                         match n with
220                           | DiscriminationTree.Node (Some s, _) -> A.union s res
221                           | _ -> res
222                       else
223                         A.union res (retrieve n term newpos)
224                   with Not_found ->
225                     res
226         in
227           retrieve tree term []
228       ;;
229
230
231       let jump_list arities = function
232         | DiscriminationTree.Node (value, map) ->
233             let rec get n tree =
234               match tree with
235                 | DiscriminationTree.Node (v, m) ->
236                     if n = 0 then
237                       [tree]
238                     else
239                       PSMap.fold
240                         (fun k v res ->
241                            let a =
242                              try List.assoc k arities 
243                              with Not_found -> 0 
244                            in
245                              (get (n-1 + a) v) @ res) m []
246             in
247               PSMap.fold
248                 (fun k v res ->
249                    let arity = 
250                      try 
251                        List.assoc k arities 
252                      with Not_found -> 0 in
253                      (get arity v) @ res)
254                 map []
255       ;;
256
257
258       let retrieve_unifiables (tree,arities) term =
259         let term = skip_prods term in
260         let rec retrieve tree term pos =
261           match tree with
262             | DiscriminationTree.Node (Some s, _) when pos = [] -> s
263             | DiscriminationTree.Node (_, map) ->
264                 let subterm =
265                   try Some (subterm_at_pos pos term) with Not_found -> None
266                 in
267                 match subterm with
268                 | None -> A.empty
269                 | Some (Cic.Meta _) ->
270                       let newpos = try next_t pos term with Not_found -> [] in
271                       let jl = jump_list arities tree in
272                         List.fold_left
273                           (fun r s -> A.union r s)
274                           A.empty
275                           (List.map (fun t -> retrieve t term newpos) jl)
276                   | Some subterm ->
277                       let res = 
278                         let hd_term = elem_of_cic (head_of_term subterm) in
279                           if hd_term = Variable then
280                            A.empty else
281                         try
282                           let n = PSMap.find hd_term map in
283                             match n with
284                               | DiscriminationTree.Node (Some s, _) -> s
285                               | DiscriminationTree.Node (None, _) ->
286                                   retrieve n term (next_t pos term)
287                         with Not_found ->
288                           A.empty
289                       in
290                         try
291                           let n = PSMap.find Variable map in
292                           let newpos = 
293                             try after_t pos term 
294                             with Not_found -> [-1] 
295                           in
296                             if newpos = [-1] then
297                               match n with
298                                 | DiscriminationTree.Node (Some s, _) -> 
299                                     A.union s res
300                                 | _ -> res
301                             else
302                               A.union res (retrieve n term newpos)
303                         with Not_found ->
304                           res
305       in
306         retrieve tree term []
307   end
308 ;;
309