]> matita.cs.unibo.it Git - helm.git/blob - matita/matita/applyTransformation.ml
cic_unification 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 (****************************************************************************)
161 (* txt_of_cic_object: IMPROVE ME *)
162
163 let remove_closed_substs s =
164     Pcre.replace ~pat:"{...}" ~templ:"" s
165
166 let term2pres ~map_unicode_to_tex n ids_to_inner_sorts annterm = 
167    let ast, ids_to_uris = 
168     TermAcicContent.ast_of_acic ~output_type:`Term ids_to_inner_sorts annterm in
169    let bobj =
170     CicNotationPres.box_of_mpres (
171      CicNotationPres.render ~prec:90
172       ~lookup_uri:(CicNotationPres.lookup_uri ids_to_uris)
173       (TermContentPres.pp_ast ast)) in
174    let render = function _::x::_ -> x | _ -> assert false in
175    let mpres = CicNotationPres.mpres_of_box bobj in
176    let s = BoxPp.render_to_string ~map_unicode_to_tex render n mpres in
177    remove_closed_substs s
178
179 let enable_notations = function
180    | true -> 
181       CicNotation.set_active_notations
182          (List.map fst (CicNotation.get_all_notations ()))
183    | false ->
184       CicNotation.set_active_notations []
185
186 let txt_of_cic_object_all
187  ~map_unicode_to_tex ?skip_thm_and_qed ?skip_initial_lambdas n params obj 
188 =
189   let get_aobj obj = 
190      try   
191         let
192           aobj,ids_to_terms,ids_to_father_ids,ids_to_inner_sorts,ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses =
193             Cic2acic.acic_object_of_cic_object obj
194         in
195         aobj, ids_to_terms, ids_to_father_ids, ids_to_inner_sorts,
196         ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses
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   (*MATITA1.0
206   if List.mem G.IPProcedural params then begin
207
208      Procedural2.debug := A2P.is_debug 1 params;
209      PO.debug := A2P.is_debug 2 params;
210 (*     
211      PO.critical := false;
212      A2P.tex_formatter := Some Format.std_formatter;    
213      let _ = ProceduralTeX.tex_of_obj Format.std_formatter obj in
214 *)      
215      let obj, info = PO.optimize_obj obj in
216 (*      
217      let _ = ProceduralTeX.tex_of_obj Format.std_formatter obj in
218 *)      
219      let  aobj, ids_to_terms, ids_to_father_ids, ids_to_inner_sorts,
220        ids_to_inner_types,ids_to_conjectures,ids_to_hypothesis = get_aobj obj in
221      let term_pp = term2pres ~map_unicode_to_tex (n - 8) ids_to_inner_sorts in
222      let lazy_term_pp = term_pp in
223      let obj_pp = CicNotationPp.pp_obj term_pp in
224      let stm_pp =             
225         GrafiteAstPp.pp_statement
226            ~map_unicode_to_tex ~term_pp ~lazy_term_pp ~obj_pp
227      in
228      let aux = function
229         | G.Executable (_, G.Command (_, G.Obj (_, N.Inductive _)))
230         | G.Executable (_, G.Command (_, G.Obj (_, N.Record _))) as stm
231               ->           
232            let hc = !Acic2content.hide_coercions in
233            if List.mem G.IPCoercions params then 
234               Acic2content.hide_coercions := false;
235            enable_notations false;
236            let str = stm_pp stm in 
237            enable_notations true;
238            Acic2content.hide_coercions := hc;
239            str
240 (* FG: we disable notation for inductive types to avoid recursive notation *) 
241         | G.Executable (_, G.Tactic _) as stm -> 
242            let hc = !Acic2content.hide_coercions in
243            Acic2content.hide_coercions := false;
244            let str = stm_pp stm in
245            Acic2content.hide_coercions := hc;
246            str
247 (* FG: we show coercion because the reconstruction is not aware of them *)
248         | stm -> 
249            let hc = !Acic2content.hide_coercions in
250            if List.mem G.IPCoercions params then 
251               Acic2content.hide_coercions := false;
252            let str = stm_pp stm in
253            Acic2content.hide_coercions := hc;
254            str
255      in
256      let script = 
257         A2P.procedural_of_acic_object 
258            ~ids_to_inner_sorts ~ids_to_inner_types ~info params aobj 
259      in
260      String.concat "" (List.map aux script) ^ "\n\n"
261   end else *)
262      let  aobj, ids_to_terms, ids_to_father_ids, ids_to_inner_sorts,
263        ids_to_inner_types,ids_to_conjectures,ids_to_hypotheses = get_aobj obj in
264      let cobj = 
265        Acic2content.annobj2content ids_to_inner_sorts ids_to_inner_types aobj 
266      in
267      let bobj = 
268         Content2pres.content2pres 
269            ?skip_initial_lambdas ?skip_thm_and_qed ~ids_to_inner_sorts cobj 
270      in
271      let txt =
272       remove_closed_substs (
273         BoxPp.render_to_string ~map_unicode_to_tex
274            (function _::x::_ -> x | _ -> assert false) n
275            (CicNotationPres.mpres_of_box bobj)
276         ^ "\n\n"
277       )
278      in
279       (txt,(aobj,
280        (ids_to_terms, ids_to_father_ids, ids_to_conjectures, ids_to_hypotheses,
281       ids_to_inner_sorts,ids_to_inner_types)))
282
283 let txt_of_cic_object
284  ~map_unicode_to_tex ?skip_thm_and_qed ?skip_initial_lambdas n params obj 
285 =
286  let txt,_ = txt_of_cic_object_all
287   ~map_unicode_to_tex ?skip_thm_and_qed ?skip_initial_lambdas n params obj
288  in txt
289
290 let cic_prefix = Str.regexp_string "cic:/"
291 let matita_prefix = Str.regexp_string "cic:/matita/"
292 let suffixes = [".ind"; "_rec.con"; "_rect.con"; "_ind.con"; ".con"]
293
294 let replacements = 
295    let map s = String.length s, s, Str.regexp_string s, "_discharged" ^ s in 
296    List.map map suffixes
297
298 let replacement (ok, u) (l, s, x, t) =
299    if ok then ok, u else
300    if Str.last_chars u l = s then true, Str.replace_first x t u else ok, u
301
302 let discharge_uri params uri =
303    let template = 
304       if List.mem G.IPProcedural params then "cic:/matita/procedural/"
305       else "cic:/matita/declarative/"
306    in
307    let s = UM.string_of_uri uri in
308    if Str.string_match matita_prefix s 0 then uri else
309    let s = Str.replace_first cic_prefix template s in
310    let _, s = List.fold_left replacement (false, s) replacements in 
311    UM.uri_of_string s
312
313 let discharge_name s = s ^ "_discharged"
314
315 let txt_of_macro ~map_unicode_to_tex metasenv context m =
316    GrafiteAstPp.pp_macro
317      ~term_pp:(txt_of_cic_term ~map_unicode_to_tex 80 metasenv context) 
318      ~lazy_term_pp:(fun (f : Cic.lazy_term) ->
319         let t,metasenv,_ = f context metasenv CicUniv.empty_ugraph in
320         txt_of_cic_term ~map_unicode_to_tex 80 metasenv context t)
321      m
322 ;;
323
324