]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic/cicParser.ml
- use PxpHelmConf
[helm.git] / helm / ocaml / cic / cicParser.ml
index bf75243ec4300773479f1fe6b2c4dbbb356fee9e..5ad48b0799d5906f458d5123f211781648f15104 100644 (file)
 (*                                                                            *)
 (******************************************************************************)
 
-exception Warnings;;
-
-class warner =
-  object 
-    method warn w =
-      print_endline ("WARNING: " ^ w) ;
-      (raise Warnings : unit)
-  end
-;;
-
-exception EmptyUri;;
-
-(* given an uri u it returns the list of tokens of the base uri of u *)
-(* e.g.: token_of_uri "cic:/a/b/c/d.xml" returns ["a" ; "b" ; "c"]   *)
-let tokens_of_uri uri =
- let uri' = UriManager.string_of_uri uri in
- let rec chop_list =
-  function
-     [] -> raise EmptyUri
-   | he::[fn] -> [he]
-   | he::tl -> he::(chop_list tl)
- in
-  let trimmed_uri = Str.replace_first (Str.regexp "cic:") "" uri' in
-   let list_of_tokens = Str.split (Str.regexp "/") trimmed_uri in
-    chop_list list_of_tokens
-;;
+exception EmptyUri of string
 
 (* given the filename of an xml file of a cic object it returns its internal *)
-(* representation. process_annotations is true if the annotations do really  *)
-(* matter                                                                    *)
-let term_of_xml filename uri process_annotations =
- let module Y = Pxp_yacc in
+(* representation.                                                           *)
+let annobj_of_xml filename filenamebody =
   try 
-    let d =
-      (* sets the current base uri to resolve relative URIs *)
-      CicParser3.current_sp := tokens_of_uri uri ;
-      CicParser3.current_uri := uri ;
-      CicParser3.process_annotations := process_annotations ;
-      CicParser3.ids_to_targets :=
-       if process_annotations then Some (Hashtbl.create 500) else None ;
-      let config = {Y.default_config with Y.warner = new warner} in
-      Y.parse_document_entity config
-(*PXP       (Y.ExtID (Pxp_types.System filename,
-         new Pxp_reader.resolve_as_file ~url_of_id ()))
-*)     (PxpUriResolver.from_file filename)
-       CicParser3.domspec
+    let root, rootbody =
+     let config = PxpHelmConf.pxp_config in
+      let doc =
+       Pxp_tree_parser.parse_document_entity config
+        (Pxp_types.from_file ~alt:[PxpUrlResolver.url_resolver] filename)
+        CicParser3.domspec in
+      let docroot = doc#root in
+       match filenamebody with
+          None -> docroot,None
+        | Some filename ->
+           let docbody =
+            Pxp_tree_parser.parse_document_entity config
+             (Pxp_types.from_file ~alt:[PxpUrlResolver.url_resolver] filename)
+             CicParser3.domspec
+           in
+            docroot,Some docbody#root
     in
-     let ids_to_targets = !CicParser3.ids_to_targets in
-      let res = (CicParser2.get_term d#root, ids_to_targets) in
-       CicParser3.ids_to_targets := None ; (* let's help the GC *)
-       res
+     CicParser2.get_term root rootbody
   with
    e ->
-     print_endline ("Filename: " ^ filename ^ "\nException: ") ;
-     print_endline (Pxp_types.string_of_exn e) ;
+     prerr_endline ("Filenames: " ^ filename ^
+      (match filenamebody with None -> "" | Some s -> ", " ^ s)) ;
+     prerr_endline ("Exception: " ^ Pxp_types.string_of_exn e) ;
      raise e
-;;
+
+let obj_of_xml filename filenamebody =
+ Deannotate.deannotate_obj (annobj_of_xml filename filenamebody)
+