]> matita.cs.unibo.it Git - helm.git/blob - components/library/coercGraph.ml
- transcript: patched to generate aliases instead of inlined variables
[helm.git] / components / library / coercGraph.ml
1 (* Copyright (C) 2000, 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 open Printf;;
29
30 type coercion_search_result = 
31   | SomeCoercion of Cic.term list
32   | NoCoercion
33   | NotMetaClosed
34   | NotHandled of string Lazy.t
35
36 let debug = false
37 let debug_print s = if debug then prerr_endline (Lazy.force s) else ()
38
39 (* searches a coercion fron src to tgt in the !coercions list *)
40 let look_for_coercion' src tgt =
41   let arity_of con =
42     try
43       let ty,_ = CicTypeChecker.type_of_aux' [] [] con CicUniv.empty_ugraph in
44       let rec count_pi = function
45         | Cic.Prod (_,_,t) -> 1 + count_pi t
46         | _ -> 0
47       in
48       count_pi ty
49     with Invalid_argument _ -> assert false (* all coercions have an uri *)
50   in
51   let rec mk_implicits = function
52     | 0 -> [] 
53     | n -> Cic.Implicit None :: mk_implicits (n-1)
54   in
55   try 
56     let l = 
57       CoercDb.find_coercion 
58         (fun (s,t) -> CoercDb.eq_carr s src && CoercDb.eq_carr t tgt) in
59     let uri =
60      match l with
61      | [] -> 
62          debug_print 
63            (lazy 
64              (sprintf ":-( coercion non trovata da %s a %s" 
65                (CoercDb.name_of_carr src) 
66                (CoercDb.name_of_carr tgt)));
67          None
68      | _::_ -> 
69          debug_print (lazy (
70            sprintf ":-) TROVATE %d coercion(s) da %s a %s" 
71              (List.length l)
72              (CoercDb.name_of_carr src) 
73              (CoercDb.name_of_carr tgt)));
74          Some l
75     in
76      (match uri with
77          None -> NoCoercion
78        | Some ul ->
79           let cl = List.map CicUtil.term_of_uri ul in
80           let funclass_arityl = 
81             let _,tgtcarl = List.split (List.map CoercDb.get_carr ul) in
82             List.map (function CoercDb.Fun i -> i | _ -> 0) tgtcarl
83           in
84           let arityl = List.map arity_of cl in
85           let argsl = 
86             List.map2 
87               (fun arity fn_arity -> 
88                 mk_implicits (arity - 1 - fn_arity)) arityl funclass_arityl
89           in
90           let newtl =
91             List.map2 
92               (fun args c -> 
93                 match args with
94                 |  [] -> c
95                 | _ -> Cic.Appl (c::args))
96               argsl cl
97           in
98            SomeCoercion newtl)
99   with
100     | CoercDb.EqCarrNotImplemented s -> NotHandled s
101     | CoercDb.EqCarrOnNonMetaClosed -> NotMetaClosed
102 ;;
103
104 let look_for_coercion src tgt = 
105   let src_uri = CoercDb.coerc_carr_of_term src in
106   let tgt_uri = CoercDb.coerc_carr_of_term tgt in
107   look_for_coercion' src_uri tgt_uri
108
109 let is_a_coercion t = 
110   try
111     let uri = CicUtil.uri_of_term t in
112     CoercDb.is_a_coercion uri
113   with Invalid_argument _ -> false
114
115 let source_of t = 
116   try
117     let uri = CicUtil.uri_of_term t in
118     CoercDb.term_of_carr (fst (CoercDb.get_carr uri))
119   with Invalid_argument _ -> assert false (* t must be a coercion *)
120
121 let is_a_coercion_to_funclass t =
122   try
123     let uri = CicUtil.uri_of_term t in
124     match snd (CoercDb.get_carr uri) with
125     | CoercDb.Fun i -> Some i
126     | _ -> None
127   with Invalid_argument _ -> None
128   
129 let generate_dot_file () =
130   let module Pp = GraphvizPp.Dot in
131   let buf = Buffer.create 10240 in
132   let fmt = Format.formatter_of_buffer buf in
133   Pp.header ~node_attrs:["fontsize", "9"; "width", ".4"; "height", ".4"]
134     ~edge_attrs:["fontsize", "10"] fmt;
135   let l = CoercDb.to_list () in
136   let pp_description carr =
137     match CoercDb.uri_of_carr carr with
138     | None -> ()
139     | Some uri ->
140         Pp.node (CoercDb.name_of_carr carr)
141           ~attrs:["href", UriManager.string_of_uri uri] fmt in
142   List.iter
143     (fun (src, tgt, cl) ->
144       let src_name = CoercDb.name_of_carr src in
145       let tgt_name = CoercDb.name_of_carr tgt in
146       pp_description src;
147       pp_description tgt;
148       List.iter
149         (fun c ->
150           Pp.edge src_name tgt_name
151             ~attrs:[ "label", UriManager.name_of_uri c;
152               "href", UriManager.string_of_uri c ]
153             fmt)
154         cl)
155     l;
156   Pp.trailer fmt;
157   Buffer.contents buf
158 ;;
159     
160 let is_composite t =
161   try
162     let uri = 
163       match t with 
164       | Cic.Appl (he::_) -> CicUtil.uri_of_term he
165       | _ -> CicUtil.uri_of_term t
166     in
167     match CicEnvironment.get_obj CicUniv.empty_ugraph uri with
168     | Cic.Constant (_,_, _, _, attrs),_  ->
169         List.exists (function `Class (`Coercion _) -> true | _ -> false) attrs
170     | _ -> false
171   with Invalid_argument _ -> false
172 ;;
173
174 let uniq = HExtlib.list_uniq ~eq:(fun (a,_) (b,_) -> CoercDb.eq_carr a b);;
175
176 let splat e l = List.map (fun x -> e, x) l;;
177
178 let get_coercions_to carr = 
179   let l = CoercDb.to_list () in
180   List.flatten 
181     (HExtlib.filter_map 
182       (fun (src,tgt,cl) -> 
183         if CoercDb.eq_carr tgt carr then Some (splat src cl) else None) 
184       l)
185 ;;
186
187 let get_coercions_from carr = 
188   let l = CoercDb.to_list () in
189   List.flatten 
190     (HExtlib.filter_map 
191       (fun (src,tgt,cl) -> 
192         if CoercDb.eq_carr src carr then Some (splat tgt cl) else None) 
193       l)
194 ;;
195
196 let intersect l1 l2 = 
197   let is_in_l1 (x,_) = List.exists (fun (src,_) -> CoercDb.eq_carr x src) l1 in
198   uniq (List.filter is_in_l1 l2)
199 ;;
200
201 let grow s = 
202   uniq (List.flatten (List.map (fun (x,_) -> get_coercions_to x) s) @ s)
203 ;;
204
205 let lb c = 
206   let l = get_coercions_from c in
207   function x -> List.exists (fun (y,_) -> CoercDb.eq_carr x y) l
208 ;;
209
210 let rec min acc = function
211   | c::tl -> 
212     if List.exists (lb c) (tl@acc) then min acc tl else min (c::acc) tl
213   | [] -> acc
214 ;;
215
216 let meets left right =
217   let u = UriManager.uri_of_string "cic:/foo.con" in
218   min [] (List.map fst (intersect (grow [left,u]) (grow [right,u])))
219 ;;
220
221 (* EOF *)