]> matita.cs.unibo.it Git - helm.git/blob - helm/software/components/ng_refiner/nDiscriminationTree.ml
c4fd43ad2a6cd163902e673951d96db473d1e4ce
[helm.git] / helm / software / components / ng_refiner / nDiscriminationTree.ml
1 (*
2     ||M||  This file is part of HELM, an Hypertextual, Electronic        
3     ||A||  Library of Mathematics, developed at the Computer Science     
4     ||T||  Department, University of Bologna, Italy.                     
5     ||I||                                                                
6     ||T||  HELM is free software; you can redistribute it and/or         
7     ||A||  modify it under the terms of the GNU General Public License   
8     \   /  version 2 or (at your option) any later version.      
9      \ /   This software is distributed as is, NO WARRANTY.     
10       V_______________________________________________________________ *)
11
12 (* $Id$ *)
13
14 type path_string_elem = 
15   | Constant of NUri.uri 
16   | Bound of int 
17   | Variable 
18   | Proposition 
19   | Datatype 
20   | Dead of NCic.term 
21 ;;
22
23 type path_string = path_string_elem list;;
24
25 let ppelem = function
26   | Constant uri -> NUri.name_of_uri uri
27   | Bound i -> string_of_int i
28   | Variable -> "?"
29   | Proposition -> "Prop"
30   | Datatype -> "Type"
31   | Dead t -> 
32       "DEAD("^NCicPp.ppterm ~context:[] ~subst:[] ~metasenv:[] t^")"
33 ;;
34
35 let pp_path_string l = String.concat "::" (List.map ppelem l) ;;
36
37 let elem_of_cic = function
38   | NCic.Meta _ | NCic.Implicit _ -> Variable
39   | NCic.Rel i -> Bound i
40   | NCic.Sort (NCic.Prop) -> Proposition
41   | NCic.Sort _ -> Datatype
42   | NCic.Const (NReference.Ref (u,_)) -> Constant u
43   | NCic.Appl _ -> assert false (* should not happen *)
44   | NCic.LetIn _ | NCic.Lambda _ | NCic.Prod _ | NCic.Match _ as t -> 
45       prerr_endline 
46         "FIXME: the discrimination tree receives an invalid term";
47       Dead t
48 ;;
49
50 let path_string_of_term arities =
51   let set_arity arities k n = 
52     (assert (k<>Variable || n=0);
53     match k with 
54     | Dead _ -> arities 
55     | _ -> 
56        (* here we override, but partial instantiation may trick us *)
57        (k,n)::(List.remove_assoc k arities))
58   in
59   let rec aux arities = function
60     | NCic.Appl ((hd::tl) as l) ->
61         let arities = 
62           set_arity arities (elem_of_cic hd) (List.length tl) 
63         in
64         List.fold_left 
65         (fun (arities,path) t -> 
66            let arities,tpath = aux arities t in
67              arities,path@tpath)
68         (arities,[]) l
69     | t -> arities, [elem_of_cic t]
70   in 
71     aux arities
72 ;;
73
74 let compare_elem e1 e2 =
75   match e1,e2 with
76   | Constant u1,Constant u2 -> NUri.compare u1 u2
77   | e1,e2 -> Pervasives.compare e1 e2
78 ;;
79
80 let head_of_term = function
81   | NCic.Appl (hd::tl) -> hd
82   | term -> term
83 ;;
84
85 let rec skip_prods = function
86   | NCic.Prod (_,_,t) -> skip_prods t
87   | term -> term
88 ;;
89
90
91 module DiscriminationTreeIndexing =  
92   functor (A:Set.S) -> 
93     struct
94
95       module OrderedPathStringElement = struct
96         type t = path_string_elem
97         let compare = compare_elem
98       end
99
100       module PSMap = Map.Make(OrderedPathStringElement);;
101
102       type key = PSMap.key
103
104       module DiscriminationTree = Trie.Make(PSMap);;
105
106       type t = A.t DiscriminationTree.t * (path_string_elem*int) list
107
108       let empty = DiscriminationTree.empty, [] ;;
109
110       let iter (dt, _ ) f =
111         DiscriminationTree.iter (fun y x -> f y  x) dt
112       ;;
113
114       let index (tree,arity) term info =
115         let arity,ps = path_string_of_term arity term in
116         let ps_set =
117           try DiscriminationTree.find ps tree 
118           with Not_found -> A.empty in
119         let tree = DiscriminationTree.add ps (A.add info ps_set) tree in
120         tree,arity
121       ;;
122
123       let remove_index (tree,arity) term info =
124         let arity,ps = path_string_of_term arity term in
125         try
126           let ps_set = A.remove info (DiscriminationTree.find ps tree) in
127           if A.is_empty ps_set then
128             DiscriminationTree.remove ps tree,arity
129           else
130             DiscriminationTree.add ps ps_set tree,arity
131         with Not_found ->
132           tree,arity
133       ;;
134
135       let in_index (tree,arity) term test =
136         let arity,ps = path_string_of_term arity term in
137         try
138           let ps_set = DiscriminationTree.find ps tree in
139           A.exists test ps_set
140         with Not_found ->
141           false
142       ;;
143
144       let rec subterm_at_pos pos term =
145         match pos with
146           | [] -> term
147           | index::pos ->
148               match term with
149                 | NCic.Appl l ->
150                     (try subterm_at_pos pos (List.nth l index)
151                      with Failure _ -> raise Not_found)
152                 | _ -> raise Not_found
153       ;;
154
155
156       let rec after_t pos term =
157         let pos' =
158           match pos with
159             | [] -> raise Not_found
160             | pos -> 
161                 List.fold_right 
162                   (fun i r -> if r = [] then [i+1] else i::r) pos []
163         in
164           try
165             ignore(subterm_at_pos pos' term ); pos'
166           with Not_found ->
167             let pos, _ =
168               List.fold_right
169                 (fun i (r, b) -> if b then (i::r, true) else (r, true))
170                 pos ([], false)
171             in
172               after_t pos term
173       ;;
174
175
176       let next_t pos term =
177         let t = subterm_at_pos pos term in
178           try
179             let _ = subterm_at_pos [1] t in
180               pos @ [1]
181           with Not_found ->
182             match pos with
183               | [] -> [1]
184               | pos -> after_t pos term
185       ;;     
186
187       let retrieve_generalizations (tree,arity) term =
188         let term = skip_prods term in
189         let rec retrieve tree term pos =
190           match tree with
191             | DiscriminationTree.Node (Some s, _) when pos = [] -> s
192             | DiscriminationTree.Node (_, map) ->
193                 let res =
194                   let hd_term = 
195                     elem_of_cic (head_of_term (subterm_at_pos pos term)) 
196                   in
197                   if hd_term = Variable then A.empty else 
198                   try
199                     let n = PSMap.find hd_term map in
200                       match n with
201                         | DiscriminationTree.Node (Some s, _) -> s
202                         | DiscriminationTree.Node (None, _) ->
203                             let newpos = 
204                               try next_t pos term 
205                               with Not_found -> [] 
206                             in
207                               retrieve n term newpos
208                   with Not_found ->
209                     A.empty
210                 in
211                   try
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
215                         match n with
216                           | DiscriminationTree.Node (Some s, _) -> A.union s res
217                           | _ -> res
218                       else
219                         A.union res (retrieve n term newpos)
220                   with Not_found ->
221                     res
222         in
223           retrieve tree term []
224       ;;
225
226
227       let jump_list arities = function
228         | DiscriminationTree.Node (value, map) ->
229             let rec get n tree =
230               match tree with
231                 | DiscriminationTree.Node (v, m) ->
232                     if n = 0 then
233                       [tree]
234                     else
235                       PSMap.fold
236                         (fun k v res ->
237                            let a =
238                              try List.assoc k arities 
239                              with Not_found -> 0 
240                            in
241                              (get (n-1 + a) v) @ res) m []
242             in
243               PSMap.fold
244                 (fun k v res ->
245                    let arity = 
246                      try 
247                        List.assoc k arities 
248                      with Not_found -> 0 in
249                      (get arity v) @ res)
250                 map []
251       ;;
252
253
254       let retrieve_unifiables (tree,arities) term =
255         let term = skip_prods term in
256         let rec retrieve tree term pos =
257           match tree with
258             | DiscriminationTree.Node (Some s, _) when pos = [] -> s
259             | DiscriminationTree.Node (_, map) ->
260                 let subterm =
261                   try Some (subterm_at_pos pos term) with Not_found -> None
262                 in
263                 match subterm with
264                 | None -> A.empty
265                 | Some (NCic.Meta _) ->
266                       let newpos = try next_t pos term with Not_found -> [] in
267                       let jl = jump_list arities tree in
268                         List.fold_left
269                           (fun r s -> A.union r s)
270                           A.empty
271                           (List.map (fun t -> retrieve t term newpos) jl)
272                   | Some subterm ->
273                       let res = 
274                         let hd_term = elem_of_cic (head_of_term subterm) in
275                           if hd_term = Variable then
276                            A.empty else
277                         try
278                           let n = PSMap.find hd_term map in
279                             match n with
280                               | DiscriminationTree.Node (Some s, _) -> s
281                               | DiscriminationTree.Node (None, _) ->
282                                   retrieve n term (next_t pos term)
283                         with Not_found ->
284                           A.empty
285                       in
286                         try
287                           let n = PSMap.find Variable map in
288                           let newpos = 
289                             try after_t pos term 
290                             with Not_found -> [-1] 
291                           in
292                             if newpos = [-1] then
293                               match n with
294                                 | DiscriminationTree.Node (Some s, _) -> 
295                                     A.union s res
296                                 | _ -> res
297                             else
298                               A.union res (retrieve n term newpos)
299                         with Not_found ->
300                           res
301       in
302         retrieve tree term []
303   end
304 ;;
305