1 (* Copyright (C) 2000, 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/.
30 type coercion_search_result =
31 | SomeCoercion of Cic.term list
34 | NotHandled of string Lazy.t
37 let debug_print s = if debug then prerr_endline (Lazy.force s) else ()
39 (* searches a coercion fron src to tgt in the !coercions list *)
40 let look_for_coercion' src tgt =
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
49 with Invalid_argument _ -> assert false (* all coercions have an uri *)
51 let rec mk_implicits = function
53 | n -> Cic.Implicit None :: mk_implicits (n-1)
58 (fun (s,t) -> CoercDb.eq_carr s src && CoercDb.eq_carr t tgt) in
64 (sprintf ":-( coercion non trovata da %s a %s"
65 (CoercDb.name_of_carr src)
66 (CoercDb.name_of_carr tgt)));
70 sprintf ":-) TROVATE %d coercion(s) da %s a %s"
72 (CoercDb.name_of_carr src)
73 (CoercDb.name_of_carr tgt)));
79 let cl = List.map CicUtil.term_of_uri ul in
81 let _,tgtcarl = List.split (List.map CoercDb.get_carr ul) in
82 List.map (function CoercDb.Fun i -> i | _ -> 0) tgtcarl
84 let arityl = List.map arity_of cl in
87 (fun arity fn_arity ->
88 mk_implicits (arity - 1 - fn_arity)) arityl funclass_arityl
95 | _ -> Cic.Appl (c::args))
100 | CoercDb.EqCarrNotImplemented s -> NotHandled s
101 | CoercDb.EqCarrOnNonMetaClosed -> NotMetaClosed
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
109 let is_a_coercion t =
111 let uri = CicUtil.uri_of_term t in
112 CoercDb.is_a_coercion uri
113 with Invalid_argument _ -> false
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 *)
121 let is_a_coercion_to_funclass t =
123 let uri = CicUtil.uri_of_term t in
124 match snd (CoercDb.get_carr uri) with
125 | CoercDb.Fun i -> Some i
127 with Invalid_argument _ -> None
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
140 Pp.node (CoercDb.name_of_carr carr)
141 ~attrs:["href", UriManager.string_of_uri uri] fmt in
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
150 Pp.edge src_name tgt_name
151 ~attrs:[ "label", UriManager.name_of_uri c;
152 "href", UriManager.string_of_uri c ]
164 | Cic.Appl (he::_) -> CicUtil.uri_of_term he
165 | _ -> CicUtil.uri_of_term t
167 match CicEnvironment.get_obj CicUniv.empty_ugraph uri with
168 | Cic.Constant (_,_, _, _, attrs),_ ->
169 List.exists (function `Class (`Coercion _) -> true | _ -> false) attrs
171 with Invalid_argument _ -> false