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