xleb-0.1.0: A simple monadic language for parsing XML structures.

Copyright(c) Getty Ritter 2017
LicenseBSD
MaintainerGetty Ritter <xleb@infinitenegativeutility.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Text.XML.Xleb

Contents

Description

The Xleb monad (and the corresponding XlebT monad transformer) is a monadic sublanguage for easily parsing XML structures.

This module is intended to be imported qualified, to avoid name clashes with Prelude functions. e.g.

import qualified Text.XML.Xleb as X

Synopsis

How To Use Xleb

The Xleb monad describes both parsing and traversing a given XML structure: several of the functions to produce Xleb computations take other Xleb computations, which are run on various sub-parts of the XML tree. Consequently, instead of decomposing an XML structure and passing it around to various functions, the Xleb language treats "the current location in the tree" as an implicit piece of data in the Xleb monad.

You will generally want to identify your root note with the elem function to ensure that your root note has the tag you expect. Children of that node can be accessed using the child or children function to either unambiguously find a specific child element, or to find all child elements that match a given selector and apply a Xleb computation to each of them.

  a <- X.child (X.byTag "a") parseA
  b <- X.children (X.byTag "b") parseB

Leaf data tends to come in two forms in XML: attribute values (like <tag attr="value">) or tag content (like <tag>value</tag>). In both cases, the Xleb functions allow you to parse that content however you'd like by providing an arbitrary function of type String -> Either String a. The "xleb" library provides several built-in functions of this type for common situations.

  c <- X.attr "index" X.number
  d <- X.contents X.string

Finally, the Xleb monad has Alternative instances which allow for concise expression of optional values or multiple possibilities.

  e <- X.children X.any (parseA <|> parseB)
  f <- optional (X.attr "total" X.number)

Consequently, for an XML structure like the following:

<feed>
  <title>Feed Name</title>
  <author>Pierre Menard</author>
  <entry title="Entry 01">First Post</entry>
  <entry title="Entry 02">Second Post Post</entry>
</feed>

We can write a Xleb computation which is capable of parsing this structure in a handful of lines:

import           Control.Applicative (optional)
import qualified Text.XML.Xleb as X

feed :: X.Xleb (String, Maybe String, [(String, String)])
feed = X.elem "feed" $ do
  feedTitle   <- X.child (X.byTag "title") $
                   X.contents X.string
  feedAuthor  <- optional $ X.child (X.byTag "author") $
                              X.contents X.string
  feedEntries <- X.children (X.byTag "entry") entry
  return (feedTitle, feedAuthor, feedEntries)

entry :: X.Xleb (String, String)
entry = (,) <$> X.attr "title" X.string <*> X.contents X.string

The Xleb monad

type Xleb a = XlebT Identity a Source #

The Xleb monad describes a computation used to parse a fragment of XML from a particular element of an XML structure. This may fail with an error, or it may produce a value.

runXleb :: String -> Xleb t -> Either XlebError t Source #

Run a Xleb computation over a string containing XML data, producing either the resulting value or an error. If the XML data contained in the argument string is invalid, then this will fail with XEBadXML.

The XlebT monad transformer

data XlebT m a Source #

The XlebT monad transformer describes a computation used to parse a fragment of XML from a particular element of an XML structure. This may fail with an error, or it may produce a value.

Instances

Monad m => Monad (XlebT m) Source # 

Methods

(>>=) :: XlebT m a -> (a -> XlebT m b) -> XlebT m b #

(>>) :: XlebT m a -> XlebT m b -> XlebT m b #

return :: a -> XlebT m a #

fail :: String -> XlebT m a #

Functor m => Functor (XlebT m) Source # 

Methods

fmap :: (a -> b) -> XlebT m a -> XlebT m b #

(<$) :: a -> XlebT m b -> XlebT m a #

Monad m => MonadFail (XlebT m) Source # 

Methods

fail :: String -> XlebT m a #

Monad m => Applicative (XlebT m) Source # 

Methods

pure :: a -> XlebT m a #

(<*>) :: XlebT m (a -> b) -> XlebT m a -> XlebT m b #

(*>) :: XlebT m a -> XlebT m b -> XlebT m b #

(<*) :: XlebT m a -> XlebT m b -> XlebT m a #

Monad m => Alternative (XlebT m) Source # 

Methods

empty :: XlebT m a #

(<|>) :: XlebT m a -> XlebT m a -> XlebT m a #

some :: XlebT m a -> XlebT m [a] #

many :: XlebT m a -> XlebT m [a] #

runXlebT :: Monad m => String -> XlebT m t -> m (Either XlebError t) Source #

Run a XlebT computation over a string containing XML data, producing either the resulting monadic value or an error. If the XML data contained in the argument string is invalid, then this will fail with XEBadXML.

Errors

data XlebError Source #

The XlebError type describes the various errors that can occur in the course of parsing an XML structure. If you simply want the human-readable string that corresponds to your error, then use the errorString function.

Constructors

XEInElem String XlebError

Describes the element context in which an error occurred

XEInAttr String XlebError

Describes the attribute context in which an error occurred

XEParseFailure String

Some parser function was unable to produce a value from the string embedded in an XML element

XENoSuchAttribute String

A XlebT computation required an attribute that wasn't found in the specified element.

XEUnexpectedElement String String

A XlebT computation expected one element but found another

XENoMatchingElement Selector

A XlebT computation used a selector which did not successfully describe any child elements

XEAmbiguousElement Selector

A XlebT computation used a selector as though it would unambiguously name a single child, but instead multiple child elements matched the selector

XEBadXML

The "xml" library was unable to parse the document as XML.

XOtherError String

Another error occurred which was not described by the above constructors

errorString :: XlebError -> String Source #

Convert a XlebError value to the corresponding human-readable string.

Element Structure

elem :: Monad m => String -> XlebT m t -> XlebT m t Source #

elem n t will ensure that the currently focused element is a tag named n and will then evaluate it using the computation t. This will fail with XEUnexpectedElement if the tag is named something else.

attr :: Monad m => String -> Parse t -> XlebT m t Source #

Find an attribute on the current focus element and parse it to a value of type t. If the parse function fails, then this will fail with XEParseFailure.

contents :: Monad m => Parse t -> XlebT m t Source #

Take the string content of the current element and parse it to a value of type t. If the parse function fails, then this will fail with XEParseFailure.

rawElement :: Monad m => XlebT m Element Source #

Access the raw underlying XML element that we are processing. This is sometimes necessary for working with free-form XML data.

child :: Monad m => Selector -> XlebT m t -> XlebT m t Source #

Use a Selector that unambiguously identifies a single child element of the current element and then parse it according to a given XlebT computation focused on that element. If no child matches the provided Selector, then this will fail with XENoMatchingElement. If multiple children match the provided Selector, then this will fail with XEAmbiguousElement.

children :: Monad m => Selector -> XlebT m t -> XlebT m [t] Source #

Use a Selector that identifies some child elements of the current element and parse each according to a given XlebT computation, which will be repeated with focus on each child element, and returning the resulting values as a list. If no child elements match the Selector, then this will return an empty list.

Parsing contained string data

type Parse t = String -> Either String t Source #

A value of type Parse t is a function that can either produce a value of type t or fail with a string message.

string :: Parse String Source #

A Parse function that accepts arbitrary string input without failing.

number :: (Read n, Num n) => Parse n Source #

A Parse function that parses numeric values according to their Haskell Read instance.

reader :: Read a => Parse a Source #

A Parse function that parses Haskell values according to their Read instance.

Selecting Elements

data Selector Source #

A Selector represents some criteria by which child elements are matched.

byTag :: String -> Selector Source #

Creates a Selector which expects an exact tag name.

any :: Selector Source #

Creates a Selector which matches any possible child element.