]> matita.cs.unibo.it Git - helm.git/blobdiff - helm/ocaml/xml/xml.mli
ocaml 3.09 transition
[helm.git] / helm / ocaml / xml / xml.mli
index c52ae8ecd80d8758874f27e361423d40ff8b5ce2..43547eaa03fdbc5a1aadeeea11bc5f29b9594ab4 100644 (file)
 (******************************************************************************)
 
 (* Tokens for XML cdata, empty elements and not-empty elements           *)
-(* Usage:                                                                *)
-(*  Str cdata                                                            *)
-(*  Empty (element_name, [attrname1, value1 ; ... ; attrnamen, valuen]   *)
-(*  NEmpty (element_name, [attrname1, value2 ; ... ; attrnamen, valuen], *)
-(*          content                                                      *)
+(* Usage:                                                             *)
+(*  Str cdata                                                         *)
+(*  Empty (prefix, element_name,                                      *)
+(*   [prefix1, attrname1, value1 ; ... ; prefixn, attrnamen, valuen]  *)
+(*  NEmpty (prefix, element_name,                                     *)
+(*   [prefix1, attrname1, value1 ; ... ; prefixn, attrnamen, valuen], *)
+(*    content                                                         *)
 type token =
-  | Str of string
-  | Empty of string * (string * string) list
-  | NEmpty of string * (string * string) list * token Stream.t
+   Str of string
+ | Empty of string option * string * (string option * string * string) list
+ | NEmpty of string option * string * (string option * string * string) list *
+    token Stream.t
+;;
 
 (* currified versions of the token constructors make the code more readable *)
-val xml_empty : string -> (string * string) list -> token Stream.t
+val xml_empty :
+ ?prefix:string -> string -> (string option * string * string) list ->
+   token Stream.t
 val xml_nempty :
-  string -> (string * string) list -> token Stream.t -> token Stream.t
+ ?prefix:string -> string -> (string option * string * string) list ->
+   token Stream.t -> token Stream.t
 val xml_cdata : string -> token Stream.t
 
 (* The pretty printer for streams of token                                  *)
 (* Usage:                                                                   *)
 (*  pp tokens None     pretty prints the output on stdout                   *)
-(*  pp tokens (Some filename) pretty prints the output on the file filename *)
-val pp : ?quiet:bool -> token Stream.t -> string option -> unit
+(*  pp tokens (Some filename) pretty prints the output on the file filename
+* @param gzip if set to true files are gzipped. Defaults to false *)
+val pp : ?gzip:bool -> token Stream.t -> string option -> unit
 val pp_to_outchan : token Stream.t -> out_channel -> unit
 val pp_to_string : token Stream.t -> string
 
+val add_xml_declaration: token Stream.t -> token Stream.t
+