Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- parse :: Parser a -> [Node] -> Either String a
- parseM :: Applicative m => ParserT m a -> [Node] -> m (Either String a)
- type Parser = ParserT Identity :: Type -> Type
- data ParserT (m :: Type -> Type) (a :: Type)
- parserT :: (ParserState -> m (ParserState, Either String a)) -> ParserT m a
- runParserT :: ParserT m a -> ParserState -> m (ParserState, Either String a)
- data ParserState
- initialParserState :: [Node] -> ParserState
- pElement :: Monad m => Text -> ParserT m a -> ParserT m a
- pAnyElement :: Monad m => ParserT m a -> ParserT m a
- pName :: Applicative m => ParserT m Text
- pAttr :: Applicative m => Text -> ParserT m Text
- pAttrs :: Applicative m => ParserT m (HashMap Text Text)
- pChildren :: Applicative m => ParserT m [Node]
- pText :: Applicative m => ParserT m Text
- pTextLazy :: Applicative m => ParserT m Text
- pEndOfInput :: Applicative m => ParserT m ()
- 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
- pattern TextLazy :: Text -> Node
- textLazy :: Text -> [Node]
- textLazy' :: 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]
- class FromXml a where
- class ToXml a where
Parsing
:: Parser a | Parser to run. |
-> [Node] | XML fragment body to parse. That is, top-level XML |
-> Either String a | If parsing fails, a |
Pure version of parseM
.
:: Applicative m | |
=> ParserT m a | Parser to run. |
-> [Node] | XML fragment body to parse. That is, top-level XML |
-> m (Either String a) | If parsing fails, a |
Run a ParserT
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 ParserT
.
Low-level
data ParserT (m :: Type -> Type) (a :: Type) Source #
XML parser for a value of type a
.
This parser runs on top of some Monad
m
,
making ParserT
a suitable monad transformer.
You can build a ParserT
using pElement
, pAnyElement
, pName
,
pAttr
, pAttrs
, pChildren
, pText
, pEndOfInput
, any of the
Applicative
, Alternative
or Monad
combinators, or you can
use parserT
directly.
Run a ParserT
using parse
, parseM
or runParserT
Instances
:: (ParserState -> m (ParserState, Either String a)) | Given a parser's internal state, obtain an |
-> ParserT m a |
parserT
is the most general way or building a ParserT
.
Notice that ParserState'
s internals are not exported, so you won't be
able to do much with it other than pass it around.
runParserT
.parserT
==id
:: ParserT m a | Parser to run. |
-> ParserState | Initial parser state. You can obtain this from
|
-> m (ParserState, Either String a) | Returns the leftover parser state, as well as an |
runParserT
is the most general way or running a ParserT
.
As a simpler alternative to runParserT
, consider using parseM
, or even parse
if you don't need transformer functionality.
Notice that ParserState'
s internals are not exported, so you won't be
able to do much with it other than pass it around.
runParserT
.parserT
==id
data ParserState Source #
Internal parser state.
Instances
Eq ParserState Source # | |
Defined in Xmlbf (==) :: ParserState -> ParserState -> Bool # (/=) :: ParserState -> ParserState -> Bool # |
initialParserState :: [Node] -> ParserState Source #
Construct an initial ParserState
to use with runParserT
from zero or
more top-level Node
s.
Parsers
runs a pElement
"foo" pParserT
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.
runs a pAnyElement
pParserT
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 ParserT
. 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.
:: Applicative m | |
=> ParserT m Text | Element name as strict |
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.
:: Applicative m | |
=> Text | Attribute name as strict |
-> ParserT m Text |
Return the value of the requested attribute, if defined, as strict
Text
. Returns an empty
strict 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.
:: Applicative m | |
=> ParserT m (HashMap Text Text) | Pairs of attribute names and possibly |
Returns all of the available element attributes.
Returns empty
strict 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.
:: Applicative m | |
=> ParserT m [Node] |
|
:: Applicative m | |
=> ParserT m Text | Content of the text node as a strict |
Returns the contents of a text node as a strict Text
.
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 strict
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.
parse
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.
parse
(pText
>>pText
) (text
"Ha" <>text
"sk" <>text
"ell") ==Left
"Missing text node"
:: Applicative m | |
=> ParserT m Text | Content of the text node as a lazy |
pEndOfInput :: Applicative m => ParserT m () 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.
Element attributes are rendered in alphabetical order.
Nodes
:: (Text -> HashMap Text Text -> [Node] -> a) | Transform an |
-> (Text -> a) | Transform a |
-> Node | |
-> a |
Case analysis for a Node
.
Element
:: Text | Element name as a strict |
-> HashMap Text Text | Pairs of attribute names and possibly |
-> [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.
Text (strict)
Construct a XML fragment body containing a single text Node
, if given
Text
not empty.
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 (lazy)
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
.
dfpreM :: Monad m => ((Node -> m [Node]) -> Node -> m [Node]) -> Node -> m [Node] Source #
Monadic version of dfpre
.