1 (* Copyright (C) 2000-2002, 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/.
26 (***************************************************************************)
30 (* Andrea Asperti <asperti@cs.unibo.it> *)
34 (***************************************************************************)
38 module UM = UriManager
41 module E = CicEnvironment
42 module TC = CicTypeChecker
44 module GE = GrafiteEngine
45 module LS = LibrarySync
46 module Ds = CicDischarge
47 module PO = ProceduralOptimizer
48 module N = CicNotationPt
49 module A2P = Acic2Procedural
51 let mpres_document pres_box =
52 Xml.add_xml_declaration (CicNotationPres.print_box pres_box)
54 let mml_of_cic_sequent metasenv sequent =
55 let unsh_sequent,(asequent,ids_to_terms,
56 ids_to_father_ids,ids_to_inner_sorts,ids_to_hypotheses)
58 Cic2acic.asequent_of_sequent metasenv sequent
60 let content_sequent = Acic2content.map_sequent asequent in
62 Sequent2pres.sequent2pres ~ids_to_inner_sorts content_sequent in
63 let xmlpres = mpres_document pres_sequent in
64 (Xml2Gdome.document_of_xml DomMisc.domImpl xmlpres,
67 (ids_to_terms,ids_to_father_ids,ids_to_hypotheses,ids_to_inner_sorts)))
69 let nmml_of_cic_sequent status metasenv subst sequent =
70 let content_sequent,ids_to_refs =
71 NTermCicContent.nmap_sequent status ~metasenv ~subst sequent in
73 Sequent2pres.nsequent2pres ids_to_refs subst content_sequent in
74 let xmlpres = mpres_document pres_sequent in
75 Xml2Gdome.document_of_xml DomMisc.domImpl xmlpres
77 let mml_of_cic_object obj =
78 let (annobj, ids_to_terms, ids_to_father_ids, ids_to_inner_sorts,
79 ids_to_inner_types, ids_to_conjectures, ids_to_hypotheses)
81 Cic2acic.acic_object_of_cic_object obj
84 Acic2content.annobj2content ~ids_to_inner_sorts ~ids_to_inner_types annobj
86 let pres = Content2pres.content2pres ~ids_to_inner_sorts content in
87 let xmlpres = mpres_document pres in
88 let mathml = Xml2Gdome.document_of_xml DomMisc.domImpl xmlpres in
90 (ids_to_terms, ids_to_father_ids, ids_to_conjectures, ids_to_hypotheses,
91 ids_to_inner_sorts,ids_to_inner_types)))
93 let nmml_of_cic_object status obj =
94 let cobj,ids_to_nrefs = NTermCicContent.nmap_obj status obj in
95 let pres_sequent = Content2pres.ncontent2pres ~ids_to_nrefs cobj in
96 let xmlpres = mpres_document pres_sequent in
97 Xml2Gdome.document_of_xml DomMisc.domImpl xmlpres
100 let txt_of_cic_sequent ~map_unicode_to_tex size metasenv sequent =
101 let unsh_sequent,(asequent,ids_to_terms,
102 ids_to_father_ids,ids_to_inner_sorts,ids_to_hypotheses)
104 Cic2acic.asequent_of_sequent metasenv sequent
106 let content_sequent = Acic2content.map_sequent asequent in
108 CicNotationPres.mpres_of_box
109 (Sequent2pres.sequent2pres ~ids_to_inner_sorts content_sequent)
111 BoxPp.render_to_string ~map_unicode_to_tex
112 (function x::_ -> x | _ -> assert false) size pres_sequent
114 let txt_of_cic_sequent_conclusion ~map_unicode_to_tex ~output_type size
116 let _,(asequent,_,_,ids_to_inner_sorts,_) =
117 Cic2acic.asequent_of_sequent metasenv sequent
119 let _,_,_,t = Acic2content.map_sequent asequent in
121 TermAcicContent.ast_of_acic ~output_type ids_to_inner_sorts t in
122 let t = TermContentPres.pp_ast t in
124 CicNotationPres.render ~lookup_uri:(CicNotationPres.lookup_uri ids_to_uris) t
126 BoxPp.render_to_string ~map_unicode_to_tex
127 (function x::_ -> x | _ -> assert false) size t
129 let txt_of_cic_term ~map_unicode_to_tex size metasenv context t =
130 let fake_sequent = (-1,context,t) in
131 txt_of_cic_sequent_conclusion ~map_unicode_to_tex ~output_type:`Term size
132 metasenv fake_sequent
136 CicMetaSubst.set_ppterm_in_context
137 (fun ~metasenv subst term context ->
139 let context' = CicMetaSubst.apply_subst_context subst context in
140 let metasenv = CicMetaSubst.apply_subst_metasenv subst metasenv in
141 let term' = CicMetaSubst.apply_subst subst term in
144 ~map_unicode_to_tex:(Helm_registry.get_bool "matita.paste_unicode_as_tex")
145 30 metasenv context' term' in
146 if String.contains res '\n' then
151 Sys.Break as exn -> raise exn
153 "[[ Exception raised during pretty-printing: " ^
155 Printexc.to_string exn
157 Sys.Break as exn -> raise exn
158 | _ -> "<<exception raised pretty-printing the exception>>"
160 (CicMetaSubst.use_low_level_ppterm_in_context := true;
163 CicMetaSubst.ppterm_in_context ~metasenv subst term context
165 CicMetaSubst.use_low_level_ppterm_in_context := false;
169 CicMetaSubst.use_low_level_ppterm_in_context := false;
173 (****************************************************************************)
174 (* txt_of_cic_object: IMPROVE ME *)
176 let remove_closed_substs s =
177 Pcre.replace ~pat:"{...}" ~templ:"" s
179 let term2pres ~map_unicode_to_tex n ids_to_inner_sorts annterm =
180 let ast, ids_to_uris =
181 TermAcicContent.ast_of_acic ~output_type:`Term ids_to_inner_sorts annterm in
183 CicNotationPres.box_of_mpres (
184 CicNotationPres.render ~prec:90
185 ~lookup_uri:(CicNotationPres.lookup_uri ids_to_uris)
186 (TermContentPres.pp_ast ast)) in
187 let render = function _::x::_ -> x | _ -> assert false in
188 let mpres = CicNotationPres.mpres_of_box bobj in
189 let s = BoxPp.render_to_string ~map_unicode_to_tex render n mpres in
190 remove_closed_substs s
192 let enable_notations = function
194 CicNotation.set_active_notations
195 (List.map fst (CicNotation.get_all_notations ()))
197 CicNotation.set_active_notations []
199 let txt_of_cic_object
200 ~map_unicode_to_tex ?skip_thm_and_qed ?skip_initial_lambdas n params obj
204 let aobj,_,_,ids_to_inner_sorts,ids_to_inner_types,_,_ =
205 Cic2acic.acic_object_of_cic_object obj
207 aobj, ids_to_inner_sorts, ids_to_inner_types
209 | E.Object_not_found uri ->
210 let msg = "txt_of_cic_object: object not found: " ^ UM.string_of_uri uri in
213 let msg = "txt_of_cic_object: " ^ Printexc.to_string e in
216 if List.mem G.IPProcedural params then begin
218 Procedural2.debug := A2P.is_debug 1 params;
219 PO.debug := A2P.is_debug 2 params;
221 PO.critical := false;
222 A2P.tex_formatter := Some Format.std_formatter;
223 let _ = ProceduralTeX.tex_of_obj Format.std_formatter obj in
225 let obj, info = PO.optimize_obj obj in
227 let _ = ProceduralTeX.tex_of_obj Format.std_formatter obj in
229 let aobj, ids_to_inner_sorts, ids_to_inner_types = get_aobj obj in
230 let term_pp = term2pres ~map_unicode_to_tex (n - 8) ids_to_inner_sorts in
231 let lazy_term_pp = term_pp in
232 let obj_pp = CicNotationPp.pp_obj term_pp in
234 GrafiteAstPp.pp_statement
235 ~map_unicode_to_tex ~term_pp ~lazy_term_pp ~obj_pp
238 | G.Executable (_, G.Command (_, G.Obj (_, N.Inductive _)))
239 | G.Executable (_, G.Command (_, G.Obj (_, N.Record _))) as stm
241 let hc = !Acic2content.hide_coercions in
242 if List.mem G.IPCoercions params then
243 Acic2content.hide_coercions := false;
244 enable_notations false;
245 let str = stm_pp stm in
246 enable_notations true;
247 Acic2content.hide_coercions := hc;
249 (* FG: we disable notation for inductive types to avoid recursive notation *)
250 | G.Executable (_, G.Tactic _) as stm ->
251 let hc = !Acic2content.hide_coercions in
252 Acic2content.hide_coercions := false;
253 let str = stm_pp stm in
254 Acic2content.hide_coercions := hc;
256 (* FG: we show coercion because the reconstruction is not aware of them *)
258 let hc = !Acic2content.hide_coercions in
259 if List.mem G.IPCoercions params then
260 Acic2content.hide_coercions := false;
261 let str = stm_pp stm in
262 Acic2content.hide_coercions := hc;
266 A2P.procedural_of_acic_object
267 ~ids_to_inner_sorts ~ids_to_inner_types ~info params aobj
269 String.concat "" (List.map aux script) ^ "\n\n"
271 let aobj, ids_to_inner_sorts, ids_to_inner_types = get_aobj obj in
273 Acic2content.annobj2content ids_to_inner_sorts ids_to_inner_types aobj
276 Content2pres.content2pres
277 ?skip_initial_lambdas ?skip_thm_and_qed ~ids_to_inner_sorts cobj
279 remove_closed_substs (
280 BoxPp.render_to_string ~map_unicode_to_tex
281 (function _::x::_ -> x | _ -> assert false) n
282 (CicNotationPres.mpres_of_box bobj)
286 let cic_prefix = Str.regexp_string "cic:/"
287 let matita_prefix = Str.regexp_string "cic:/matita/"
288 let suffixes = [".ind"; "_rec.con"; "_rect.con"; "_ind.con"; ".con"]
291 let map s = String.length s, s, Str.regexp_string s, "_discharged" ^ s in
292 List.map map suffixes
294 let replacement (ok, u) (l, s, x, t) =
295 if ok then ok, u else
296 if Str.last_chars u l = s then true, Str.replace_first x t u else ok, u
298 let discharge_uri params uri =
300 if List.mem G.IPProcedural params then "cic:/matita/procedural/"
301 else "cic:/matita/declarative/"
303 let s = UM.string_of_uri uri in
304 if Str.string_match matita_prefix s 0 then uri else
305 let s = Str.replace_first cic_prefix template s in
306 let _, s = List.fold_left replacement (false, s) replacements in
309 let discharge_name s = s ^ "_discharged"
311 let txt_of_inline_uri ~map_unicode_to_tex params suri =
315 let print_exc = function
316 | ProofEngineHelpers.Bad_pattern s as e ->
317 Printexc.to_string e ^ " " ^ Lazy.force s
318 | e -> Printexc.to_string e
320 let dbd = LibraryDb.instance () in
321 let sorted_uris = MetadataDeps.sorted_uris_of_baseuri ~dbd suri in
325 "ERROR IN THE GENERATION OF %s\nEXCEPTION: %s"
326 (UM.string_of_uri uri) e
328 Printf.eprintf "%s\n" msg;
329 GrafiteTypes.command_error msg
332 Librarian.time_stamp "AT: BEGIN MAP";
334 (* FG: for now the explicit variables must be discharged *)
336 let r = txt_of_cic_object ~map_unicode_to_tex 78 params obj in
337 Librarian.time_stamp "AT: END MAP "; r
340 let s = UM.string_of_uri uri in
341 if Str.string_match matita_prefix s 0 then begin
342 Librarian.time_stamp "AT: GETTING OBJECT";
343 let obj, _ = E.get_obj Un.default_ugraph uri in
344 Librarian.time_stamp "AT: DONE ";
347 Ds.discharge_uri discharge_name (discharge_uri params) uri
349 if real then do_it obj else
350 let newuri = discharge_uri params uri in
351 let _lemmas = LS.add_obj ~pack_coercion_obj:CicRefine.pack_coercion_obj newuri obj in
354 | TC.TypeCheckerFailure s ->
355 error uri ("failure : " ^ Lazy.force s)
356 | TC.AssertFailure s ->
357 error uri ("assert : " ^ Lazy.force s)
358 | E.Object_not_found u ->
359 error uri ("not found: " ^ UM.string_of_uri u)
360 | e -> error uri (print_exc e)
362 String.concat "" (List.map map sorted_uris)
364 let txt_of_inline_macro ~map_unicode_to_tex params name =
366 if Librarian.is_uri name then name else
368 Helm_registry.get_list Helm_registry.string "matita.includes"
370 let _, baseuri, _, _ =
371 Librarian.baseuri_of_script ~include_paths name
375 txt_of_inline_uri ~map_unicode_to_tex params suri
377 (****************************************************************************)
378 (* procedural_txt_of_cic_term *)
380 let procedural_txt_of_cic_term ~map_unicode_to_tex n params context term =
381 let term, _info = PO.optimize_term context term in
382 let annterm, ids_to_inner_sorts, ids_to_inner_types =
383 try Cic2acic.acic_term_of_cic_term context term
385 let msg = "procedural_txt_of_cic_term: " ^ Printexc.to_string e in
388 let term_pp = term2pres ~map_unicode_to_tex (n - 8) ids_to_inner_sorts in
389 let lazy_term_pp = term_pp in
390 let obj_pp = CicNotationPp.pp_obj term_pp in
391 let aux = GrafiteAstPp.pp_statement
392 ~map_unicode_to_tex ~term_pp ~lazy_term_pp ~obj_pp in
394 A2P.procedural_of_acic_term
395 ~ids_to_inner_sorts ~ids_to_inner_types params context annterm
397 String.concat "" (List.map aux script)
400 (****************************************************************************)
402 let txt_of_macro ~map_unicode_to_tex metasenv context m =
403 GrafiteAstPp.pp_macro
404 ~term_pp:(txt_of_cic_term ~map_unicode_to_tex 80 metasenv context)
405 ~lazy_term_pp:(fun (f : Cic.lazy_term) ->
406 let t,metasenv,_ = f context metasenv CicUniv.empty_ugraph in
407 txt_of_cic_term ~map_unicode_to_tex 80 metasenv context t)