]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/cic/cicParser.ml
- the mathql interpreter is not helm-dependent any more
[helm.git] / helm / ocaml / cic / cicParser.ml
index 7cabeb6ae16413f6ac108b15b54f109b0ad8c755..38fe9e210c41787004f1f970000d88d938f121ec 100644 (file)
@@ -41,55 +41,44 @@ exception Warnings;;
 class warner =
   object 
     method warn w =
-      print_endline ("WARNING: " ^ w) ;
+      prerr_endline ("WARNING: " ^ w) ;
       (raise Warnings : unit)
   end
 ;;
 
 exception EmptyUri of string;;
 
-(* 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 uri')
-   | [fn] -> []
-   | 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
-;;
-
 (* given the filename of an xml file of a cic object it returns its internal *)
 (* representation.                                                           *)
-let annobj_of_xml filename uri =
+let annobj_of_xml filename filenamebody =
  let module Y = Pxp_yacc in
   try 
-    let d =
-      (* sets the current base uri to resolve relative URIs *)
-      CicParser3.current_sp := tokens_of_uri uri ;
-      CicParser3.current_uri := uri ;
-      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) *)
-       (Y.from_file ~alt:[PxpUrlResolver.url_resolver] filename)
-       CicParser3.domspec
+    let root, rootbody =
+     let config = {Y.default_config with Y.warner = new warner} in
+      let doc =
+       Y.parse_document_entity config
+        (Y.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 =
+            Y.parse_document_entity config
+             (Y.from_file ~alt:[PxpUrlResolver.url_resolver] filename)
+             CicParser3.domspec
+           in
+            docroot,Some docbody#root
     in
-     CicParser2.get_term d#root
+     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 uri =
- Deannotate.deannotate_obj (annobj_of_xml filename uri)
+let obj_of_xml filename filenamebody =
+ Deannotate.deannotate_obj (annobj_of_xml filename filenamebody)
 ;;