xmlbf-0.3: 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 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 element, pAttr, pAttrs, pText, pRead, or any of the Applicative, Alternative or Monad combinators.

Instances

Monad Parser Source # 

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 # 

Methods

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

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

MonadFail Parser Source # 

Methods

fail :: String -> Parser a #

Applicative Parser Source # 

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.

Methods

empty :: Parser a #

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

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

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

MonadPlus Parser Source #

Backtracks.

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

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.

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

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.

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

pText :: Parser Text Source #

Return a text node value (including CDATA).

Consumes the text node from the parser state.

Law: When two consecutive calls to pText are made, the first call returns all of the available consecutive text, and the second call always fails.

pRead :: (Typeable a, Read a) => Text -> Parser a Source #

Parses a value that can be read.

Consumes the raw string from the parser state.

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.

If a FromXml instance for a exists, then:

runParser fromXml (toXml a) == Right a

encode :: [Node] -> Builder Source #

Encodes a list of XML Nodes to an UTF8-encoded and XML-escaped bytestring.

data Node Source #

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

Construct with text or element. Destruct with Text or Element.

Instances

Eq Node Source # 

Methods

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

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

Show Node Source # 

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

IsString Node Source #

Constructs a Text.

Methods

fromString :: String -> 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.

-> Either String Node

Returns Left if the element name, or atribute names, or attribute values are invalid.

TODO: We just check for emptyness currently.

Construct an element Node.

element' Source #

Arguments

:: Text

Element' name.

-> HashMap Text Text

Attributes.

-> [Node]

Children.

-> Node 

Unsafe version of element, causing a runtime error in situations where element would return Left. So, don't use this unless you know what you are doing.

pattern Text :: Text -> Node Source #

Destruct a text Node.

text :: Text -> Node Source #

Construct a text Node.

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 -> let Right e = element "x" as cs in k e
    Element "x" as cs -> let Right e = element "y" as cs in [e]
    Element "y" as cs -> let Right e = element "z" as cs in k e

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.