This module provides both a native Haskell solution for parsing XML documents into a stream of events, and a set of parser combinators for dealing with a stream of events.
As a simple example, if you have the following XML file:
<?xml version="1.0" encoding="utf-8"?> <people> <person age="25">Michael</person> <person age="2">Eliezer</person> </people>
Then this code:
{-# LANGUAGE OverloadedStrings #-} import Text.XML.Enumerator.Parse import Data.Text.Lazy (Text, unpack) data Person = Person { age :: Int, name :: Text } deriving Show parsePerson = tagName "person" (requireAttr "age") $ \age -> do name <- content return $ Person (read $ unpack age) name parsePeople = tagNoAttr "people" $ many parsePerson main = parseFile_ "people.xml" decodeEntities $ force "people required" parsePeople
will produce:
[Person {age = 25, name = "Michael"},Person {age = 2, name = "Eliezer"}]
Previous versions of this module contained a number of more sophisticated functions written by Aristid Breitkreuz and Dmitry Olshansky. To keep this package simpler, those functions are being moved to a separate package. This note will be updated with the name of the package(s) when available.
- parseBytes :: Monad m => ParseSettings -> Enumeratee ByteString Event m a
- parseText :: Monad m => ParseSettings -> Enumeratee Text Event m a
- detectUtf :: Monad m => Enumeratee ByteString Text m a
- parseFile :: ParseSettings -> FilePath -> Iteratee Event IO a -> IO (Either SomeException a)
- parseFile_ :: ParseSettings -> FilePath -> Iteratee Event IO a -> IO a
- parseLBS :: ParseSettings -> ByteString -> Iteratee Event IO a -> IO (Either SomeException a)
- parseLBS_ :: ParseSettings -> ByteString -> Iteratee Event IO a -> IO a
- data ParseSettings
- def :: Default a => a
- type DecodeEntities = Text -> Content
- psDecodeEntities :: ParseSettings -> DecodeEntities
- tag :: Monad m => (Name -> Maybe a) -> (a -> AttrParser b) -> (b -> Iteratee Event m c) -> Iteratee Event m (Maybe c)
- tagPredicate :: Monad m => (Name -> Bool) -> AttrParser a -> (a -> Iteratee Event m b) -> Iteratee Event m (Maybe b)
- tagName :: Monad m => Name -> AttrParser a -> (a -> Iteratee Event m b) -> Iteratee Event m (Maybe b)
- tagNoAttr :: Monad m => Name -> Iteratee Event m a -> Iteratee Event m (Maybe a)
- content :: Monad m => Iteratee Event m Text
- contentMaybe :: Monad m => Iteratee Event m (Maybe Text)
- data AttrParser a
- requireAttr :: Name -> AttrParser Text
- optionalAttr :: Name -> AttrParser (Maybe Text)
- requireAttrRaw :: String -> ((Name, [Content]) -> Maybe b) -> AttrParser b
- optionalAttrRaw :: ((Name, [Content]) -> Maybe b) -> AttrParser (Maybe b)
- ignoreAttrs :: AttrParser ()
- orE :: Monad m => Iteratee Event m (Maybe a) -> Iteratee Event m (Maybe a) -> Iteratee Event m (Maybe a)
- choose :: Monad m => [Iteratee Event m (Maybe a)] -> Iteratee Event m (Maybe a)
- many :: Monad m => Iteratee Event m (Maybe a) -> Iteratee Event m [a]
- force :: Monad m => String -> Iteratee Event m (Maybe a) -> Iteratee Event m a
- data XmlException
- = XmlException { }
- | InvalidEndElement Name
- | InvalidEntity Text
- | UnparsedAttributes [(Name, [Content])]
Parsing XML files
parseBytes :: Monad m => ParseSettings -> Enumeratee ByteString Event m aSource
Parses a byte stream into Event
s. This function is implemented fully in
Haskell using attoparsec-text for parsing. The produced error messages do
not give line/column information, so you may prefer to stick with the parser
provided by libxml-enumerator. However, this has the advantage of not
relying on any C libraries.
This relies on detectUtf
to determine character encoding, and parseText
to do the actual parsing.
parseText :: Monad m => ParseSettings -> Enumeratee Text Event m aSource
Parses a character stream into Event
s. This function is implemented
fully in Haskell using attoparsec-text for parsing. The produced error
messages do not give line/column information, so you may prefer to stick
with the parser provided by libxml-enumerator. However, this has the
advantage of not relying on any C libraries.
detectUtf :: Monad m => Enumeratee ByteString Text m aSource
Automatically determine which UTF variant is being used. This function first checks for BOMs, removing them as necessary, and then check for the equivalent of <?xml for each of UTF-8, UTF-16LEBE, and UTF-32LEBE. It defaults to assuming UTF-8.
parseFile :: ParseSettings -> FilePath -> Iteratee Event IO a -> IO (Either SomeException a)Source
A helper function which reads a file from disk using enumFile
, detects
character encoding using detectUtf
, parses the XML using parseBytes
, and
then hands off control to your supplied parser.
parseFile_ :: ParseSettings -> FilePath -> Iteratee Event IO a -> IO aSource
The same as parseFile
, but throws any exceptions.
parseLBS :: ParseSettings -> ByteString -> Iteratee Event IO a -> IO (Either SomeException a)Source
Parse an event stream from a lazy ByteString
.
parseLBS_ :: ParseSettings -> ByteString -> Iteratee Event IO a -> IO aSource
Same as parseLBS
, but throws exceptions.
Parser settings
type DecodeEntities = Text -> ContentSource
Event parsing
tag :: Monad m => (Name -> Maybe a) -> (a -> AttrParser b) -> (b -> Iteratee Event m c) -> Iteratee Event m (Maybe c)Source
The most generic way to parse a tag. It takes a predicate for checking if
this is the correct tag name, an AttrParser
for handling attributes, and
then a parser for dealing with content.
This function automatically absorbs its balancing closing tag, and will
throw an exception if not all of the attributes or child elements are
consumed. If you want to allow extra attributes, see ignoreAttrs
.
This function automatically ignores comments, instructions and whitespace.
tagPredicate :: Monad m => (Name -> Bool) -> AttrParser a -> (a -> Iteratee Event m b) -> Iteratee Event m (Maybe b)Source
A simplified version of tag
which matches against boolean predicates.
tagName :: Monad m => Name -> AttrParser a -> (a -> Iteratee Event m b) -> Iteratee Event m (Maybe b)Source
tagNoAttr :: Monad m => Name -> Iteratee Event m a -> Iteratee Event m (Maybe a)Source
A further simplified tag parser, which requires that no attributes exist.
content :: Monad m => Iteratee Event m TextSource
Grabs the next piece of content. If none if available, returns empty
.
This is simply a wrapper around contentMaybe
.
contentMaybe :: Monad m => Iteratee Event m (Maybe Text)Source
Grabs the next piece of content if available. This function skips over any comments and instructions and concatenates all content until the next start or end tag.
Attribute parsing
data AttrParser a Source
A monad for parsing attributes. By default, it requires you to deal with
all attributes present on an element, and will throw an exception if there
are unhandled attributes. Use the requireAttr
, optionalAttr
et al
functions for handling an attribute, and ignoreAttrs
if you would like to
skip the rest of the attributes on an element.
Alternative
instance behave like First
monoid. It chooses first
parser which doesn't fail.
requireAttr :: Name -> AttrParser TextSource
Require that a certain attribute be present and return its value.
optionalAttr :: Name -> AttrParser (Maybe Text)Source
Return the value for an attribute if present.
requireAttrRaw :: String -> ((Name, [Content]) -> Maybe b) -> AttrParser bSource
optionalAttrRaw :: ((Name, [Content]) -> Maybe b) -> AttrParser (Maybe b)Source
ignoreAttrs :: AttrParser ()Source
Skip the remaining attributes on an element. Since this will clear the
list of attributes, you must call this after any calls to requireAttr
,
optionalAttr
, etc.
Combinators
orE :: Monad m => Iteratee Event m (Maybe a) -> Iteratee Event m (Maybe a) -> Iteratee Event m (Maybe a)Source
many :: Monad m => Iteratee Event m (Maybe a) -> Iteratee Event m [a]Source
Keep parsing elements as long as the parser returns Just
.