]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic_transformations/applyTransformation.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / cic_transformations / applyTransformation.ml
index e1b36ea5c379697fbb191a85f1966622cb3f2d74..54402e0bc12372d17207fa16085b605521aaca06 100644 (file)
 (*                                                                         *)
 (***************************************************************************)
 
-let reload_stylesheets = ignore
-;;
-
 let mpres_document pres_box =
-  Ast2pres.add_xml_declaration
-    (Box.box2xml ~obj2xml:Mpresentation.print_mpres pres_box)
+  Xml.add_xml_declaration (CicNotationPres.print_box pres_box)
 
 let mml_of_cic_sequent metasenv sequent =
-  let asequent,ids_to_terms,
-    ids_to_father_ids,ids_to_inner_sorts,ids_to_hypotheses =
-    Cic2acic.asequent_of_sequent metasenv sequent in
+  let unsh_sequent,(asequent,ids_to_terms,
+    ids_to_father_ids,ids_to_inner_sorts,ids_to_hypotheses)
+  =
+    Cic2acic.asequent_of_sequent metasenv sequent
+  in
   let content_sequent = Cic2content.map_sequent asequent in 
   let pres_sequent = 
-    (Sequent2pres.sequent2pres ~ids_to_inner_sorts content_sequent) in
+    (Sequent2pres.sequent2pres ~ids_to_inner_sorts content_sequent)
+  in
   let xmlpres = mpres_document pres_sequent in
-  (*  Xml.pp_to_outchan xmlpres stdout ; *)
-  try
-    Xml2Gdome.document_of_xml Misc.domImpl xmlpres, (ids_to_terms,ids_to_father_ids,ids_to_hypotheses)
-  with
-      e ->
-       prerr_endline ("LUCA: eccezione in document_of_xml " ^ (Printexc.to_string e)) ;
-       raise e
-;;
-
-let mml_of_cic_object ~explode_all uri acic 
-  ids_to_inner_sorts ids_to_inner_types =
-  match acic with
-    Cic.ACurrentProof (id,idbody,n,conjectures,bo,ty,params) ->
-      let time1 = Sys.time () in
-      let content = 
-        Cic2content.annobj2content 
-          ~ids_to_inner_sorts ~ids_to_inner_types acic in
-      (* ContentPp.print_obj content; *)
-      let pres = Content2pres.content2pres ~ids_to_inner_sorts content in
-      let time2 = Sys.time () in
-      (* prerr_endline ("Fine trasformazione:" ^ (string_of_float (time2 -. time1))); *)
-      let xmlpres = mpres_document pres in
-      let time25 = Sys.time () in
-      (* alternative: printing to file 
-      prerr_endline ("FINE printing to stream:" ^ (string_of_float (time25 -. time2)));
-      Xml.pp xmlpres (Some "tmp");
-      let time3 = Sys.time () in
-      prerr_endline ("FINE valutazione e printing dello stream:" ^ (string_of_float (time3 -. time25))); 
-      end alternative *)
-      (try 
-         Xml2Gdome.document_of_xml Misc.domImpl xmlpres 
-       with (GdomeInit.DOMException (_,s)) as e ->
-              prerr_endline s; raise e)
-   | _ -> assert false
-;;
+  (Xml2Gdome.document_of_xml DomMisc.domImpl xmlpres,
+   unsh_sequent,
+   (asequent,
+    (ids_to_terms,ids_to_father_ids,ids_to_hypotheses,ids_to_inner_sorts)))
 
-(*
-let _ =
- Cexpr2pres_hashtbl.init Cexpr2pres.cexpr2pres Cexpr2pres.cexpr2pres_charcount
-;;
-*)
+let mml_of_cic_object obj =
+  let (annobj, ids_to_terms, ids_to_father_ids, ids_to_inner_sorts,
+    ids_to_inner_types, ids_to_conjectures, ids_to_hypotheses)
+  =
+    Cic2acic.acic_object_of_cic_object obj
+  in
+  let content = 
+    Cic2content.annobj2content ~ids_to_inner_sorts ~ids_to_inner_types annobj
+  in
+  let pres = Content2pres.content2pres ~ids_to_inner_sorts content in
+  let xmlpres = mpres_document pres in
+  let mathml = Xml2Gdome.document_of_xml DomMisc.domImpl xmlpres in
+  (mathml,(annobj,
+   (ids_to_terms, ids_to_father_ids, ids_to_conjectures, ids_to_hypotheses,
+  ids_to_inner_sorts,ids_to_inner_types)))