Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- class FromXml a where
- data Parser a
- runParser :: Parser a -> [Node] -> Either String a
- pFail :: String -> Parser a
- pElement :: Text -> Parser a -> Parser a
- pAnyElement :: Parser a -> Parser a
- pName :: Parser Text
- pAttr :: Text -> Parser Text
- pAttrs :: Parser (HashMap Text Text)
- pChildren :: Parser [Node]
- pText :: Parser Text
- pEndOfInput :: Parser ()
- class ToXml a where
- encode :: [Node] -> Builder
- data Node
- node :: (Text -> HashMap Text Text -> [Node] -> a) -> (Text -> a) -> Node -> a
- pattern Element :: Text -> HashMap Text Text -> [Node] -> Node
- element :: Text -> HashMap Text Text -> [Node] -> [Node]
- element' :: Text -> HashMap Text Text -> [Node] -> Either String Node
- pattern Text :: Text -> Node
- text :: Text -> [Node]
- text' :: Text -> Either String Node
- dfpos :: ((Node -> [Node]) -> Node -> [Node]) -> Node -> [Node]
- dfposM :: Monad m => ((Node -> m [Node]) -> Node -> m [Node]) -> Node -> m [Node]
- dfpre :: ((Node -> [Node]) -> Node -> [Node]) -> Node -> [Node]
- dfpreM :: Monad m => ((Node -> m [Node]) -> Node -> m [Node]) -> Node -> m [Node]
Parsing
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.
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
.
pElement :: Text -> Parser a -> Parser a Source #
runs a pElement
"foo" pParser
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 #
runs a pAnyElement
pParser
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.
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.
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
encode :: [Node] -> Builder Source #
Encodes a list of XML Node
s, 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.
:: (Text -> HashMap Text Text -> [Node] -> a) | Transform an |
-> (Text -> a) | Transform a |
-> Node | |
-> a |
Case analysis for a 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.
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.
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 -> \caseElement
"w" as cs ->element'
"x" as cs >>= kElement
"x" as cs ->element'
"y" as csElement
"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
.