]> matita.cs.unibo.it Git - helm.git/blob - helm/software/components/ng_refiner/nCicCoercion.ml
Preparing for 0.5.9 release.
[helm.git] / helm / software / components / ng_refiner / nCicCoercion.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: nCicRefiner.mli 9227 2008-11-21 16:00:06Z tassi $ *)
13
14 let debug s = prerr_endline (Lazy.force s);;
15 let debug _ = ();;
16
17 let convert_term = ref (fun _ _ -> assert false);;
18 let set_convert_term f = convert_term := f;;
19
20 module COT : Set.OrderedType 
21 with type t = string * NCic.term * int * int  * NCic.term *
22 NCic.term = 
23   struct
24      type t = string * NCic.term * int * int * NCic.term * NCic.term
25      let compare = Pervasives.compare
26   end
27
28 module CoercionSet = Set.Make(COT)
29
30 module DB = 
31   Discrimination_tree.Make(NDiscriminationTree.NCicIndexable)(CoercionSet)
32
33 type db = DB.t * DB.t
34
35 let empty_db = DB.empty,DB.empty
36
37 class type g_status =
38  object
39   inherit NCicUnifHint.g_status
40   method coerc_db: db
41  end
42
43 class status =
44  object
45   inherit NCicUnifHint.status
46   val db = empty_db
47   method coerc_db = db
48   method set_coerc_db v = {< db = v >}
49   method set_coercion_status
50    : 'status. #g_status as 'status -> 'self
51    = fun o -> {< db = o#coerc_db >}#set_unifhint_status o
52  end
53
54 let index_coercion status name c src tgt arity arg =
55   let db_src,db_tgt = status#coerc_db in
56   let data = (name,c,arity,arg,src,tgt) in
57   debug (lazy ("INDEX:" ^ 
58     NCicPp.ppterm ~metasenv:[] ~subst:[] ~context:[] src ^ " ===> " ^
59     NCicPp.ppterm ~metasenv:[] ~subst:[] ~context:[] tgt ^ "  :=  " ^
60     NCicPp.ppterm ~metasenv:[] ~subst:[] ~context:[] c ^ " " ^ 
61     string_of_int arg ^ " " ^ string_of_int arity));
62   let db_src = DB.index db_src src data in
63   let db_tgt = DB.index db_tgt tgt data in
64   status#set_coerc_db (db_src, db_tgt)
65 ;;
66
67 let index_old_db odb (status : #status) =
68   List.fold_left 
69     (fun status (_,tgt,clist) -> 
70        List.fold_left 
71          (fun status (uri,_,arg) ->
72            try
73             let c=fst (!convert_term uri (CicUtil.term_of_uri uri)) in
74             let arity = match tgt with | CoercDb.Fun i -> i | _ -> 0 in
75             let src, tgt = 
76               let cty = NCicTypeChecker.typeof ~subst:[] ~metasenv:[] [] c in
77               let scty, metasenv,_ = 
78                 NCicMetaSubst.saturate ~delta:max_int [] [] [] cty (arity+1) 
79               in
80               match scty with
81               | NCic.Prod (_, src, tgt) -> 
82                  let tgt =
83                    NCicSubstitution.subst (NCic.Meta (-1,(0,NCic.Irl 0))) tgt
84                  in
85 (*
86             debug (lazy (Printf.sprintf "indicizzo %s (%d)) : %s ===> %s" 
87               (NCicPp.ppterm ~metasenv ~subst:[] ~context:[] scty) (arity+1)
88               (NCicPp.ppterm ~metasenv ~subst:[] ~context:[] src)
89               (NCicPp.ppterm ~metasenv ~subst:[] ~context:[] tgt));
90 *)
91                 src, tgt
92               | t -> 
93                   debug (lazy (
94                     NCicPp.ppterm ~metasenv ~subst:[] ~context:[] t));
95                   assert false
96             in
97             index_coercion status "foo" c src tgt arity arg
98            with 
99            | NCicEnvironment.BadDependency _ 
100            | NCicTypeChecker.TypeCheckerFailure _ -> status)
101          status clist)
102     status (CoercDb.to_list odb)
103 ;;
104
105 let look_for_coercion status metasenv subst context infty expty =
106  let db_src,db_tgt = status#coerc_db in
107   match 
108     NCicUntrusted.apply_subst subst context infty, 
109     NCicUntrusted.apply_subst subst context expty 
110   with
111   | (NCic.Meta _ | NCic.Appl (NCic.Meta _::_)), 
112     (NCic.Meta _ | NCic.Appl (NCic.Meta _::_)) -> [] 
113   | infty, expty ->
114
115     debug (lazy ("LOOK FOR COERCIONS: " ^ 
116       NCicPp.ppterm ~metasenv ~subst ~context infty ^ "  |===> " ^
117       NCicPp.ppterm ~metasenv ~subst ~context expty));
118
119     let src_class = infty :: NCicUnifHint.eq_class_of status infty in
120     let tgt_class = expty :: NCicUnifHint.eq_class_of status expty in
121
122     let set_src = 
123       List.fold_left 
124         (fun set infty -> 
125           CoercionSet.union (DB.retrieve_unifiables db_src infty) set)
126         CoercionSet.empty src_class
127     in
128     let set_tgt = 
129       List.fold_left 
130         (fun set expty -> 
131           CoercionSet.union (DB.retrieve_unifiables db_tgt expty) set)
132         CoercionSet.empty tgt_class
133     in
134
135     debug (lazy ("CANDIDATES SRC: " ^ 
136       String.concat "," (List.map (fun (name,t,_,_,_,_) ->
137         name ^ " :: " ^ NCicPp.ppterm ~metasenv ~subst ~context t) 
138       (CoercionSet.elements set_src))));
139     debug (lazy ("CANDIDATES TGT: " ^ 
140       String.concat "," (List.map (fun (name,t,_,_,_,_) ->
141         name ^ " :: " ^ NCicPp.ppterm ~metasenv ~subst ~context t) 
142       (CoercionSet.elements set_tgt))));
143
144     let candidates = CoercionSet.inter set_src set_tgt in
145
146     debug (lazy ("CANDIDATES: " ^ 
147       String.concat "," (List.map (fun (name,t,_,_,_,_) ->
148         name ^ " :: " ^ NCicPp.ppterm ~metasenv ~subst ~context t) 
149       (CoercionSet.elements candidates))));
150
151     List.map
152       (fun (name,t,arity,arg,_,_) ->
153           let ty =
154             try NCicTypeChecker.typeof ~metasenv:[] ~subst:[] [] t 
155             with NCicTypeChecker.TypeCheckerFailure s ->
156              prerr_endline ("illtyped coercion: "^Lazy.force s);
157              prerr_endline (NCicPp.ppterm ~metasenv:[] ~subst:[] ~context:[] t);
158              assert false
159           in
160           let ty, metasenv, args = 
161            NCicMetaSubst.saturate ~delta:max_int metasenv subst context ty arity
162           in
163
164           debug (lazy (
165             NCicPp.ppterm ~metasenv ~subst:[] ~context:[] ty ^ " --- " ^ 
166             NCicPp.ppterm ~metasenv ~subst ~context
167             (NCicUntrusted.mk_appl t args) ^ " --- " ^ 
168               string_of_int (List.length args) ^ " == " ^ string_of_int arg)); 
169              
170           name,metasenv, NCicUntrusted.mk_appl t args, ty, List.nth args arg)
171       (CoercionSet.elements candidates)
172 ;;
173
174 (* CSC: very inefficient implementation!
175    Enrico, can we use a discrimination tree here? *)
176 let match_coercion status ~metasenv ~subst ~context t =
177  let db =
178   DB.fold (fst (status#coerc_db)) (fun _ v l -> (CoercionSet.elements v)@l) []
179  in
180     (HExtlib.list_findopt
181       (fun (_,p,arity,cpos,_,_) _ ->
182         try
183          let t =
184           match p,t with
185              NCic.Appl lp, NCic.Appl lt ->
186               (match fst (HExtlib.split_nth (List.length lp) lt) with
187                   [t] -> t
188                 | l -> NCic.Appl l)
189            | _,NCic.Appl (he::_) -> he
190            | _,_ -> t
191          in
192          let b = NCicReduction.alpha_eq metasenv subst context p t in
193          if not b then None else
194          let ty = NCicTypeChecker.typeof ~metasenv:[] ~subst:[] [] p in
195          let pis = 
196            let rec aux = function NCic.Prod (_,_,t) -> 1+aux t | _ -> 0 in
197            aux ty
198          in
199          Some (p,pis - arity - cpos - 1,cpos)
200         with
201          Failure _ -> None (* raised by split_nth *)
202       ) db)
203 ;;
204
205 let generate_dot_file status fmt =
206   let module Pp = GraphvizPp.Dot in
207   let src_db, _ = status#coerc_db in
208   let edges = ref [] in
209   DB.iter src_db (fun _ dataset -> 
210      edges := !edges @ 
211       List.map
212         (fun (name,t,a,g,sk,dk) -> 
213           debug(lazy (let p = NCicPp.ppterm ~metasenv:[] ~context:[]
214                 ~subst:[] in p t ^ " ::: " ^ p sk ^ " |--> " ^ p dk));
215           let eq_s= sk::NCicUnifHint.eq_class_of status sk in
216           let eq_t= dk::NCicUnifHint.eq_class_of status dk in
217           (name,t,a,g),eq_s,eq_t
218           )
219         (CoercionSet.elements dataset);
220     );
221   let nodes = 
222     HExtlib.list_uniq
223      (List.sort compare 
224        (List.flatten
225          (List.map
226            (fun (_,a,b) ->
227              [a;b]
228             )
229            !edges)))
230   in
231   let names = ref [] in
232   let id = ref 0 in
233   let mangle l =
234     try List.assoc l !names
235     with Not_found ->
236       incr id;
237       names := (l,"node"^string_of_int!id) :: !names;
238       List.assoc l !names
239   in
240   List.iter 
241     (fun cl -> 
242       Pp.node (mangle cl) 
243       ~attrs:["label",String.concat "\\n"
244         (List.map (fun t->
245           NCicPp.ppterm ~metasenv:[] ~subst:[]
246            ~context:[] t ~margin:max_int
247         ) cl)]
248       fmt)
249     nodes;
250   List.iter 
251     (fun ((name,_,_,_),src,tgt) ->
252        Pp.edge (mangle src) (mangle tgt)
253        ~attrs:["label", name] fmt)
254     !edges;
255 ;;