Copyright | Copyright (C) 2005 Uwe Schmidt |
---|---|
License | MIT |
Maintainer | Uwe Schmidt (uwe@fh-wedel.de) |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
Pickler functions for converting between user defined data types and XmlTree data. Usefull for persistent storage and retreival of arbitray data as XML documents
This module is an adaptation of the pickler combinators developed by Andrew Kennedy ( http://research.microsoft.com/~akenn/fun/picklercombinators.pdf )
The difference to Kennedys approach is that the target is not a list of Chars but a list of XmlTrees. The basic picklers will convert data into XML text nodes. New are the picklers for creating elements and attributes.
One extension was neccessary: The unpickling may fail. Therefore the unpickler has a Maybe result type. Failure is used to unpickle optional elements (Maybe data) and lists of arbitray length
There is an example program demonstrating the use of the picklers for a none trivial data structure. (see "examples/arrows/pickle" directory)
- xpickleDocument :: PU a -> SysConfigList -> String -> IOStateArrow s a XmlTree
- xunpickleDocument :: PU a -> SysConfigList -> String -> IOStateArrow s b a
- xpickleWriteDTD :: PU b -> SysConfigList -> String -> IOStateArrow s b XmlTree
- xpickleDTD :: PU b -> IOStateArrow s b XmlTree
- checkPickler :: Eq a => PU a -> IOStateArrow s a a
- xpickleVal :: ArrowXml a => PU b -> a b XmlTree
- xunpickleVal :: PU b -> IOStateArrow s XmlTree b
- thePicklerDTD :: PU b -> XmlTrees
- a_addDTD :: String
- pickleDoc :: PU a -> a -> XmlTree
- unpickleDoc :: PU a -> XmlTree -> Maybe a
- unpickleDoc' :: PU a -> XmlTree -> Either String a
- showPickled :: XmlPickler a => SysConfigList -> a -> String
- data PU a = PU {}
- class XmlPickler a where
- xp4Tuple :: PU a -> PU b -> PU c -> PU d -> PU (a, b, c, d)
- xp5Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU (a, b, c, d, e)
- xp6Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU (a, b, c, d, e, f)
- xp7Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU (a, b, c, d, e, f, g)
- xp8Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU (a, b, c, d, e, f, g, h)
- xp9Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU (a, b, c, d, e, f, g, h, i)
- xp10Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU (a, b, c, d, e, f, g, h, i, j)
- xp11Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU (a, b, c, d, e, f, g, h, i, j, k)
- xp12Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU (a, b, c, d, e, f, g, h, i, j, k, l)
- xp13Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m)
- xp14Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
- xp15Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
- xp16Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)
- xp17Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q)
- xp18Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r)
- xp19Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s)
- xp20Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t)
- xp21Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU u -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u)
- xp22Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU u -> PU v -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v)
- xp23Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU u -> PU v -> PU w -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w)
- xp24Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU u -> PU v -> PU w -> PU x -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x)
- xpAddFixedAttr :: String -> String -> PU a -> PU a
- xpAddNSDecl :: String -> String -> PU a -> PU a
- xpAlt :: (a -> Int) -> [PU a] -> PU a
- xpAttr :: String -> PU a -> PU a
- xpAttrFixed :: String -> String -> PU ()
- xpAttrImplied :: String -> PU a -> PU (Maybe a)
- xpAttrNS :: String -> String -> String -> PU a -> PU a
- xpCheckEmpty :: PU a -> PU a
- xpCheckEmptyAttributes :: PU a -> PU a
- xpCheckEmptyContents :: PU a -> PU a
- xpTextAttr :: String -> PU String
- xpChoice :: PU b -> PU a -> (a -> PU b) -> Unpickler b
- xpDefault :: Eq a => a -> PU a -> PU a
- xpElem :: String -> PU a -> PU a
- xpElemNS :: String -> String -> String -> PU a -> PU a
- xpElemWithAttrValue :: String -> String -> String -> PU a -> PU a
- xpFilterAttr :: LA XmlTree XmlTree -> PU a -> PU a
- xpFilterCont :: LA XmlTree XmlTree -> PU a -> PU a
- xpInt :: PU Int
- xpLift :: a -> PU a
- xpLiftEither :: Either String a -> PU a
- xpLiftMaybe :: Maybe a -> PU a
- xpList :: PU a -> PU [a]
- xpList1 :: PU a -> PU [a]
- xpMap :: Ord k => String -> String -> PU k -> PU v -> PU (Map k v)
- xpOption :: PU a -> PU (Maybe a)
- xpPair :: PU a -> PU b -> PU (a, b)
- xpPrim :: (Read a, Show a) => PU a
- xpSeq :: (b -> a) -> PU a -> (a -> PU b) -> PU b
- xpSeq' :: PU () -> PU a -> PU a
- xpText :: PU String
- xpText0 :: PU String
- xpTextDT :: Schema -> PU String
- xpText0DT :: Schema -> PU String
- xpTree :: PU XmlTree
- xpTrees :: PU [XmlTree]
- xpTriple :: PU a -> PU b -> PU c -> PU (a, b, c)
- xpUnit :: PU ()
- xpWrap :: (a -> b, b -> a) -> PU a -> PU b
- xpWrapEither :: (a -> Either String b, b -> a) -> PU a -> PU b
- xpWrapMaybe :: (a -> Maybe b, b -> a) -> PU a -> PU b
- xpXmlText :: PU String
- xpZero :: String -> PU a
- data Schema
- type Schemas = [Schema]
- data DataTypeDescr
Documentation
xpickleDocument :: PU a -> SysConfigList -> String -> IOStateArrow s a XmlTree Source #
store an arbitray value in a persistent XML document
The pickler converts a value into an XML tree, this is written out with
writeDocument
. The option list is passed to writeDocument
An option evaluated by this arrow is a_addDTD
.
If a_addDTD
is set (v_1
), the pickler DTD is added as an inline DTD into the document.
xunpickleDocument :: PU a -> SysConfigList -> String -> IOStateArrow s b a Source #
read an arbitray value from an XML document
The document is read with readDocument
. Options are passed
to readDocument
. The conversion from XmlTree is done with the
pickler.
xpickleDocument xp al dest >>> xunpickleDocument xp al' dest
is the identity arrow
when applied with the appropriate options. When during pickling indentation is switched on,
the whitespace must be removed during unpickling.
xpickleWriteDTD :: PU b -> SysConfigList -> String -> IOStateArrow s b XmlTree Source #
Write out the DTD generated out of a pickler. Calls xpicklerDTD
xpickleDTD :: PU b -> IOStateArrow s b XmlTree Source #
The arrow for generating the DTD out of a pickler
A DTD is generated from a pickler and check for consistency. Errors concerning the DTD are issued.
checkPickler :: Eq a => PU a -> IOStateArrow s a a Source #
An arrow for checking picklers
A value is transformed into an XML document by a given pickler, the associated DTD is extracted from the pickler and checked, the document including the DTD is tranlated into a string, this string is read and validated against the included DTD, and unpickled. The last step is the equality with the input.
If the check succeeds, the arrow works like this, else it fails.
xunpickleVal :: PU b -> IOStateArrow s XmlTree b Source #
The arrow version of the unpickler function
thePicklerDTD :: PU b -> XmlTrees Source #
Compute the associated DTD of a pickler
pickleDoc :: PU a -> a -> XmlTree Source #
conversion of an arbitrary value into an XML document tree.
The pickler, first parameter, controls the conversion process. Result is a complete document tree including a root node
unpickleDoc :: PU a -> XmlTree -> Maybe a Source #
Conversion of an XML document tree into an arbitrary data type
The inverse of pickleDoc
.
This law should hold for all picklers: unpickle px . pickle px $ v == Just v
.
Not every possible combination of picklers does make sense.
For reconverting a value from an XML tree, is becomes neccessary,
to introduce "enough" markup for unpickling the value
unpickleDoc' :: PU a -> XmlTree -> Either String a Source #
Like unpickleDoc but with a (sometimes) useful error message, when unpickling failed.
showPickled :: XmlPickler a => SysConfigList -> a -> String Source #
Pickles a value, then writes the document to a string.
class XmlPickler a where Source #
The class for overloading xpickle
, the default pickler
XmlPickler Int Source # | |
XmlPickler Integer Source # | |
XmlPickler () Source # | |
XmlPickler a => XmlPickler [a] Source # | |
XmlPickler a => XmlPickler (Maybe a) Source # | |
(XmlPickler a, XmlPickler b) => XmlPickler (a, b) Source # | |
(XmlPickler a, XmlPickler b, XmlPickler c) => XmlPickler (a, b, c) Source # | |
(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d) => XmlPickler (a, b, c, d) Source # | |
(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e) => XmlPickler (a, b, c, d, e) Source # | |
xp7Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU (a, b, c, d, e, f, g) Source #
xp8Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU (a, b, c, d, e, f, g, h) Source #
xp9Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU (a, b, c, d, e, f, g, h, i) Source #
xp10Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU (a, b, c, d, e, f, g, h, i, j) Source #
xp11Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU (a, b, c, d, e, f, g, h, i, j, k) Source #
xp12Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU (a, b, c, d, e, f, g, h, i, j, k, l) Source #
xp13Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #
xp14Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #
xp15Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #
xp16Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source #
xp17Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source #
xp18Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source #
xp19Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source #
xp20Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source #
xp21Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU u -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source #
xp22Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU u -> PU v -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source #
xp23Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU u -> PU v -> PU w -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source #
xp24Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU u -> PU v -> PU w -> PU x -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source #
Hopefully no one needs a xp25Tuple
xpAddFixedAttr :: String -> String -> PU a -> PU a Source #
Add/Check an attribute with a fixed value.
xpAddNSDecl :: String -> String -> PU a -> PU a Source #
Add a namespace declaration.
When generating XML the namespace decl is added, when reading a document, the unpickler checks whether there is a namespace declaration for the given namespace URI (2. arg)
xpAlt :: (a -> Int) -> [PU a] -> PU a Source #
Pickler for sum data types.
Every constructor is mapped to an index into the list of picklers. The index is used only during pickling, not during unpickling, there the 1. match is taken
xpAttr :: String -> PU a -> PU a Source #
convenient Pickler for xpAttrQN
xpAttr n = xpAttrQN (mkName n)
xpAttrImplied :: String -> PU a -> PU (Maybe a) Source #
Add an optional attribute for an optional value (Maybe a).
xpAttrNS :: String -> String -> String -> PU a -> PU a Source #
convenient Pickler for xpAttrQN
xpAttr ns px lp = xpAttrQN (mkQName px lp ns)
xpCheckEmpty :: PU a -> PU a Source #
Composition of xpCheckEmptyContents and xpCheckAttributes
xpCheckEmptyAttributes :: PU a -> PU a Source #
Like xpCheckEmptyContents, but checks the attribute list
xpCheckEmptyContents :: PU a -> PU a Source #
Check EOF pickler.
When pickling, this behaves like the unit pickler. The unpickler fails, when there is some unprocessed XML contents left.
xpChoice :: PU b -> PU a -> (a -> PU b) -> Unpickler b Source #
combine tow picklers with a choice
Run two picklers in sequence like with xpSeq. If during unpickling the first one fails, an alternative pickler (first argument) is applied. This pickler is only used as combinator for unpickling.
xpDefault :: Eq a => a -> PU a -> PU a Source #
Optional conversion with default value
The default value is not encoded in the XML document, during unpickling the default value is inserted if the pickler fails
xpElem :: String -> PU a -> PU a Source #
convenient Pickler for xpElemQN
xpElem n = xpElemQN (mkName n)
xpElemNS :: String -> String -> String -> PU a -> PU a Source #
convenient Pickler for xpElemQN for pickling elements with respect to namespaces
xpElemNS ns px lp = xpElemQN (mkQName px lp ns)
xpElemWithAttrValue :: String -> String -> String -> PU a -> PU a Source #
Pickler for wrapping/unwrapping data into an XML element with an attribute with given value
To make XML structures flexible but limit the number of different elements, it's sometimes useful to use a kind of generic element with a key value structure
Example:
<attr name="key1">value1</attr> <attr name="key2">value2</attr> <attr name="key3">value3</attr>
the Haskell datatype may look like this
type T = T { key1 :: Int ; key2 :: String ; key3 :: Double }
Then the picker for that type looks like this
xpT :: PU T xpT = xpWrap ( uncurry3 T, \ t -> (key1 t, key2 t, key3 t) ) $ xpTriple (xpElemWithAttrValue "attr" "name" "key1" $ xpickle) (xpElemWithAttrValue "attr" "name" "key2" $ xpText0) (xpElemWithAttrValue "attr" "name" "key3" $ xpickle)
xpFilterAttr :: LA XmlTree XmlTree -> PU a -> PU a Source #
Same as xpFilterCont
but for the attribute list of the element currently processed.
Maybe useful to ignore some stuff in the input, e.g. class attributes, or to do some cleanup before unpickling.
xpFilterCont :: LA XmlTree XmlTree -> PU a -> PU a Source #
When unpickling, filter the contents of the element currently processed, before applying the pickler argument
Maybe useful to ignore some stuff in the input, or to do some cleanup before unpickling.
xpLiftMaybe :: Maybe a -> PU a Source #
Lift a Maybe value to a pickler.
Nothing
is mapped to the zero pickler, Just x
is pickled with xpLift x
.
xpList :: PU a -> PU [a] Source #
Encoding of list values by pickling all list elements sequentially.
Unpickler relies on failure for detecting the end of the list.
The standard pickler for lists. Can also be used in combination with xpWrap
for constructing set and map picklers
xpList1 :: PU a -> PU [a] Source #
Encoding of a none empty list of values
Attention: when calling this pickler with an empty list, an internal error "head of empty list is raised".
xpMap :: Ord k => String -> String -> PU k -> PU v -> PU (Map k v) Source #
Standard pickler for maps
This pickler converts a map into a list of pairs. All key value pairs are mapped to an element with name (1.arg), the key is encoded as an attribute named by the 2. argument, the 3. arg is the pickler for the keys, the last one for the values
xpOption :: PU a -> PU (Maybe a) Source #
Encoding of optional data by ignoring the Nothing case during pickling and relying on failure during unpickling to recompute the Nothing case
The default pickler for Maybe types
xpPair :: PU a -> PU b -> PU (a, b) Source #
pickle a pair of values sequentially
Used for pairs or together with wrap for pickling algebraic data types with two components
xpPrim :: (Read a, Show a) => PU a Source #
Pickle an arbitrary value by applyling show during pickling and read during unpickling.
Real pickling is then done with xpText
.
One of the most often used pimitive picklers. Applicable for all
types which are instances of Read
and Show
xpSeq :: (b -> a) -> PU a -> (a -> PU b) -> PU b Source #
Combine two picklers sequentially.
If the first fails during unpickling, the whole unpickler fails
xpSeq' :: PU () -> PU a -> PU a Source #
First apply a fixed pickler/unpickler, then a 2. one
If the first fails during unpickling, the whole pickler fails.
This can be used to check some properties of the input, e.g. whether
a given fixed attribute or a namespace declaration exists (xpAddFixedAttr
, xpAddNSDecl
)
or to filter the input, e.g. to ignore some elements or attributes (xpFilterCont
, xpFilterAttr
).
When pickling, this can be used to insert some fixed XML pieces, e.g. namespace declarations, class attributes or other stuff.
Pickle a possibly empty string into an XML node.
Must be used in all places, where empty strings are legal values. If the content of an element can be an empty string, this string disapears during storing the DOM into a document and reparse the document. So the empty text node becomes nothing, and the pickler must deliver an empty string, if there is no text node in the document.
Pickle an XmlTree by just adding it
Usefull for components of type XmlTree in other data structures
xpTrees :: PU [XmlTree] Source #
Pickle a whole list of XmlTrees by just adding the list, unpickle is done by taking all element contents.
This pickler should always be combined with xpElem
for taking the whole contents of an element.
xpWrap :: (a -> b, b -> a) -> PU a -> PU b Source #
map value into another domain and apply pickler there
One of the most often used picklers.
xpWrapEither :: (a -> Either String b, b -> a) -> PU a -> PU b Source #
like xpWrap
, but if the inverse mapping is undefined, the unpickler fails
Map a value into another domain. If the inverse mapping is undefined, the unpickler fails with an error message in the Left component
xpWrapMaybe :: (a -> Maybe b, b -> a) -> PU a -> PU b Source #
like xpWrap
, but if the inverse mapping is undefined, the unpickler fails
Map a value into another domain. If the inverse mapping is undefined (Nothing), the unpickler fails
Deprecated: Use xpWrapEither, this gives better error messages
xpXmlText :: PU String Source #
Pickle a string representing XML contents by inserting the tree representation into the XML document.
Unpickling is done by converting the contents with
xshowEscapeXml
into a string,
this function will escape all XML special chars, such that pickling the value back becomes save.
Pickling is done with xread
The datatype for modelling the structure of an