xmlbf-0.7: XML back and forth! Parser, renderer, ToXml, FromXml, fixpoints.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Xmlbf

Description

XML back and forth!

xmlbf provides high-level tools for encoding and decoding XML.

xmlbf provides tools like dfpos and dfposM for finding a fixpoint of an XML fragment.

xmlbf provides FromXml and ToXml typeclasses intended to be used as the familiar FromJSON and ToXml from the aeson package.

xmlbf doesn't do any parsing of raw XML on its own. Instead, one should use xmlbf together with libraries like xmlbf-xeno or xmlbf-xmlhtml for this.

Synopsis

Parsing

parse Source #

Arguments

:: Parser a

Parser to run.

-> [Node]

XML fragment body to parse. That is, top-level XML Nodes.

-> Either String a

If parsing fails, a String with an error message is returned. Otherwise, the parser output a is returned.

Pure version of parseM.

parseM Source #

Arguments

:: Applicative m 
=> ParserT m a

Parser to run.

-> [Node]

XML fragment body to parse. That is, top-level XML Nodes.

-> m (Either String a)

If parsing fails, a String with an error message is returned. Otherwise, the parser output a is returned.

Run a ParserT on an XML fragment body.

Notice that this function doesn't enforce that all input is consumed. If you want that behavior, then please use pEndOfInput in the given ParserT.

Low-level

type Parser = ParserT Identity :: Type -> Type Source #

Parser a is a type synonym for Parser Identity a.

data ParserT (m :: Type -> Type) (a :: Type) Source #

XML parser for a value of type a.

This parser runs on top of some Monad m, making ParserT a suitable monad transformer.

You can build a ParserT using pElement, pAnyElement, pName, pAttr, pAttrs, pChildren, pText, pEndOfInput, any of the Applicative, Alternative or Monad combinators, or you can use parserT directly.

Run a ParserT using parse, parseM or runParserT

Instances

Instances details
MonadTrans ParserT Source # 
Instance details

Defined in Xmlbf

Methods

lift :: Monad m => m a -> ParserT m a #

MFunctor ParserT Source # 
Instance details

Defined in Xmlbf

Methods

hoist :: forall m n (b :: k). Monad m => (forall a. m a -> n a) -> ParserT m b -> ParserT n b #

MonadError e m => MonadError e (ParserT m) Source # 
Instance details

Defined in Xmlbf

Methods

throwError :: e -> ParserT m a #

catchError :: ParserT m a -> (e -> ParserT m a) -> ParserT m a #

MonadReader r m => MonadReader r (ParserT m) Source # 
Instance details

Defined in Xmlbf

Methods

ask :: ParserT m r #

local :: (r -> r) -> ParserT m a -> ParserT m a #

reader :: (r -> a) -> ParserT m a #

MonadState s m => MonadState s (ParserT m) Source # 
Instance details

Defined in Xmlbf

Methods

get :: ParserT m s #

put :: s -> ParserT m () #

state :: (s -> (a, s)) -> ParserT m a #

Monad m => MonadFail (ParserT m) Source # 
Instance details

Defined in Xmlbf

Methods

fail :: String -> ParserT m a #

MonadFix m => MonadFix (ParserT m) Source # 
Instance details

Defined in Xmlbf

Methods

mfix :: (a -> ParserT m a) -> ParserT m a #

MonadIO m => MonadIO (ParserT m) Source # 
Instance details

Defined in Xmlbf

Methods

liftIO :: IO a -> ParserT m a #

MonadZip m => MonadZip (ParserT m) Source # 
Instance details

Defined in Xmlbf

Methods

mzip :: ParserT m a -> ParserT m b -> ParserT m (a, b) #

mzipWith :: (a -> b -> c) -> ParserT m a -> ParserT m b -> ParserT m c #

munzip :: ParserT m (a, b) -> (ParserT m a, ParserT m b) #

Monad m => Alternative (ParserT m) Source #

ma <|> mb backtracks the internal parser state before running mb.

Instance details

Defined in Xmlbf

Methods

empty :: ParserT m a #

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

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

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

Monad m => Applicative (ParserT m) Source #

The Monad superclass is necessary because ParserT shortcircuits like ExceptT.

Instance details

Defined in Xmlbf

Methods

pure :: a -> ParserT m a #

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

liftA2 :: (a -> b -> c) -> ParserT m a -> ParserT m b -> ParserT m c #

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

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

Functor m => Functor (ParserT m) Source # 
Instance details

Defined in Xmlbf

Methods

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

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

Monad m => Monad (ParserT m) Source # 
Instance details

Defined in Xmlbf

Methods

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

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

return :: a -> ParserT m a #

Monad m => MonadPlus (ParserT m) Source #

mplus ma mb backtracks the internal parser state before running mb.

Instance details

Defined in Xmlbf

Methods

mzero :: ParserT m a #

mplus :: ParserT m a -> ParserT m a -> ParserT m a #

MonadCatch m => MonadCatch (ParserT m) Source # 
Instance details

Defined in Xmlbf

Methods

catch :: Exception e => ParserT m a -> (e -> ParserT m a) -> ParserT m a #

MonadMask m => MonadMask (ParserT m) Source # 
Instance details

Defined in Xmlbf

Methods

mask :: ((forall a. ParserT m a -> ParserT m a) -> ParserT m b) -> ParserT m b #

uninterruptibleMask :: ((forall a. ParserT m a -> ParserT m a) -> ParserT m b) -> ParserT m b #

generalBracket :: ParserT m a -> (a -> ExitCase b -> ParserT m c) -> (a -> ParserT m b) -> ParserT m (b, c) #

MonadThrow m => MonadThrow (ParserT m) Source # 
Instance details

Defined in Xmlbf

Methods

throwM :: Exception e => e -> ParserT m a #

Monad m => Selective (ParserT m) Source # 
Instance details

Defined in Xmlbf

Methods

select :: ParserT m (Either a b) -> ParserT m (a -> b) -> ParserT m b #

(Monad m, Monoid a) => Monoid (ParserT m a) Source # 
Instance details

Defined in Xmlbf

Methods

mempty :: ParserT m a #

mappend :: ParserT m a -> ParserT m a -> ParserT m a #

mconcat :: [ParserT m a] -> ParserT m a #

(Monad m, Semigroup a) => Semigroup (ParserT m a) Source # 
Instance details

Defined in Xmlbf

Methods

(<>) :: ParserT m a -> ParserT m a -> ParserT m a #

sconcat :: NonEmpty (ParserT m a) -> ParserT m a #

stimes :: Integral b => b -> ParserT m a -> ParserT m a #

parserT Source #

Arguments

:: (ParserState -> m (ParserState, Either String a))

Given a parser's internal state, obtain an a if possible, otherwise return a String describing the parsing failure. A new state with leftovers is returned.

-> ParserT m a 

parserT is the most general way or building a ParserT.

Notice that ParserState's internals are not exported, so you won't be able to do much with it other than pass it around.

runParserT . parserT  ==  id

runParserT Source #

Arguments

:: ParserT m a

Parser to run.

-> ParserState

Initial parser state. You can obtain this from initialParserState or from a previous execution of runParserT.

-> m (ParserState, Either String a)

Returns the leftover parser state, as well as an a in case parsing was successful, or a String with an error message otherwise.

runParserT is the most general way or running a ParserT.

As a simpler alternative to runParserT, consider using parseM, or even parse if you don't need transformer functionality.

Notice that ParserState's internals are not exported, so you won't be able to do much with it other than pass it around.

runParserT . parserT  ==  id

data ParserState Source #

Internal parser state.

Instances

Instances details
Eq ParserState Source # 
Instance details

Defined in Xmlbf

initialParserState :: [Node] -> ParserState Source #

Construct an initial ParserState to use with runParserT from zero or more top-level Nodes.

Parsers

pElement Source #

Arguments

:: Monad m 
=> Text

Element name as strict Text.

-> ParserT m a

ParserT to run inside the matched Element.

-> ParserT m a 

pElement "foo" p runs a ParserT p inside a Element node named "foo". This parser fails if such element does not exist at the current position.

Leading whitespace is ignored. If you need to preserve that whitespace for some reason, capture it using pText before using pElement.

Consumes the matched element from the parser state.

pAnyElement Source #

Arguments

:: Monad m 
=> ParserT m a

ParserT to run inside any matched Element.

-> ParserT m a 

pAnyElement p runs a ParserT p inside the Element node at the current position, if any. Otherwise, if no such element exists, this parser fails.

You can recover the name of the matched element using pName inside the given ParserT. However, if you already know beforehand the name of the element that you want to match, it's better to use pElement rather than pAnyElement.

Leading whitespace is ignored. If you need to preserve that whitespace for some reason, capture it using pText before using pAnyElement.

Consumes the matched element from the parser state.

pName Source #

Arguments

:: Applicative m 
=> ParserT m Text

Element name as strict Text.

Returns the name of the currently selected Element.

This parser fails if there's no currently selected Element (see pElement, pAnyElement).

Doesn't modify the parser state.

pAttr Source #

Arguments

:: Applicative m 
=> Text

Attribute name as strict Text.

-> ParserT m Text

Attribute value as strict Text, possibly empty.

Return the value of the requested attribute, if defined, as strict Text. Returns an empty strict Text in case the attribute is defined but no value was given to it.

This parser fails if there's no currently selected Element (see pElement, pAnyElement).

Consumes the matched attribute from the parser state.

pAttrs Source #

Arguments

:: Applicative m 
=> ParserT m (HashMap Text Text)

Pairs of attribute names and possibly empty values, as strict Text.

Returns all of the available element attributes.

Returns empty strict Text as values in case an attribute is defined but no value was given to it.

This parser fails if there's no currently selected Element (see pElement, pAnyElement).

Consumes all the attributes for this element from the parser state.

pChildren Source #

Arguments

:: Applicative m 
=> ParserT m [Node]

Nodes in their original order.

Returns all of the immediate children of the current element.

If parsing top-level nodes rather than a particular element (that is, if pChildren is not being run inside pElement), then all of the top level Nodes will be returned.

Consumes all the returned nodes from the parser state.

pText Source #

Arguments

:: Applicative m 
=> ParserT m Text

Content of the text node as a strict Text.

Returns the contents of a text node as a strict Text.

Surrounidng whitespace is not removed, as it is considered to be part of the text node.

If there is no text node at the current position, then this parser fails. This implies that pText never returns an empty strict Text, since there is no such thing as a text node without text.

Please note that consecutive text nodes are always concatenated and returned together.

parse pText (text "Ha" <> text "sk" <> text "ell")
    == Right (text Haskell)

Consumes the text from the parser state. This implies that if you perform two consecutive pText calls, the second will always fail.

parse (pText >> pText) (text "Ha" <> text "sk" <> text "ell")
    == Left "Missing text node"

pTextLazy Source #

Arguments

:: Applicative m 
=> ParserT m Text

Content of the text node as a lazy Text.

Like pText, but returns a lazy Text.

pEndOfInput :: Applicative m => ParserT m () Source #

Succeeds if all of the elements, attributes and text nodes have been consumed.

Rendering

encode :: [Node] -> Builder Source #

Encodes a list of XML Nodes, representing an XML fragment body, to an UTF8-encoded and XML-escaped bytestring.

This function doesn't render self-closing elements. Instead, all elements have a corresponding closing tag.

Also, it doesn't render CDATA sections. Instead, all text is escaped as necessary.

Element attributes are rendered in alphabetical order.

Nodes

data Node Source #

Either a text or an element node in an XML fragment body.

Construct with text, textLazy or element.

Destruct with Text, TextLazy or Element.

Instances

Instances details
Show Node Source # 
Instance details

Defined in Xmlbf

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

NFData Node Source # 
Instance details

Defined in Xmlbf

Methods

rnf :: Node -> () #

Eq Node Source # 
Instance details

Defined in Xmlbf

Methods

(==) :: Node -> Node -> Bool #

(/=) :: Node -> Node -> Bool #

node Source #

Arguments

:: (Text -> HashMap Text Text -> [Node] -> a)

Transform an Element node.

-> (Text -> a)

Transform a TextLazy node.

-> Node 
-> a 

Case analysis for a Node.

Element

pattern Element Source #

Arguments

:: Text

Element name as strict Text.

-> HashMap Text Text

Pairs of attribute names and possibly empty values, as strict Text.

-> [Node]

Element children.

-> Node 

Destruct an element Node.

case n :: Node of
  Element t as cs -> ...
  _ -> ...

element Source #

Arguments

:: Text

Element name as a strict Text.

-> HashMap Text Text

Pairs of attribute names and possibly empty values, as strict Text.

-> [Node]

Children.

-> [Node] 

Construct a XML fragment body containing a single Element Node, if possible.

This function will return empty list if it is not possible to construct the Element with the given input. To learn more about why it was not possible to construct it, use element instead.

Using element' rather than element is recommended, so that you are forced to acknowledge a failing situation in case it happens. However, element is at times more convenient to use, whenever you know the input is valid.

element' Source #

Arguments

:: Text

Element name as a strict Text.

-> HashMap Text Text

Pairs of attribute names and possibly empty values, as strict Text.

-> [Node]

Children.

-> Either String Node 

Construct an Element Node.

Returns Left if the Element Node can't be created, with an explanation of why.

Text (strict)

pattern Text Source #

Arguments

:: Text

Strict Text.

-> Node 

Destruct a text Node into a strict Text.

case n :: Node of
  Text t -> ...
  _ -> ...

text Source #

Arguments

:: Text

Strict Text.

-> [Node] 

Construct a XML fragment body containing a single text Node, if given Text not empty.

This function will return empty list if it is not possible to construct the Text with the given input. To learn more about why it was not possible to construct it, use text' instead.

Using text' rather than text is recommended, so that you are forced to acknowledge a failing situation in case it happens. However, text is at times more convenient to use. For example, when you know statically the input is valid.

text' Source #

Arguments

:: Text

Strict Text.

-> Either String Node 

Construct a text Node, if given Text not empty.

Returns Left if the Text Node can't be created, with an explanation of why.

Text (lazy)

pattern TextLazy Source #

Arguments

:: Text

Lazy Text.

-> Node 

Destruct a text Node into a lazy Text.

case n :: Node of
  TextLazy tl -> ...
  _ -> ...

textLazy Source #

Arguments

:: Text

Lazy Text.

-> [Node] 

A version of text working with lazy Text.

textLazy' Source #

Arguments

:: Text

Lazy Text.

-> Either String Node 

A version of text' working with lazy Text.

Fixpoints

dfpos :: ((Node -> [Node]) -> Node -> [Node]) -> Node -> [Node] Source #

Post-order depth-first replacement of Node and all of its children.

This function works like fix, but the given function is trying to find a fixpoint for the individual children nodes, not for the root node.

For example, the following function renames every node named "w" to "y", and every node named "y" to "z". It accomplishes this by first renaming "w" nodes to "x", and then, by using k recursively to further rename all "x" nodes (including the ones that were just created) to "y" in a post-order depth-first manner. After renaming an "x" node to "y", the recursion stops (i.e., k is not used), so our new "y" nodes won't be further renamed to "z". However, nodes that were named "y" initially will be renamed to "z".

In our example we only replace one node with another, but a node can be replaced with zero or more nodes, depending on the length of the resulting list.

foo :: Node -> [Node]
foo = dfpos $ \k -> \case
    Element "w" as cs -> element "x" as cs >>= k
    Element "x" as cs -> element "y" as cs
    Element "y" as cs -> element "z" as cs >>= k

See dfpre for pre-orderd depth-first replacement.

WARNING If you call k in every branch, then dfpos will never terminate. Make sure the recursion stops at some point by simply returning a list of nodes instead of calling k.

dfposM :: Monad m => ((Node -> m [Node]) -> Node -> m [Node]) -> Node -> m [Node] Source #

Monadic version of dfpos.

dfpre :: ((Node -> [Node]) -> Node -> [Node]) -> Node -> [Node] Source #

Pre-order depth-first replacement of Node and all of its children.

This is just like dfpos but the search proceeds in a different order.

dfpreM :: Monad m => ((Node -> m [Node]) -> Node -> m [Node]) -> Node -> m [Node] Source #

Monadic version of dfpre.

Typeclasses

class FromXml a where Source #

Methods

fromXml :: Monad m => ParserT m a Source #

Parses an XML fragment body into a value of type a.

If a ToXml instance for a exists, then:

parse fromXml (toXml a)  ==  Right a

class ToXml a where Source #

Methods

toXml :: a -> [Node] Source #

Renders a value of type a into an XML fragment body.

If a FromXml instance for a exists, then:

parse fromXml (toXml a)  ==  Right a