Safe Haskell | None |
---|
- class IsXML a where
- xmlPickler :: PU [UNode ByteString] a
- encodeXML :: IsXML a => a -> ByteString
- decodeXML :: IsXML a => ByteString -> Either String a
- data PU t a = PU {
- unpickleTree :: t -> a
- unpickleTree' :: t -> Either String a
- pickleTree :: a -> t
- data GenericXMLOptions = GenericXMLOptions {
- constructorTagModifier :: String -> String
- fieldLabelModifier :: String -> String
- defaultXMLOptions :: Options
- genericXMLPickler :: (Generic x, GIsXML t (Rep x)) => Options -> PU t x
- xpSum :: PU t (f r) -> PU t (g r) -> PU t ((f :+: g) r)
- xpEither :: PU t a -> PU t b -> PU t (Either a b)
- xpGenericString :: GenericXMLString t => PU [UNode ByteString] t
- xpText0 :: PU text text
- xpText :: GenericXMLString text => PU text text
- xpList0 :: Show tag => PU [Node tag text] a -> PU [Node tag text] [a]
- xpList :: Show tag => PU [Node tag text] a -> PU [Node tag text] [a]
- xpContent :: GenericXMLString text => PU text a -> PU [Node tag text] a
- xpPrim :: (Read b, Show b, GenericXMLString t) => PU [Node a t] b
- xpWrap :: (a -> b, b -> a) -> PU t a -> PU t b
Class
xmlPickler :: PU [UNode ByteString] aSource
Functions
encodeXML :: IsXML a => a -> ByteStringSource
Re-exported Data Types
data PU t a
A two-way pickler/unpickler that pickles an arbitrary
data type ''a'' to a part of an XML tree ''t''.
A PU
can be composed using the pickler primitives defined in this module.
unpickleTree, unpickleTree' and pickleTree should be used directly by the caller.
PU | |
|
Options
data GenericXMLOptions Source
GenericXMLOptions | |
|
defaultXMLOptions :: OptionsSource
Generics
genericXMLPickler :: (Generic x, GIsXML t (Rep x)) => Options -> PU t xSource
Combinators
xpGenericString :: GenericXMLString t => PU [UNode ByteString] tSource
Re-exported Combinators
xpText :: GenericXMLString text => PU text text
Convert XML text content <-> String. Empty strings result in unpickle failure (Be warned!).
xpList0 :: Show tag => PU [Node tag text] a -> PU [Node tag text] [a]
Convert XML text <-> a list of elements. Unlike xpList
, this function
uses no more elements as the end of list condition, which means it can
evaluate its children lazily.
Any error in a child will cause an error to be reported.
xpList :: Show tag => PU [Node tag text] a -> PU [Node tag text] [a]
Convert XML text <-> a list of elements. During unpickling, failure of the argument unpickler is the end-of-list condition (and it isn't a failure).
Note on lazy unpickle: Because we're using a failure to pickle a child as
the end condition it means we're only lazy at the top-level xpList. Children
of xpList are evaluated strictly. Use xpList0
to fix this.
xpContent :: GenericXMLString text => PU text a -> PU [Node tag text] a
If you have a pickler that works with text, and you want to use it as text content of an XML element, you need to wrap it with xpContent. See the example at the top.
xpWrap :: (a -> b, b -> a) -> PU t a -> PU t b
Apply a lens to convert the type of your data structure to/from types that
the pickler primitives can handle, with the unpickle case first.
Mostly this means the tuples used by xpPair
and friends. A typical example is:
xpWrap (\(name, address) -> Person name address, \(Person name address) -> (name, address)) $ ...