xmlbf-0.5: XML back and forth! Parser, renderer, ToXml, FromXml, fixpoints.

Safe HaskellNone
LanguageHaskell2010

Xmlbf

Contents

Description

XML back and forth!

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

xmlbf provides a FromXml class intended to be used as the familiar FromJSON from the aeson package. This relies on the Parser type and the related tools.

xmlbf provides a ToXml class intended to be used as the familiar toJSON from the aeson package.

xmlb provides tools like dfpos and dfposM for finding a fixpoint of a XML structure.

Synopsis

Parsing

class FromXml a where Source #

Minimal complete definition

fromXml

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) == Right a

data Parser a Source #

XML parser monad. To be run with runParser.

You can build a Parser using pElement, pAttr, pAttrs, pText, pFail, or any of the Applicative, Alternative or Monad combinators.

Instances
Monad Parser Source # 
Instance details

Methods

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

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

return :: a -> Parser a #

fail :: String -> Parser a #

Functor Parser Source # 
Instance details

Methods

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

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

MonadFail Parser Source # 
Instance details

Methods

fail :: String -> Parser a #

Applicative Parser Source # 
Instance details

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 #

Alternative Parser Source #

Backtracks.

Instance details

Methods

empty :: Parser a #

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

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

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

MonadPlus Parser Source #

Backtracks.

Instance details

Methods

mzero :: Parser a #

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

runParser :: Parser a -> [Node] -> Either String a Source #

Run a parser on an XML fragment body. If the parser fails, then a String with an error message is returned.

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.

pFail :: String -> Parser a Source #

A Parser that always fails with the given error message.

pElement :: Text -> Parser a -> Parser a Source #

pElement "foo" p runs a Parser p inside a element node named "foo". This 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 element from the parser state.

pAnyElement :: Parser a -> Parser a Source #

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 element from the parser state.

pName :: Parser Text Source #

Returns the name of the currently selected element.

This parser fails if there's no currently selected element.

Doesn't modify the parser state.

pAttr :: Text -> Parser Text Source #

Return the value of the requested attribute, if defined. May return an empty string in case the attribute is defined but no value was given to it.

This parser fails if there's no currently selected element.

Consumes the attribute from the parser state.

pAttrs :: Parser (HashMap Text Text) Source #

Returns all of the available element attributes. May return empty strings 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.

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

pChildren :: Parser [Node] Source #

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 of the returned nodes from the parser state.

pText :: Parser Text Source #

Return a text node value.

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)

The returned text is consumed 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

class ToXml a where Source #

Minimal complete definition

toXml

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

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.

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
Eq Node Source # 
Instance details

Methods

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

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

Show Node Source # 
Instance details

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

NFData Node Source # 
Instance details

Methods

rnf :: Node -> () #

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.

-> HashMap Text Text

Attributes.

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

-> HashMap Text Text

Attributes.

-> [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 :: Text -> [Node] Source #

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, whenever you know the input is valid.

text' :: Text -> Either String Node Source #

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.