hexpat-iteratee-0.5: Chunked XML parsing using iterateesSource codeContentsIndex
Text.XML.Expat.Chunked
Contents
Tree structure
Generic node manipulation
Generic manipulation of the child list
Qualified nodes
Namespaced nodes
Parse to tree
Synopsis
type Node s m tag text = NodeG (ListT (XMLT s m)) tag text
data NodeG c tag text
= Element {
eName :: !tag
eAttributes :: ![(tag, text)]
eChildren :: c (NodeG c tag text)
}
| Text !text
type UNode s m text = Node s m text text
module Text.XML.Expat.Internal.NodeClass
module Data.List.Class
type QNode s m a text = Node s a (QName text) text
module Text.XML.Expat.Internal.Qualified
type NNode s m text a = Node s a (NName text) text
module Text.XML.Expat.Internal.Namespaced
data ParseOptions tag text = ParseOptions {
defaultEncoding :: Maybe Encoding
entityDecoder :: Maybe (tag -> Maybe text)
}
defaultParseOptions :: ParseOptions tag text
data Encoding
= ASCII
| UTF8
| UTF16
| ISO88591
parse :: forall m a tag text. (MonadIO m, GenericXMLString tag, GenericXMLString text) => ParseOptions tag text -> (forall s. ListT (XMLT s m) (Node s m tag text) -> XMLT s m a) -> m (IterateeG WrappedByteString Word8 m (Either ErrMsg a))
data XMLT s m a
data XMLParseError = XMLParseError String XMLParseLocation
data XMLParseLocation = XMLParseLocation {
xmlLineNumber :: Int64
xmlColumnNumber :: Int64
xmlByteIndex :: Int64
xmlByteCount :: Int64
}
Tree structure
type Node s m tag text = NodeG (ListT (XMLT s m)) tag textSource

A tree representation that uses a monadic list as its child list type.

Note that you can use the type function ListOf to give a list of any node type, using that node's associated list type, e.g. ListOf (UNode Text)

The s parameter is a dummy type used to prevent nodes escaping from the handler. See s for more explanation.

data NodeG c tag text Source

The tree representation of the XML document.

c is the container type for the element's children, which is [] in the hexpat package, and a monadic list type for hexpat-iteratee.

tag is the tag type, which can either be one of several string types, or a special type from the Text.XML.Expat.Namespaced or Text.XML.Expat.Qualified modules.

text is the string type for text content.

Constructors
Element
eName :: !tag
eAttributes :: ![(tag, text)]
eChildren :: c (NodeG c tag text)
Text !text
show/hide Instances
(Functor c, List c) => NodeClass NodeG c
(Functor c, List c) => MkElementClass NodeG c
(Eq tag, Eq text) => Eq (NodeG [] tag text)
(Show tag, Show text) => Show (NodeG [] tag text)
(NFData tag, NFData text) => NFData (NodeG [] tag text)
type UNode s m text = Node s m text textSource

Type alias for a single node with unqualified tag names where tag and text are the same string type.

The s parameter is a dummy type used to prevent nodes escaping from the handler. See s for more explanation.

Generic node manipulation
module Text.XML.Expat.Internal.NodeClass
Generic manipulation of the child list
module Data.List.Class
Qualified nodes
type QNode s m a text = Node s a (QName text) textSource

Type alias for a single annotated node where qualified names are used for tags

The s parameter is a dummy type used to prevent nodes escaping from the handler. See s for more explanation.

module Text.XML.Expat.Internal.Qualified
Namespaced nodes
type NNode s m text a = Node s a (NName text) textSource

Type alias for a single annotated node where namespaced names are used for tags

The s parameter is a dummy type used to prevent nodes escaping from the handler. See s for more explanation.

module Text.XML.Expat.Internal.Namespaced
Parse to tree
data ParseOptions tag text Source
Constructors
ParseOptions
defaultEncoding :: Maybe EncodingThe encoding parameter, if provided, overrides the document's encoding declaration.
entityDecoder :: Maybe (tag -> Maybe text)If provided, entity references (i.e.   and friends) will be decoded into text using the supplied lookup function
defaultParseOptions :: ParseOptions tag textSource
data Encoding Source
Encoding types available for the document encoding.
Constructors
ASCII
UTF8
UTF16
ISO88591
parseSource
:: forall m a tag text . (MonadIO m, GenericXMLString tag, GenericXMLString text)
=> ParseOptions tag text
-> forall s. ListT (XMLT s m) (Node s m tag text) -> XMLT s m aHandler for parsed tree
-> m (IterateeG WrappedByteString Word8 m (Either ErrMsg a))

An iteratee that parses the input document, passing a representation of it to the specified handler monad. The monad runs lazily using co-routines, so if it requests a part of the tree that hasn't been parsed yet, it will be suspended, and continued when it's available.

This implementation does not use Haskell's lazy I/O.

The s type argument is a dummy type, which you should just leave polymorphic by typing s when using the type. The "forall s ." in the type signature prevents any parsed nodes escaping from the handler, because they may refer to parts of the tree that haven't been parsed yet, and this parsing can't take happen outside the handler. If you need to extract nodes from your handler, use a function like fromNodeContainer to convert the container type.

data XMLT s m a Source
The monad transformer used for writing your handler for chunked XML trees, which executes as a co-routine.
show/hide Instances
MonadTrans (XMLT s)
Monad m => Monad (XMLT s m)
Monad m => Functor (XMLT s m)
MonadIO m => MonadIO (XMLT s m)
data XMLParseError Source
Parse error, consisting of message text and error location
Constructors
XMLParseError String XMLParseLocation
show/hide Instances
data XMLParseLocation Source
Specifies a location of an event within the input text
Constructors
XMLParseLocation
xmlLineNumber :: Int64Line number of the event
xmlColumnNumber :: Int64Column number of the event
xmlByteIndex :: Int64Byte index of event from start of document
xmlByteCount :: Int64The number of bytes in the event
show/hide Instances
Produced by Haddock version 2.6.1