Safe Haskell | None |
---|
This module provides XML picklers that plug into the XML tree of the xml-types package. This module was "inspired" by hexpat-pickle.
The API differences between hexpat-pickle and this module include:
- When unpickling, picklers will consume matching elmements so that they
will be ignored by sucessive picklers. To circumvent this behaviour, use
xpPeek
- Wrappers like
xpWrap
are uncurried - There are no lazy unpicklers
- Most unpicklers will produce an error when their child unpicklers fail to
consume all elements. Use
xpClean
to discard those elements
The data type
represents both a pickler (converting Haskell data
to XML) and an unpickler (XML to Haskell data), so your code only needs to
be written once for both serialization and deserialization. The PU
t aPU
primitives, such as xpElem
for XML elements, may be composed into complex
arrangements using xpPair
and other combinators.
Most picklers will try to find the first match rather than failing when
the first element doesn't match. This is why the target type often is a
list. To prevent this behaviour and commit the pickler to the first element
available, use xpIsolate
.
The top level of the document does not follow this rule, because it is a
single node type. xpRoot
is needed to adapt this to type [Node
] for your
pickler to use. You would typically define a pickler for a whole document
with xpElem
, then pickle it to a single Node
with
.
pickleTree
(xpRoot
myDocPickler) value
NB: Unresolved entities are considered an error and will trigger an exception
When unpickling, the following invariant regarding the list of remaining elements should be observed:
- The returned list should be a subset of or the initial list itself, that is, no elements should be added or changed
- The relative order of elements should be preserved
- Elements may, however, be removed from anywhere in the list
Here is a simple example to get you started:
{-# LANGUAGE OverloadedStrings #-} import Data.Text import Data.XML.Types import Data.XML.Pickle -- Person name, age and description data Person = Person Text Int Text xpPerson :: PU [Node] Person xpPerson = -- How to wrap and unwrap a Person xpWrap (\((name, age), descr) -> Person name age descr) (\(Person name age descr) -> ((name, age), descr)) $ xpElem "person" (xpPair (xpAttr "name" xpId) (xpAttr "age" xpPrim)) (xpContent xpId) people = [ Person "Dave" 27 "A fat thin man with long short hair", Person "Jane" 21 "Lives in a white house with green windows"] main = do print $ pickle (xpRoot $ xpElemNodes "people" $ xpAll xpPerson) people
Program output would be an xml-value equivalent to:
<people> <person name="Dave" age="27"> A fat thin man with long short hair </person> <person name="Jane" age="21"> Lives in a white house with green windows </person> </people>
Functions marked with compat are included for compatibility with hexpat-pickle.
- data PU t a = PU {
- unpickleTree :: t -> UnpickleResult t a
- pickleTree :: a -> t
- type Attribute = (Name, [Content])
- data UnpickleResult t a
- = UnpickleError UnpickleError
- | NoResult Text
- | Result a (Maybe t)
- pickle :: PU t a -> a -> t
- unpickle :: PU t a -> t -> Either UnpickleError a
- xpUnit :: PU [a] ()
- xpZero :: PU [t] a
- xpThrow :: Monoid m => String -> PU m a
- xpIso :: (a -> b) -> (b -> a) -> PU a b
- xpPartial :: (a -> Either Text b) -> (b -> a) -> PU a b
- xpId :: PU a a
- xpFst :: Monoid b => PU t (a, b) -> PU t a
- xpSnd :: Monoid a => PU t (a, b) -> PU t b
- xpTrees :: PU a a
- xpHead :: PU [a] a
- xpTree :: PU [a] a
- xpText0 :: PU Text Text
- xpText :: PU Text Text
- xpString :: PU Text String
- xpRoot :: PU [a] b -> PU a b
- xpPrim :: (Show a, Read a) => PU Text a
- xpAttribute :: Name -> PU Text a -> PU [Attribute] a
- xpAttribute' :: Name -> PU Text a -> PU [Attribute] (Maybe a)
- xpAttribute_ :: Name -> Text -> PU [Attribute] ()
- xpAttr :: Name -> PU Text a -> PU [Attribute] a
- xpAttrImplied :: Name -> PU Text a -> PU [Attribute] (Maybe a)
- xpAttrFixed :: Name -> Text -> PU [Attribute] ()
- xpAddFixedAttr :: Name -> Text -> PU [Attribute] b -> PU [Attribute] b
- xpElem :: Name -> PU [Attribute] a -> PU [Node] n -> PU [Node] (a, n)
- xpElemWithName :: PU [Attribute] a -> PU [Node] n -> PU [Node] (Name, a, n)
- xpElemByNamespace :: Text -> PU Text name -> PU [Attribute] a -> PU [Node] n -> PU [Node] (name, a, n)
- xpElemVerbatim :: PU [Node] Element
- xpElemAttrs :: Name -> PU [Attribute] b -> PU [Node] b
- xpElemNodes :: Name -> PU [Node] b -> PU [Node] b
- xpElemText :: Name -> PU [Node] Text
- xpElemBlank :: Name -> PU [Node] ()
- xpElemExists :: Name -> PU [Node] Bool
- xpElems :: Name -> PU [Attribute] a -> PU [Node] n -> PU [Node] [(a, n)]
- xpContent :: PU Text a -> PU [Node] a
- xpBool :: PU Text Bool
- xpOption :: PU [t] a -> PU [t] (Maybe a)
- xpDefault :: Eq a => a -> PU [t] a -> PU [t] a
- xpWithDefault :: a -> PU t a -> PU t a
- xpMap :: Ord k => Name -> Name -> PU Text k -> PU [Node] a -> PU [Node] (Map k a)
- xpAlt :: (a -> Int) -> [PU t a] -> PU t a
- xpChoice :: (a -> Int) -> [PU t a] -> PU t a
- xpEither :: PU n t1 -> PU n t2 -> PU n (Either t1 t2)
- xpTryCatch :: PU t a -> PU t a -> PU t a
- xpFindMatches :: PU [b] a -> PU [b] [a]
- xpFindFirst :: (t -> Bool) -> PU [t] a -> PU [t] a
- xpAll :: PU [a] b -> PU [a] [b]
- xpSubsetAll :: (a -> Bool) -> PU [a] b -> PU [a] [b]
- xpAllByNamespace :: Text -> PU [Node] b -> PU [Node] [b]
- xpList0 :: PU [a] b -> PU [a] [b]
- xpSeqWhile :: PU [a] b -> PU [a] [b]
- xpList :: PU [a] b -> PU [a] [b]
- xpListMinLen :: Int -> PU [a] b -> PU [a] [b]
- xp2Tuple :: PU [a] b1 -> PU [a] b2 -> PU [a] (b1, b2)
- xpPair :: PU [a] b1 -> PU [a] b2 -> PU [a] (b1, b2)
- (<#>) :: PU [a] b1 -> PU [a] b2 -> PU [a] (b1, b2)
- xp3Tuple :: PU [a] a1 -> PU [a] a2 -> PU [a] a3 -> PU [a] (a1, a2, a3)
- xpTriple :: PU [a] a1 -> PU [a] a2 -> PU [a] a3 -> PU [a] (a1, a2, a3)
- xp4Tuple :: PU [a] a1 -> PU [a] a2 -> PU [a] a3 -> PU [a] a4 -> PU [a] (a1, a2, a3, a4)
- xp5Tuple :: PU [a] a1 -> PU [a] a2 -> PU [a] a3 -> PU [a] a4 -> PU [a] a5 -> PU [a] (a1, a2, a3, a4, a5)
- xp6Tuple :: PU [a] a1 -> PU [a] a2 -> PU [a] a3 -> PU [a] a4 -> PU [a] a5 -> PU [a] a6 -> PU [a] (a1, a2, a3, a4, a5, a6)
- xpWrap :: (a -> b) -> (b -> a) -> PU t a -> PU t b
- xpConst :: a -> PU t () -> PU t a
- xpWrapEither :: Show e => (a -> Either e b) -> (b -> a) -> PU t a -> PU t b
- xpWrapMaybe :: (a -> Maybe b) -> (b -> a) -> PU t a -> PU t b
- xpWrapMaybe_ :: String -> (a -> Maybe b) -> (b -> a) -> PU t a -> PU t b
- xpAssert :: Text -> (a -> Bool) -> PU t a -> PU t a
- xpMayFail :: PU t a -> PU t a
- xpUnliftElems :: PU [Node] a -> PU [Element] a
- xpIsolate :: PU [t] a -> PU [t] a
- xpPeek :: PU t a -> PU t a
- xpClean :: PU t a -> PU t a
- data UnpickleError
- = ErrorMessage Text
- | TraceStep (Text, Text) UnpickleError
- | Variants [UnpickleError]
- ppUnpickleError :: UnpickleError -> String
- (<++>) :: (Text, Text) -> UnpickleError -> UnpickleError
- (<?+>) :: (Text, Text) -> PU t a -> PU t a
- (<?>) :: (Text, Text) -> PU t a -> PU t a
- (<??>) :: Text -> PU t a -> PU t a
- data UnresolvedEntityException = UnresolvedEntityException
- flattenContent :: [Node] -> [Node]
- tErr :: Text -> UnpickleResult t a -> UnpickleResult t a
- getRest :: UnpickleResult [a] b -> UnpickleResult [a] (b, [a])
Types
data UnpickleResult t a Source
UnpickleError UnpickleError | |
NoResult Text | Not found, description of element |
Result a (Maybe t) | Result and remainder. The
remainder is wrapped in Invariant: When |
Monad (UnpickleResult t) | |
Functor (UnpickleResult t) | |
(Show t, Show a) => Show (UnpickleResult t a) |
Pickler invocation
unpickle :: PU t a -> t -> Either UnpickleError aSource
Unpickle a tree.
Primitive picklers
The zero pickler.
Encodes nothing, always fails during unpickling. (Same as
).
xpThrow
"got xpZero"
No output when pickling, always generates an error with the specified message on unpickling.
Value-preserving picklers
xpRoot :: PU [a] b -> PU a bSource
Transforms a pickler on lists to a pickler on single elements.
NB: Will error when the given pickler doesn't produce exactly one element.
XML specific picklers
Attributes
xpAttribute' :: Name -> PU Text a -> PU [Attribute] (Maybe a)Source
Pickle attribute if Just
is given, on unpickling return Just val
when the attribute is found, Nothing
otherwise.
xpAttribute_ :: Name -> Text -> PU [Attribute] ()Source
Pickle an attribute with the specified name and value, fail if the same attribute is not present on unpickle.
xpAttrFixed :: Name -> Text -> PU [Attribute] ()Source
xpAttribute_
(compat)
xpAddFixedAttr :: Name -> Text -> PU [Attribute] b -> PU [Attribute] bSource
Add an attribute with a fixed value.
Elements
:: Name | Name of the |
-> PU [Attribute] a | Pickler for attributes |
-> PU [Node] n | Pickler for child nodes |
-> PU [Node] (a, n) |
When unpickling, tries to find the first element with the supplied name. Once such an element is found, it will commit to it and fail if any of the picklers don't match.
:: PU [Attribute] a | Pickler for attributes |
-> PU [Node] n | Pickler for child nodes |
-> PU [Node] (Name, a, n) |
Pickle Element
without a restriction on the name. The name as taken /
returned as the first element of the triple.
:: Text | Namespace |
-> PU Text name | Pickler for the local name |
-> PU [Attribute] a | Pickler for attributes |
-> PU [Node] n | Pickler for child nodes |
-> PU [Node] (name, a, n) |
Find element by name space, prefixes are ignored.
xpElemVerbatim :: PU [Node] ElementSource
Pickler returns the first found Element
untouched.
Unpickler wraps element in NodeElement
.
xpElemAttrs :: Name -> PU [Attribute] b -> PU [Node] bSource
A helper variant of xpElem
for elements that contain attributes but no
child tags.
xpElemNodes :: Name -> PU [Node] b -> PU [Node] bSource
A helper variant of xpElem
for elements that contain child nodes but no
attributes.
xpElemText :: Name -> PU [Node] TextSource
A helper variant of xpElem
for elements that contain only character
data.
xpElemExists :: Name -> PU [Node] BoolSource
When pickling, creates an empty element iff parameter is True
.
When unpickling, checks whether element exists. Generates an error when the element is not empty.
:: Name | Name of the |
-> PU [Attribute] a | Pickler for attributes |
-> PU [Node] n | Pickler for child nodes |
-> PU [Node] [(a, n)] |
Handle all elements with a given name. The unpickler will fail when any of the elements fails to unpickle.
Character Content
Converts Booleans to XML boolean values
- "true" and "1" are read as
True
- "false" and "0" are read as
False
- All other values generate an unpickle error
Will always generate "true" or "false" (not "0" or "1") when pickling.
Pickler combinators
Choice
xpOption :: PU [t] a -> PU [t] (Maybe a)Source
Lift a pickler. Nothing is returned when the given pickler doesn't return
a value (e.g. the element isn't found). Does not affect unpickling errors.
Nothing
is pickled to mempty
.
A typical example is:
xpElemAttributes "score" $ xpOption $ xpAttribute "value" xpPrim
in which Just 5
is encoded as <score value="5"/>
and Nothing
as <score/>
.
xpDefault :: Eq a => a -> PU [t] a -> PU [t] aSource
Optional conversion with default value.
Unlike xpWithDefault
the default value is not encoded in the XML document,
during unpickling the default value is inserted if the pickler doesn't
return a value.
xpWithDefault :: a -> PU t a -> PU t aSource
Attempt to use a pickler. Return a default value when the pickler doesn't
return anything (doesn't touch on UnpickleError
).
Unlike xpDefault
, the default value is encoded in the XML document.
:: Ord k | |
=> Name | Element name (elt) |
-> Name | Attribute name (attr) |
-> PU Text k | Pickler for keys (key) |
-> PU [Node] a | Pickler for values (value) |
-> PU [Node] (Map k a) |
Standard pickler for maps
This pickler converts a map into a list of pairs of the form
<elt attr="key">value</elt>
Execute one of a list of picklers. The selector function is used during
pickling, and the integer returned is taken as a 0-based index to select a
pickler from pickler options. Unpickling is done by trying each list
element in order until one returns a Result
(the selector is not used).
This is typically used to handle each constructor of a data type. However, it can be used wherever multiple serialization strategies apply to a single type.
NB: This function will ignore all errors as long as one of the branches
returns a result. Also, it will produce an error when all branches return
NoResult
. Use xpChoice
for a saner version of this function.
Execute one of a list of picklers. The selector function is used during
pickling, and the integer returned is taken as a 0-based index to select a
pickler from pickler options. Unpickling is done by trying each list
element in order until one returns a Result
or an Error
.
This is typically used to handle each constructor of a data type. However, it can be used wherever multiple serialization strategies apply to a single type.
This function is similar to xpAlt
but it will stop unpickling on the first
error. It will return NoResult
iff all of the picklers return NoResult
(or the list of picklers is empty).
xpEither :: PU n t1 -> PU n t2 -> PU n (Either t1 t2)Source
Try the left pickler first and if that doesn't produce anything the right
one. Wrapping the result in Left
or Right
, respectively.
Not to be confused with xpWrapEither
.
xpTryCatch :: PU t a -> PU t a -> PU t aSource
Pickler that during pickling always uses the first pickler, and during unpickling tries the first, and on failure then tries the second.
Sequencing
NB: The sequencing operations do not enforce any order on the
matched elements unless stated otherwise, but you can commit individial
picklers to the next available element with xpIsolate
. Applying
xpIsolate
on all nested Picklers will in effect enforce order.
Howver, once a pickler consumes an element it will not be available to
following picklers. You can circumvent this behaviour with xpPeek
.
If you want ensure that all elements are consumed after the last pickler
is run you may want to use xpClean
.
- ** Lists | The List pickler combinators will pickle lists in the given order without any special treatment and unpickle as stated.
xpFindMatches :: PU [b] a -> PU [b] [a]Source
When unpickling, tries to apply the pickler to all elements returning and consuming only matched elements.
xpFindFirst :: (t -> Bool) -> PU [t] a -> PU [t] aSource
Select a single element from the list and apply unpickler to it.
Returns no value when no element matches the predicate.
Fails when the unpickler doesn't return a value.
When pickling, this is a noop.
xpAll :: PU [a] b -> PU [a] [b]Source
Tries to apply the pickler to all the remaining elements; fails if any of them don't match.
:: (a -> Bool) | Predicate to select the subset |
-> PU [a] b | Pickler to apply on the subset |
-> PU [a] [b] |
For unpickling, apply the given pickler to a subset of the elements determined by a given predicate.
Pickles like xpAll
.
xpAllByNamespace :: Text -> PU [Node] b -> PU [Node] [b]Source
Apply unpickler to all elements with the given namespace.
Pickles like xpAll
.
xpSeqWhile :: PU [a] b -> PU [a] [b]Source
When unpickling, successively applies pickler to single elements until it doesn't return anything; returns all matched elements.
xpList :: PU [a] b -> PU [a] [b]Source
xpSeqWhile
. (compat)
xpListMinLen :: Int -> PU [a] b -> PU [a] [b]Source
Like xpList
, but only succeed during unpickling if at least a minimum
number of elements are unpickled.
Tuples
Tuple combinators apply their picklers from left to right. They will succeed when all their constituents produce a value.
xp4Tuple :: PU [a] a1 -> PU [a] a2 -> PU [a] a3 -> PU [a] a4 -> PU [a] (a1, a2, a3, a4)Source
Combines 4 picklers.
xp5Tuple :: PU [a] a1 -> PU [a] a2 -> PU [a] a3 -> PU [a] a4 -> PU [a] a5 -> PU [a] (a1, a2, a3, a4, a5)Source
Combines 5 picklers.
xp6Tuple :: PU [a] a1 -> PU [a] a2 -> PU [a] a3 -> PU [a] a4 -> PU [a] a5 -> PU [a] a6 -> PU [a] (a1, a2, a3, a4, a5, a6)Source
You guessed it ... Combines 6 picklers.
Wrappers
Value wrappers
xpWrap :: (a -> b) -> (b -> a) -> PU t a -> PU t bSource
Apply a bijection before pickling / after unpickling.
xpWrapEither :: Show e => (a -> Either e b) -> (b -> a) -> PU t a -> PU t bSource
Like xpWrap, except it strips Right
(and treats Left
as a failure)
during unpickling.
Not to be confused with xpEither
.
xpWrapMaybe :: (a -> Maybe b) -> (b -> a) -> PU t a -> PU t bSource
Like xpWrap, but strips Just
(and treats Nothing
as a failure) during
unpickling.
xpWrapMaybe_ :: String -> (a -> Maybe b) -> (b -> a) -> PU t a -> PU t bSource
Like xpWrap, but strips Just
(and treats Nothing
as a failure) during
unpickling, with specified error message for Nothing
value.
xpAssert :: Text -> (a -> Bool) -> PU t a -> PU t aSource
Test predicate when unpickling. Fails with given error message when the predicate return false.
NB: The predicate will only be tested while unpickling. When pickling, this is a noop.
Bookkeeping
Change the semantics of picklers
xpIsolate :: PU [t] a -> PU [t] aSource
Noop when pickling.
When unpickling, only give access to the first element.
xpPeek :: PU t a -> PU t aSource
When unpickling, don't consume the matched element(s), noop when pickling.
Cleannes
Picklers keep track of elements left over after unpickling, so the may
be [clean
] an unpickling is considered clean
when it doesn't leave any
remainng elements.
xpClean :: PU t a -> PU t aSource
Run unpickler and consume and discard remaining elements.
When pickling, this is a noop.
Error handling
data UnpickleError Source
(<++>) :: (Text, Text) -> UnpickleError -> UnpickleErrorSource
(<?>) :: (Text, Text) -> PU t a -> PU t aSource
Override the last backtrace level in the error report.
Helper functions
flattenContent :: [Node] -> [Node]Source
Merge successive NodeContent
values.
tErr :: Text -> UnpickleResult t a -> UnpickleResult t aSource
getRest :: UnpickleResult [a] b -> UnpickleResult [a] (b, [a])Source
Try to extract the remainig elements, fail if there are none.