]> matita.cs.unibo.it Git - helm.git/blob - helm/software/matita/applyTransformation.ml
9f5f5c311f7196441db3e6626416c86432766814
[helm.git] / helm / software / matita / applyTransformation.ml
1 (* Copyright (C) 2000-2002, 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 (***************************************************************************)
27 (*                                                                         *)
28 (*                               PROJECT HELM                              *)
29 (*                                                                         *)
30 (*                   Andrea Asperti <asperti@cs.unibo.it>                  *)
31 (*                                21/11/2003                               *)
32 (*                                                                         *)
33 (*                                                                         *)
34 (***************************************************************************)
35
36 (* $Id$ *)
37
38 module UM = UriManager
39 module C  = Cic
40 module Un = CicUniv
41 module E  = CicEnvironment
42 module TC = CicTypeChecker
43 module G  = GrafiteAst
44 module GE = GrafiteEngine
45 module LS = LibrarySync
46 module Ds = CicDischarge
47 module PO = ProceduralOptimizer
48 module N = CicNotationPt
49
50 let mpres_document pres_box =
51   Xml.add_xml_declaration (CicNotationPres.print_box pres_box)
52
53 let mml_of_cic_sequent metasenv sequent =
54   let unsh_sequent,(asequent,ids_to_terms,
55     ids_to_father_ids,ids_to_inner_sorts,ids_to_hypotheses)
56   =
57     Cic2acic.asequent_of_sequent metasenv sequent
58   in
59   let content_sequent = Acic2content.map_sequent asequent in 
60   let pres_sequent = 
61    Sequent2pres.sequent2pres ~ids_to_inner_sorts content_sequent in
62   let xmlpres = mpres_document pres_sequent in
63   (Xml2Gdome.document_of_xml DomMisc.domImpl xmlpres,
64    unsh_sequent,
65    (asequent,
66     (ids_to_terms,ids_to_father_ids,ids_to_hypotheses,ids_to_inner_sorts)))
67
68 let nmml_of_cic_sequent metasenv subst sequent =
69   let content_sequent = NTermCicContent.nmap_sequent ~subst sequent in 
70   let pres_sequent = 
71    Sequent2pres.nsequent2pres subst content_sequent in
72   let xmlpres = mpres_document pres_sequent in
73    Xml2Gdome.document_of_xml DomMisc.domImpl xmlpres
74
75 let mml_of_cic_object obj =
76   let (annobj, ids_to_terms, ids_to_father_ids, ids_to_inner_sorts,
77     ids_to_inner_types, ids_to_conjectures, ids_to_hypotheses)
78   =
79     Cic2acic.acic_object_of_cic_object obj
80   in
81   let content = 
82     Acic2content.annobj2content ~ids_to_inner_sorts ~ids_to_inner_types annobj
83   in
84   let pres = Content2pres.content2pres ~ids_to_inner_sorts content in
85   let xmlpres = mpres_document pres in
86   let mathml = Xml2Gdome.document_of_xml DomMisc.domImpl xmlpres in
87   (mathml,(annobj,
88    (ids_to_terms, ids_to_father_ids, ids_to_conjectures, ids_to_hypotheses,
89   ids_to_inner_sorts,ids_to_inner_types)))
90
91 let txt_of_cic_sequent ~map_unicode_to_tex size metasenv sequent =
92   let unsh_sequent,(asequent,ids_to_terms,
93     ids_to_father_ids,ids_to_inner_sorts,ids_to_hypotheses)
94   =
95     Cic2acic.asequent_of_sequent metasenv sequent
96   in
97   let content_sequent = Acic2content.map_sequent asequent in 
98   let pres_sequent = 
99    CicNotationPres.mpres_of_box
100     (Sequent2pres.sequent2pres ~ids_to_inner_sorts content_sequent)
101   in
102   BoxPp.render_to_string ~map_unicode_to_tex
103     (function x::_ -> x | _ -> assert false) size pres_sequent
104
105 let txt_of_cic_sequent_conclusion ~map_unicode_to_tex ~output_type size
106  metasenv sequent =
107   let _,(asequent,_,_,ids_to_inner_sorts,_) = 
108     Cic2acic.asequent_of_sequent metasenv sequent 
109   in
110   let _,_,_,t = Acic2content.map_sequent asequent in 
111   let t, ids_to_uris =
112    TermAcicContent.ast_of_acic ~output_type ids_to_inner_sorts t in
113   let t = TermContentPres.pp_ast t in
114   let t = CicNotationPres.render ids_to_uris t in
115   BoxPp.render_to_string ~map_unicode_to_tex
116     (function x::_ -> x | _ -> assert false) size t
117
118 let txt_of_cic_term ~map_unicode_to_tex size metasenv context t = 
119  let fake_sequent = (-1,context,t) in
120   txt_of_cic_sequent_conclusion ~map_unicode_to_tex ~output_type:`Term size
121    metasenv fake_sequent 
122 ;;
123
124 ignore (
125  CicMetaSubst.set_ppterm_in_context
126   (fun ~metasenv subst term context ->
127     try
128      let context' = CicMetaSubst.apply_subst_context subst context in
129      let metasenv = CicMetaSubst.apply_subst_metasenv subst metasenv in
130      let term' = CicMetaSubst.apply_subst subst term in
131      let res =
132       txt_of_cic_term
133        ~map_unicode_to_tex:(Helm_registry.get_bool "matita.paste_unicode_as_tex")
134        30 metasenv context' term' in
135       if String.contains res '\n' then
136        "\n" ^ res ^ "\n"
137       else
138        res
139     with
140        Sys.Break as exn -> raise exn
141      | exn ->
142         "[[ Exception raised during pretty-printing: " ^
143          (try
144            Printexc.to_string exn
145           with
146              Sys.Break as exn -> raise exn
147            | _ -> "<<exception raised pretty-printing the exception>>"
148          ) ^ " ]] " ^
149         (CicMetaSubst.use_low_level_ppterm_in_context := true;
150          try
151           let res =
152            CicMetaSubst.ppterm_in_context ~metasenv subst term context
153           in
154            CicMetaSubst.use_low_level_ppterm_in_context := false;
155            res
156          with
157           exc -> 
158            CicMetaSubst.use_low_level_ppterm_in_context := false;
159            raise exc))
160 );;
161
162 (****************************************************************************)
163 (* txt_of_cic_object: IMPROVE ME *)
164
165 let remove_closed_substs s =
166     Pcre.replace ~pat:"{...}" ~templ:"" s
167
168 let term2pres ~map_unicode_to_tex n ids_to_inner_sorts annterm = 
169    let ast, ids_to_uris = 
170     TermAcicContent.ast_of_acic ~output_type:`Term ids_to_inner_sorts annterm in
171    let bobj =
172       CicNotationPres.box_of_mpres (
173          CicNotationPres.render ~prec:90 ids_to_uris 
174             (TermContentPres.pp_ast ast)) in
175    let render = function _::x::_ -> x | _ -> assert false in
176    let mpres = CicNotationPres.mpres_of_box bobj in
177    let s = BoxPp.render_to_string ~map_unicode_to_tex render n mpres in
178    remove_closed_substs s
179
180 let enable_notations = function
181    | true -> 
182       CicNotation.set_active_notations
183          (List.map fst (CicNotation.get_all_notations ()))
184    | false ->
185       CicNotation.set_active_notations []
186
187 let txt_of_cic_object 
188  ~map_unicode_to_tex ?skip_thm_and_qed ?skip_initial_lambdas
189  n style ?flavour prefix obj 
190 =
191   let get_aobj obj = 
192      try   
193         let aobj,_,_,ids_to_inner_sorts,ids_to_inner_types,_,_ =
194             Cic2acic.acic_object_of_cic_object obj
195         in
196         aobj, ids_to_inner_sorts, ids_to_inner_types
197      with 
198         | E.Object_not_found uri -> 
199              let msg = "txt_of_cic_object: object not found: " ^ UM.string_of_uri uri in
200              failwith msg
201         | e                     ->
202              let msg = "txt_of_cic_object: " ^ Printexc.to_string e in
203              failwith msg
204   in
205   match style with
206      | G.Declarative      ->
207         let aobj, ids_to_inner_sorts, ids_to_inner_types = get_aobj obj in
208         let cobj = 
209           Acic2content.annobj2content 
210             ids_to_inner_sorts ids_to_inner_types aobj 
211         in
212         let bobj = 
213           Content2pres.content2pres 
214             ?skip_initial_lambdas ?skip_thm_and_qed ~ids_to_inner_sorts cobj 
215         in
216         remove_closed_substs (
217            BoxPp.render_to_string ~map_unicode_to_tex
218             (function _::x::_ -> x | _ -> assert false) n
219             (CicNotationPres.mpres_of_box bobj)
220         ^ "\n\n" )
221      | G.Procedural depth ->
222 (*     
223         PO.debug := true;
224         PO.critical := false;
225         Acic2Procedural.tex_formatter := Some Format.std_formatter;     
226         let _ = ProceduralTeX.tex_of_obj Format.std_formatter obj in
227 *)      
228         let obj, info = PO.optimize_obj obj in
229 (*      
230         let _ = ProceduralTeX.tex_of_obj Format.std_formatter obj in
231 *)      
232         let aobj, ids_to_inner_sorts, ids_to_inner_types = get_aobj obj in
233         let term_pp = term2pres ~map_unicode_to_tex (n - 8) ids_to_inner_sorts in
234         let lazy_term_pp = term_pp in
235         let obj_pp = CicNotationPp.pp_obj term_pp in
236         let stm_pp =          
237            GrafiteAstPp.pp_statement
238               ~map_unicode_to_tex ~term_pp ~lazy_term_pp ~obj_pp
239         in
240         let aux = function
241            | G.Executable (_, G.Command (_, G.Obj (_, N.Inductive _))) as stm
242                  -> 
243               enable_notations false;
244               let str = stm_pp stm in enable_notations true; str
245 (* FG: we disable notation for Inductive to avoid recursive notation *) 
246            | stm -> stm_pp stm 
247         in
248         let script = 
249            Acic2Procedural.procedural_of_acic_object 
250               ~ids_to_inner_sorts ~ids_to_inner_types ~info
251               ?depth ?flavour prefix aobj 
252   in
253         String.concat "" (List.map aux script) ^ "\n\n"
254
255 let cic_prefix = Str.regexp_string "cic:/"
256 let matita_prefix = Str.regexp_string "cic:/matita/"
257 let suffixes = [".ind"; "_rec.con"; "_rect.con"; "_ind.con"; ".con"]
258
259 let replacements = 
260    let map s = String.length s, s, Str.regexp_string s, "_discharged" ^ s in 
261    List.map map suffixes
262
263 let replacement (ok, u) (l, s, x, t) =
264    if ok then ok, u else
265    if Str.last_chars u l = s then true, Str.replace_first x t u else ok, u
266
267 let discharge_uri style uri =
268    let template = match style with
269       | G.Declarative  -> "cic:/matita/declarative/"   
270       | G.Procedural _ -> "cic:/matita/procedural/"
271    in
272    let s = UM.string_of_uri uri in
273    if Str.string_match matita_prefix s 0 then uri else
274    let s = Str.replace_first cic_prefix template s in
275    let _, s = List.fold_left replacement (false, s) replacements in 
276    UM.uri_of_string s
277
278 let discharge_name s = s ^ "_discharged"
279
280 let txt_of_inline_uri ~map_unicode_to_tex style ?flavour prefix suri =
281 (*   
282    Ds.debug := true;
283 *)
284    let print_exc = function
285       | ProofEngineHelpers.Bad_pattern s as e ->
286            Printexc.to_string e ^ " " ^ Lazy.force s
287       | e -> Printexc.to_string e
288    in
289    let dbd = LibraryDb.instance () in   
290    let sorted_uris = MetadataDeps.sorted_uris_of_baseuri ~dbd suri in
291    let error uri e =
292       let msg  = 
293          Printf.sprintf 
294             "ERROR IN THE GENERATION OF %s\nEXCEPTION: %s" 
295             (UM.string_of_uri uri) e
296       in
297       Printf.eprintf "%s\n" msg;
298       GrafiteTypes.command_error msg
299    in
300    let map uri =
301       Librarian.time_stamp "AT: BEGIN MAP";
302       try
303 (* FG: for now the explicit variables must be discharged *)
304         let do_it obj =
305            let r = txt_of_cic_object ~map_unicode_to_tex 78 style ?flavour prefix obj in
306            Librarian.time_stamp "AT: END MAP  "; r
307         in
308         let obj, real = 
309            let s = UM.string_of_uri uri in
310            if Str.string_match matita_prefix s 0 then begin
311               Librarian.time_stamp "AT: GETTING OBJECT";
312               let obj, _ = E.get_obj Un.default_ugraph uri in
313               Librarian.time_stamp "AT: DONE          ";
314               obj, true
315            end else
316               Ds.discharge_uri discharge_name (discharge_uri style) uri
317         in
318         if real then do_it obj else
319         let newuri = discharge_uri style uri in
320         let _lemmas = LS.add_obj ~pack_coercion_obj:CicRefine.pack_coercion_obj newuri obj in
321         do_it obj
322       with
323          | TC.TypeCheckerFailure s ->
324             error uri ("failure  : " ^ Lazy.force s)
325          | TC.AssertFailure s      ->
326             error uri ("assert   : " ^ Lazy.force s)
327          | E.Object_not_found u    ->
328             error uri ("not found: " ^ UM.string_of_uri u)
329          | e                       -> error uri (print_exc e)
330    in
331    String.concat "" (List.map map sorted_uris)
332
333 let txt_of_inline_macro ~map_unicode_to_tex style ?flavour prefix name =
334    let suri = 
335       if Librarian.is_uri name then name else
336       let include_paths = 
337          Helm_registry.get_list Helm_registry.string "matita.includes"
338       in
339       let _, baseuri, _, _ = 
340          Librarian.baseuri_of_script ~include_paths name
341       in
342       baseuri ^ "/"
343    in
344    txt_of_inline_uri ~map_unicode_to_tex style ?flavour prefix suri
345
346 (****************************************************************************)
347 (* procedural_txt_of_cic_term *)
348
349 let procedural_txt_of_cic_term ~map_unicode_to_tex n ?depth context term =
350   let term, _info = PO.optimize_term context term in
351   let annterm, ids_to_inner_sorts, ids_to_inner_types = 
352      try Cic2acic.acic_term_of_cic_term context term
353      with e -> 
354         let msg = "procedural_txt_of_cic_term: " ^ Printexc.to_string e in
355         failwith msg
356   in
357   let term_pp = term2pres ~map_unicode_to_tex (n - 8) ids_to_inner_sorts in
358   let lazy_term_pp = term_pp in
359   let obj_pp = CicNotationPp.pp_obj term_pp in
360   let aux = GrafiteAstPp.pp_statement
361      ~map_unicode_to_tex ~term_pp ~lazy_term_pp ~obj_pp in
362   let script = 
363      Acic2Procedural.procedural_of_acic_term 
364         ~ids_to_inner_sorts ~ids_to_inner_types ?depth "" context annterm 
365   in
366   String.concat "" (List.map aux script)
367 ;;
368
369 (****************************************************************************)
370
371 let txt_of_macro ~map_unicode_to_tex metasenv context m =
372    GrafiteAstPp.pp_macro
373      ~term_pp:(txt_of_cic_term ~map_unicode_to_tex 80 metasenv context) 
374      ~lazy_term_pp:(fun (f : Cic.lazy_term) ->
375         let t,metasenv,_ = f context metasenv CicUniv.empty_ugraph in
376         txt_of_cic_term ~map_unicode_to_tex 80 metasenv context t)
377      m
378 ;;
379
380