]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/metadata/metadataPp.ml
ocaml 3.09 transition
[helm.git] / helm / ocaml / metadata / metadataPp.ml
index fdbbaf071f133afc377845f71ccfdbf844dce824..acf425ce130df9f5af422cbc30ff6ea9788b23b6 100644 (file)
@@ -71,8 +71,8 @@ type t = [ `Int of int | `String of string | `Null ]
 
 let columns_of_metadata_aux ~about metadata =
   let sort s = `String (CicPp.ppsort s) in
-  let source = `String about in
-  let occurrence u = `String u in
+  let source = `String (UriManager.string_of_uri about) in
+  let occurrence u = `String (UriManager.string_of_uri u) in
   List.fold_left
     (fun (sort_cols, rel_cols, obj_cols) metadata ->
       match metadata with
@@ -102,7 +102,7 @@ let pp_constr =
          (CicPp.ppsort sort) (String.concat ";" (List.map pp_position p))
     | `Rel p -> sprintf "Rel [%s]" (String.concat ";" (List.map pp_position p))
     | `Obj (uri, p) -> sprintf "Obj %s; [%s]" 
-       uri (String.concat ";" (List.map pp_position p))
+       (UriManager.string_of_uri uri) (String.concat ";" (List.map pp_position p))
  
 (*
 let pp_columns ?(sep = "\n") (sort_cols, rel_cols, obj_cols) =