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.
- class FromXml a where
- data Parser a
- runParser :: Parser a -> [Node] -> Either String a
- pElement :: Text -> Parser a -> Parser a
- pAttr :: Text -> Parser Text
- pAttrs :: Parser (HashMap Text Text)
- pText :: Parser Text
- pRead :: (Typeable a, Read a) => Text -> Parser a
- pEndOfInput :: Parser ()
- class ToXml a where
- encode :: [Node] -> Builder
- data Node
- pattern Element :: Text -> HashMap Text Text -> [Node] -> Node
- element :: Text -> HashMap Text Text -> [Node] -> Either String Node
- element' :: Text -> HashMap Text Text -> [Node] -> Node
- pattern Text :: Text -> Node
- text :: Text -> 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
,
pRead
, or any of the Applicative
, Alternative
or Monad
combinators.
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 #
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.
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.
Return a text node value (including CDATA).
Consumes the text node from the parser state. Surrounding whitespace is not removed.
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
encode :: [Node] -> Builder Source #
Encodes a list of XML Node
s to an UTF8-encoded and XML-escaped
bytestring.
:: Text | Element' name. |
-> HashMap Text Text | Attributes. |
-> [Node] | Children. |
-> Either String Node | Returns TODO: We just check for emptyness currently. |
Construct an element 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 -> \caseElement
"w" as cs -> k (element'
"x" as cs)Element
"x" as cs -> [element'
"y" as cs]Element
"y" as cs -> k (element'
"z" as cs)
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
.