xmlbf-0.6.2: 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

runParser 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, we the parser output a is returned.

Run a Parser 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 Parser.

data Parser a Source #

XML parser for a value of type a.

You can build a Parser using pElement, pAnyElement, pName, pAttr, pAttrs, pChildren, pText, pEndOfInput, any of the Applicative, Alternative, Monad or related combinators.

Run a Parser using runParser.

Instances

Instances details
MonadFail Parser Source # 
Instance details

Defined in Xmlbf

Methods

fail :: String -> Parser a #

MonadFix Parser Source # 
Instance details

Defined in Xmlbf

Methods

mfix :: (a -> Parser a) -> Parser a #

MonadZip Parser Source # 
Instance details

Defined in Xmlbf

Methods

mzip :: Parser a -> Parser b -> Parser (a, b) #

mzipWith :: (a -> b -> c) -> Parser a -> Parser b -> Parser c #

munzip :: Parser (a, b) -> (Parser a, Parser b) #

Alternative Parser Source #

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

Instance details

Defined in Xmlbf

Methods

empty :: Parser a #

(<|>) :: Parser a -> Parser a -> Parser a #

some :: Parser a -> Parser [a] #

many :: Parser a -> Parser [a] #

Applicative Parser Source # 
Instance details

Defined in Xmlbf

Methods

pure :: a -> Parser a #

(<*>) :: Parser (a -> b) -> Parser a -> Parser b #

liftA2 :: (a -> b -> c) -> Parser a -> Parser b -> Parser c #

(*>) :: Parser a -> Parser b -> Parser b #

(<*) :: Parser a -> Parser b -> Parser a #

Functor Parser Source # 
Instance details

Defined in Xmlbf

Methods

fmap :: (a -> b) -> Parser a -> Parser b #

(<$) :: a -> Parser b -> Parser a #

Monad Parser Source # 
Instance details

Defined in Xmlbf

Methods

(>>=) :: Parser a -> (a -> Parser b) -> Parser b #

(>>) :: Parser a -> Parser b -> Parser b #

return :: a -> Parser a #

MonadPlus Parser Source #

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

Instance details

Defined in Xmlbf

Methods

mzero :: Parser a #

mplus :: Parser a -> Parser a -> Parser a #

Selective Parser Source # 
Instance details

Defined in Xmlbf

Methods

select :: Parser (Either a b) -> Parser (a -> b) -> Parser b #

Monoid a => Monoid (Parser a) Source # 
Instance details

Defined in Xmlbf

Methods

mempty :: Parser a #

mappend :: Parser a -> Parser a -> Parser a #

mconcat :: [Parser a] -> Parser a #

Semigroup a => Semigroup (Parser a) Source # 
Instance details

Defined in Xmlbf

Methods

(<>) :: Parser a -> Parser a -> Parser a #

sconcat :: NonEmpty (Parser a) -> Parser a #

stimes :: Integral b => b -> Parser a -> Parser a #

Parsers

pElement Source #

Arguments

:: Text

Element name as strict Text.

-> Parser a

Parser to run inside the matched Element.

-> Parser a 

pElement "foo" p runs a 'Parser 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

:: Parser a

Parser to run inside any matched Element.

-> Parser a 

pAnyElement p runs a Parser 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 Parser. 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

:: Parser 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

:: Text

Attribute name as strict Text.

-> Parser Text

Attribute value as strict Text, possibly empty.

Return the value of the requested attribute, if defined. Returns an empty 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

:: Parser (HashMap Text Text)

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

Returns all of the available element attributes.

Returns empty 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

:: Parser [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

:: Parser Text

Content of the text node as a lazy Text.

Returns the contents of a Text node.

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 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.

runParser 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.

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

pEndOfInput :: Parser () 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 or element. Destruct with Text 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 Text node.

-> Node 
-> a 

Case analysis for a Node.

pattern Element :: Text -> HashMap Text Text -> [Node] -> Node Source #

Destruct an element Node.

element Source #

Arguments

:: Text

Element' name as a strict Text.

-> HashMap Text Text

Attributes as strict Text pairs.

-> [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

Attributes as strict Text pairs.

-> [Node]

Children.

-> Either String Node 

Construct an Element Node.

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

pattern Text :: Text -> Node Source #

Destruct a text Node.

text Source #

Arguments

:: Text

Lazy Text.

-> [Node] 

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

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

Lazy Text.

-> Either String Node 

Construct a Text Node, if possible.

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

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 :: Parser a Source #

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

If a ToXml instance for a exists, then:

runParser fromXml (toXml a) == pure (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:

runParser fromXml (toXml a) == Right a