module Pxp_types:Type definitions used throughout PXPsig..end
Pxp_core_types.S (and finally defined in Pxp_core_types.I), so 
 the user only has to
 open Pxp_types to get all relevant type definitions. The re-exported
 definitions are shown here in the indented grey block:include Pxp_core_types.S
module StringMap:Map.Swith type key = string
typeext_id =Pxp_core_types.A.ext_id=
| | | System of  | 
| | | Public of  | 
| | | Anonymous | 
| | | Private of  | 
System identifier is
      a URL. PXP (without extensions) only supports file URLs in the form
      file:///directory/directory/.../file. Note that the percent encoding
      (% plus two hex digits) is supported in file URLs. A public identifier
      can be looked up in a catalog to find a local copy of the file; this
      type is mostly used for well-known documents (e.g. after
      standardization). A public identifier can be accompanied by a
      system identifier (Public(pubid,sysid)), but the system identifier
      can be the empty string. The value Anonymous should not be used
      to identify a real document; it is more thought as a placeholder when
      an ID is not yet known. Private identifiers are used by PXP internally.
      These identifiers have, unlike system or public IDs, no textual
      counterparts.
      The identifiers are encoded as UTF-8 strings.
typeprivate_id =Pxp_core_types.A.private_id
val allocate_private_id : unit -> private_idtyperesolver_id =Pxp_core_types.A.resolver_id= {
|    | rid_private : | 
|    | rid_public : | 
|    | rid_system : | 
|    | rid_system_base : | 
val resolver_id_of_ext_id : ext_id -> resolver_idSystem ID is turned into a resolver_id where only rid_system is
 set. A Public ID is turned into a resolver_id where both rid_public
 and rid_system are set. A Private ID is turned into a resolver_id
 where only rid_private is set. An Anonymous ID is turned into a
 resolver_id without any value (all components are None).typedtd_id =Pxp_core_types.A.dtd_id=
| | | External of  | (* | DTD is completely external | *) | 
| | | Derived of  | (* | DTD is derived from an external DTD | *) | 
| | | Internal | (* | DTD is completely internal | *) | 
typecontent_model_type =Pxp_core_types.A.content_model_type=
| | | Unspecified | (* | A specification of the model has not yet been found | *) | 
| | | Empty | (* | Nothing is allowed as content | *) | 
| | | Any | (* | Everything is allowed as content | *) | 
| | | Mixed of  | (* | The contents consist of elements and PCDATAin arbitrary order. What is allowed in
 particular is given asmixed_spec. | *) | 
| | | Regexp of  | (* | The contents are elements following this regular expression | *) | 
typemixed_spec =Pxp_core_types.A.mixed_spec=
| | | MPCDATA | (* | PCDATAchildren are allowed | *) | 
| | | MChild of  | (* | This kind of Element is allowed | *) | 
typeregexp_spec =Pxp_core_types.A.regexp_spec=
| | | Optional of  | (* | subexpression? | *) | 
| | | Repeated of  | (* | subexpression* | *) | 
| | | Repeated1 of  | (* | subexpression+ | *) | 
| | | Alt of  | (* | subexpr1 | subexpr2 | ... | subexprN | *) | 
| | | Seq of  | (* | subexpr1 , subexpr2 , ... , subexprN | *) | 
| | | Child of  | (* | This kind of Element is allowed here | *) | 
typeatt_type =Pxp_core_types.A.att_type=
| | | A_cdata | (* | CDATA | *) | 
| | | A_id | (* | ID | *) | 
| | | A_idref | (* | IDREF | *) | 
| | | A_idrefs | (* | IDREFS | *) | 
| | | A_entity | (* | ENTITY | *) | 
| | | A_entities | (* | ENTITIES | *) | 
| | | A_nmtoken | (* | NMTOKEN | *) | 
| | | A_nmtokens | (* | NMTOKENS | *) | 
| | | A_notation of  | (* | NOTATION(name1 | name2 | ... | nameN) | *) | 
| | | A_enum of  | (* | (name1 | name2 | ... | nameN) | *) | 
typeatt_default =Pxp_core_types.A.att_default=
| | | D_required | (* | #REQUIRED | *) | 
| | | D_implied | (* | #IMPLIED | *) | 
| | | D_default of  | (* | a value default -- the value is already expanded | *) | 
| | | D_fixed of  | (* | FIXEDvalue default -- the value is already expanded | *) | 
typeatt_value =Pxp_core_types.A.att_value=
| | | Value of  | 
| | | Valuelist of  | 
| | | Implied_value | 
Value s: The attribute is declared as a non-list type, or the
     attribute is undeclared; and the attribute is either defined with
     value "s", or it is missing but has the default value s.[Valuelist [s1;...;sk]]: The attribute is declared as a list type,
     and the attribute is either defined with value "s1 ... sk"
     (space-separated words),
     or it is missing but has the default value "s1 ... sk".Implied_value: The attribute is declared without default value,
     and there is no definition for the attribute.class type collect_warnings =object..end
class drop_warnings :collect_warnings
typewarning =[ `W_XML_version_not_supported of string
| `W_code_point_cannot_be_represented of int
| `W_element_mentioned_but_not_declared of string
| `W_entity_declared_twice of string
| `W_multiple_ATTLIST_declarations of string
| `W_multiple_attribute_declarations of string * string
| `W_name_is_reserved_for_extensions of string ]
class type symbolic_warnings =object..end
val string_of_warning : warning -> stringval warn : symbolic_warnings option ->
       collect_warnings -> warning -> unitsymbolic_warnings object, and then to the
 collect_warnings object.typeencoding =Netconversion.encoding
typerep_encoding =[ `Enc_cp1006
| `Enc_cp437
| `Enc_cp737
| `Enc_cp775
| `Enc_cp850
| `Enc_cp852
| `Enc_cp855
| `Enc_cp856
| `Enc_cp857
| `Enc_cp860
| `Enc_cp861
| `Enc_cp862
| `Enc_cp863
| `Enc_cp864
| `Enc_cp865
| `Enc_cp866
| `Enc_cp869
| `Enc_cp874
| `Enc_iso88591
| `Enc_iso885910
| `Enc_iso885913
| `Enc_iso885914
| `Enc_iso885915
| `Enc_iso885916
| `Enc_iso88592
| `Enc_iso88593
| `Enc_iso88594
| `Enc_iso88595
| `Enc_iso88596
| `Enc_iso88597
| `Enc_iso88598
| `Enc_iso88599
| `Enc_koi8r
| `Enc_macroman
| `Enc_usascii
| `Enc_utf8
| `Enc_windows1250
| `Enc_windows1251
| `Enc_windows1252
| `Enc_windows1253
| `Enc_windows1254
| `Enc_windows1255
| `Enc_windows1256
| `Enc_windows1257
| `Enc_windows1258 ]
encoding that may be used for the internal representation
 of strings. The common property of the  following encodings is that
 they are ASCII-compatible - the PXP code relies on that.exception Validation_error of string
exception WF_error of string
exception Namespace_error of string
exception Error of string
exception Character_not_supported
exception At of (string * exn)
At(_,_) (for example, when an entity within an entity causes
 the error).exception Undeclared
exception Method_not_applicable of string
exception Namespace_method_not_applicable of string
exception Not_competent
exception Not_resolvable of exn
exception Namespace_not_managed of string
exception Namespace_prefix_not_managed of string
exception Namespace_not_in_scope of string
val string_of_exn : exn -> stringtypeoutput_stream =[ `Out_buffer of Buffer.t
| `Out_channel of Pervasives.out_channel
| `Out_function of string -> int -> int -> unit
| `Out_netchannel of Netchannels.out_obj_channel ]
`Out_buffer b: Output to buffer b`Out_channel ch: Output to channel ch`Out_function f: Output to function f. The function f is
          used like Pervasives.output_string.`Out_netchannel n: Output to the ocamlnet channel nval write : output_stream -> string -> int -> int -> unitwrite os s pos len: Writes the string (portion) to the
         buffer/channel/streamtypepool =Pxp_core_types.A.pool
val make_probabilistic_pool : ?fraction:float -> int -> poolval pool_string : pool -> string -> string
    
Configuration
type |    | warner : | (* | An object that collects warnings. | *) | 
|    | swarner : | (* | Another object getting warnings expressed as polymorphic
 variants. This is especially useful to turn warnings into
 errors. If defined, the swarnergets the warning
 first before it is sent to the classicwarner. | *) | 
|    | enable_pinstr_nodes : | (* | if true, processing instructions (PI's) are represented by
 nodes of their own in the document tree. If not enabled, PI's
 are attached to their surrounding elements, and the exact
 location within the element is lost.
 For example, if the XML text
 is  
 The event-based parser reacts on the  | *) | 
|    | enable_comment_nodes : | (* | When enabled, comments are represented as nodes with type T_comment. If not enabled, comments are ignored.Event-based parser: This flag controls whether E_comment events are generated. | *) | 
|    | enable_super_root_node : | (* | The enable_super_root_nodechanges the layout of the document
 tree: The top-most node is no longer the top-most element of the
 document (i.e. the element root), but a special node called the
 super root node (T_super_root). The top-most element is then
 a child of the super
 root node. The super root node can have further children, namely
 comment nodes and processing instructions that are placed before
 or after the top-most element in the XML text. However, the exact
 behaviour depends on whether the other special modes in the
 configuration are also enabled:
 | *) | 
|    | drop_ignorable_whitespace : | (* | Ignorable whitespace is whitespace between XML nodes where
 the DTD does not specify that #PCDATAmust be parsed. For example,
 if the DTD contains <!ELEMENT a (b,c)>the XML text<a><b> </b> <c></c></a>is legal. There are two
 spaces:
 cis declared asEMPTY. XML does not allow space
 characters between<c>and</c>such that it is not the question
 whether such characters are to be ignored or not - they are
 simply illegal and will lead to a parsing error.In the well-formed mode, the parser treats every whitespace character occuring in an element as non-ignorable. Event-based parser: ignored. (Maybe there will be a stream filter with the same effect if I find time to program it.) | *) | 
|    | encoding : | (* | Specifies the encoding used for the internal representation of any character data. | *) | 
|    | recognize_standalone_declaration : | (* | Whether the standalonedeclaration is recognized or not.
 This option does not have an effect on well-formedness parsing:
 in this case such declarations are never recognized.
 Recognizing the  
 This means: If a document is flagged  
 Event-based parser: The option has an effect if the  | *) | 
|    | store_element_positions : | (* | Whether the file name, the line and the column of the
 beginning of elements are stored in the element nodes.
 This option may be useful to generate error messages. Positions are only stored for: 
 
 You can access positions by the method  
 Event-based parser: If true, the  | *) | 
|    | idref_pass : | (* | Whether the parser does a second pass and checks that all IDREFandIDREFSattributes contain valid references.
 This option works only if an ID index is available. To create
 an ID index, pass an index object asid_indexargument to the
 parsing functions (such asPxp_tree_parser.parse_document_entity).
 "Second pass" does not mean that the XML text is again parsed;
 only the existing document tree is traversed, and the check
 on bad  Event-based parser: this option is ignored. | *) | 
|    | validate_by_dfa : | (* | If true, and if DFAs are available for validation, the DFAs will
 actually be used for validation.
 If false, or if no DFAs are available, the standard backtracking
 algorithm will be used. 
 DFAs are only available if  I strongly recommend using DFAs; however, there are examples for which validation by backtracking is faster. Event-based parser: this option is ignored. | *) | 
|    | accept_only_deterministic_models : | (* | Whether only deterministic content models are accepted in DTDs. Event-based parser: this option is ignored. | *) | 
|    | disable_content_validation : | (* | When set to true, content validation is disabled; however,
 other validation checks remain activated.
 This option is intended to save time when a validated document
 is parsed and it can be assumed that it is valid. 
 Do not forget to set  Event-based parser: this option is ignored. | *) | 
|    | name_pool : | |||
|    | enable_name_pool_for_element_types : | |||
|    | enable_name_pool_for_attribute_names : | |||
|    | enable_name_pool_for_attribute_values : | |||
|    | enable_name_pool_for_pinstr_targets : | (* | The name pool maps strings to pool strings such that strings with
 the same value share the same block of memory.
 Enabling the name pool saves memory, but makes the parser
 slower. Event-based parser: As far as I remember, some of the pool options are honoured, but not all. | *) | 
|    | enable_namespace_processing : | (* | Setting this option to a namespace_managerenables namespace
 processing. This works only if the namespace-aware implementationnamespace_element_implof element nodes is used in the spec;
 otherwise you will get error messages complaining about missing
 methods.
 Note that PXP uses a technique called "prefix normalization" to
 implement namespaces on top of the plain document model. This means
 that the namespace prefixes of elements and attributes are changed
 to unique prefixes if they are ambiguous, and that these 
 "normprefixes" are actually stored in the document tree. Furthermore,
 the normprefixes are used for validation. (See
  
 Event-based parser: If true, the events  | *) | 
|    | escape_contents : | (* | Experimental feature.
 If defined, the escape_contentsfunction is called whenever 
 the tokens "{", "{{", "}", or "}}" are found in the context
 of character data contents. The first argument is the token.
 The second argument is the entity manager, it can be used to
 access the lexing buffer directly. The result of the function
 are the characters to substitute.
 "{" is the token  Event-based parser: this option works. | *) | 
|    | escape_attributes : | (* | Experimental feature.
 If defined, the escape_attributesfunction is called whenever 
 the tokens "{", "{{", "}", or "}}" are found inside attribute
 values. The function takes three arguments: The token (Lcurly,LLcurly,RcurlyorRRcurly), the position in the attribute value,
 and the entity manager. 
 The result of the function is the string substituted for the
 token.Example: The attribute is "a{b{{c", and the function is called as follows: 
 
 See also  Event-based parser: this option works. | *) | 
|    | debugging_mode : | 
val default_config : configval default_namespace_config : configdefault_config, but namespace processing is turned on.
      Note however, that a globally defined namespace manager is used.
      Because of this, this config should no longer be used. Instead, do
               let m = Pxp_dtd.create_namespace_manager() in
         let namespace_config =
               { default_config with
                    enable_namespace_processing = Some m
               }
      
      and take control of the scope of m.source is often not used directly, but sources are constructed
 with the help of the functions from_channel, from_obj_channel,
 from_file, and from_string (see below). Note that you can
 usually view the type source as an opaque type. There is no need
 to understand why it enumerates these three cases, or to use them
 directly. Just create sources with one of the from_* functions.
 The type source is an abstraction on top of resolver (defined in
 module Pxp_reader). The resolver is a configurable object that knows 
 how to access files that are
PUBLIC or SYSTEM name)Private and Anonymous.resolver knows a lot about the character encoding
 of the files. See Pxp_reader for details.
 A source is a resolver that is applied to a certain ID that should
 be initially opened.
typesource =Pxp_dtd.source=
| | | Entity of  | 
| | | ExtID of  | 
| | | XExtID of  | 
Entity(m,r) is a very low-level way of denoting a source. After the
   parser has created the DTD object d, it calls
    e = m d 
   and uses the entity object e together with the resolver r. This kind
   of source is intended to implement customized versions of the entity
   classes. Use it only if there is a strong need to do so.ExtID(xid,r) is the normal way of denoting a source. The external entity
   referred to by the ID xid is opened by using the resolver r.XExtID(xid,sys_base,r) is an extension of ExtID. The additional parameter
   sys_base is the base URI to assume if xid is a relative URI (i.e.
   a SYSTEM ID).val from_channel : ?alt:Pxp_reader.resolver list ->
       ?system_id:string ->
       ?fixenc:encoding ->
       ?id:ext_id ->
       ?system_encoding:encoding -> Pervasives.in_channel -> sourcein_channel. By default, this source is not able to read
 XML text from any other location (you cannot read from files etc.).
 The optional arguments allow it to modify this behaviour.
Keep the following in mind:
alt argument specifies something else, you cannot
   refer to entities by SYSTEM or PUBLIC names (error "no input method
   available")alt method that can handle SYSTEM, it is
   not immediately possible to open SYSTEM entities that are defined
   by a URL relative to the entity that is accessed over the in_channel.
   You first must pass the system_id
   argument, so the parser knows the base name relative to which
   other SYSTEM entities can be resolved.Intro_resolution.alt: A list of further resolvers that are used to open further entities
   referenced in the initially opened entity. For example, you can pass
    new Pxp_reader.resolve_as_file() to enable resolving of
    file names found in SYSTEM IDs.system_id: By default, the XML text found in the in_channel does not
    have any visible ID (to be exact, the in_channel has a private ID, but
    this is hidden). Because of this, it is not possible to open
    a second file by using a relative SYSTEM ID. The parameter system_id
    assigns the channel a SYSTEM ID that is only used to resolve 
    further relative SYSTEM IDs. -
    This parameter must be encoded as UTF-8 string.fixenc: By default, the character encoding of the XML text is 
    determined by looking at the XML declaration. Setting fixenc
    forces a certain character encoding. Useful if you can assume
    that the XML text has been recoded by the transmission media.id: This parameter assigns the channel an arbitrary ID (like system_id,
    but PUBLIC, anonymous, and private IDs are also possible - although
    not reasonable). Furthermore, setting id also enables resolving
    of file names. id has higher precedence than system_id.system_encoding: (Only useful together with id.) The character encoding
    used for file names. (UTF-8 by default.)val from_obj_channel : ?alt:Pxp_reader.resolver list ->
       ?system_id:string ->
       ?fixenc:encoding ->
       ?id:ext_id ->
       ?system_encoding:encoding -> Netchannels.in_obj_channel -> sourcefrom_channel, but reads from an Ocamlnet netchannel 
      instead.val from_string : ?alt:Pxp_reader.resolver list ->
       ?system_id:string -> ?fixenc:encoding -> string -> sourcefrom_channel, but reads from a string.
 Of course, it is possible to parse this source several times, unlike
 the channel-based sources.
val from_file : ?alt:Pxp_reader.resolver list ->
       ?system_encoding:encoding -> ?enc:encoding -> string -> sourceThis source can open further files by default, and relative URLs work immediately.
Arguments:
alt: A list of further resolvers, especially useful to open 
    non-SYSTEM IDs, and non-file entities.system_encoding: The character encoding the system uses to represent
    filenames. By default, UTF-8 is assumed.enc: The character encoding of the string argument. As mentioned, this
    is UTF-8 by default.
 from_file "/tmp/file.xml"  
   reads from this file, which is assumed to have the ID 
   SYSTEM "file://localhost/tmp/file.xml". It is no problem when
   other files are included by either absolute SYSTEM file name,
   or by a relative SYSTEM. let ch = open_in "/tmp/file.xml" in
 from_channel
    ~alt:[ new Pxp_reader.resolve_as_file() ] 
    ~system_id:"file://localhost/tmp/file.xml" ch
   does roughly the same, but uses a channel for the initially opened
   entity. Because of the alt argument, it is possible to reference
   other entities by absolute SYSTEM name. The system_id assignment
   makes it possible that SYSTEM names relative to the initially used
   entity are resolvable. let cat = new Pxp_reader.lookup_id
                  [ Public("My Public ID",""),"/usr/share/xml/public.xml" ] in
 from_file ~alt:[cat] "/tmp/file.xml"
   sets that the PUBLIC ID "My Public ID" is mapped to the
   shown file, i.e. this file is parsed when this PUBLIC ID occurs in
   the XML text. (Without mapping PUBLIC names these cannot be resolved.)val open_source : config ->
       source ->
       bool -> Pxp_dtd.dtd -> Pxp_reader.resolver * Pxp_entity.entityPxp_dtd.Entity for functions dealing with entities.typeentity_id =Pxp_lexer_types.entity_id
entity_id is an identifier for an entity, or a fake identifier.typeentity =Pxp_entity.entity
typeentry =[ `Entry_content of [ `Dummy ] list
| `Entry_declarations of [ `Extend_dtd_fully | `Val_mode_dtd ] list
| `Entry_document of
[ `Extend_dtd_fully | `Parse_xml_decl | `Val_mode_dtd ] list
| `Entry_element_content of [ `Dummy ] list
| `Entry_expr of [ `Dummy ] list ]
process_entity):`Entry_document: The parser reads a complete document that
   must have a DOCTYPE and may have a DTD.`Entry_declarations: The parser reads the external subset
   of a DTD`Entry_element_content: 
   The parser reads an entity containing contents, but there must
   be one top element, i.e. "misc* element misc*". At the beginning,
   there can be an XML declaration as for external entities.`Entry_content:
   The parser reads an entity containing contents, but without the
   restriction of having a top element. At the beginning,
   there can be an XML declaration as for external entities.`Entry_expr: The parser reads a single element, a single
   processing instruction or a single comment, or whitespace, whatever is
   found. In contrast to the other entry points, the expression
   need not to be a complete entity, but can start and end in 
   the middle of an entity
 The entry points have a list of flags. Note that `Dummy is
 ignored and only present because O'Caml does not allow empty
 variants. 
 For `Entry_document, and `Entry_declarations, the flags determine
 the kind of DTD object that is generated. 
Without flags, the DTD object is configured for well-formedness mode:
dtd#arbitrary_allowed).
`Extend_dtd_fully: Elements, attributes, and notations are added
    to the DTD. The DTD mode dtd#arbitrary_allowed is enabled. 
    If the resulting event stream is validated later, this mode
    has the effect that the actually declared elements, attributes, 
    and notations are validated as declared. Also, non-declared
    elements, attributes, and notations are not rejected, but
    handled as in well-formed mode.`Val_mode_dtd: The DTD object is set up for validation, i.e. all
    declarations are added to the DTD, and dtd#arbitrary_allowed is 
    disabled. Furthermore, some validation checks are already done
    for the DTD (e.g. whether the root element is declared).
    If the resulting event stream is validated later, all validation
    checks are conducted (except for the XML declaration - see the
    next flag - this check must be separately enabled).`Parse_xml_decl: By default, the XML declaration
   <?xml version="1.0" encoding="..." standalone="..."?> is
   ignored except for the encoding attribute. This flag causes
   that the XML declaration is completely parsed.type | | | E_start_doc of  | (* | Starts a document. The string is the XML version ("1.0") | *) | 
| | | E_end_doc of  | (* | Ends a document. The string is the literal name of the root element (without any normalization or transformation) | *) | 
| | | E_start_tag of  | (* | (name, attlist, scope_opt, entid): Starts an elementnamewith an attribute listattlist.scope_optis the scope
           object in namespace mode, otherwiseNone.entididentifies
           the identity where the start tag occurs | *) | 
| | | E_end_tag of  | (* | (name,entid): Ends the elementnamein entityentid. | *) | 
| | | E_char_data of  | (* | Character data | *) | 
| | | E_pinstr of  | (* | A processing instruction <?target value?> | *) | 
| | | E_comment of  | (* | A comment node. The string does not include the delimiters | *) | 
| | | E_start_super | (* | Starts the super root | *) | 
| | | E_end_super | (* | Ends the super root | *) | 
| | | E_position of  | (* | (entity,line,pos): Describes that the next element, which is
           eitherE_start_tag,E_pinstr, orE_comment, is located
           inentityatlineand character positionpos. | *) | 
| | | E_error of  | (* | May occur as last event in a stream to describe an error | *) | 
| | | E_end_of_stream | (* | If the text can be parsed without error, this event is the last event of the stream | *) | 
`Entry_document), the events
      of the text are surrounded by E_start_doc and E_end_doc, i.e. 
      the overall structure is:
E_start_docE_end_docE_error or E_end_of_stream`Entry_content and `Entry_expr the document
      events are left out. The final E_error or E_end_of_stream event
      is nevertheless emitted.