xml-picklers-0.3.1: XML picklers based on xml-types, ported from hexpat-pickle

Safe HaskellNone

Data.XML.Pickle

Contents

Description

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 PU t a 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 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 ist 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 folowing 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 outputs 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>

Funktions marked with compat are included for compatibility with hexpat-pickle

Synopsis

Types

data PU t a Source

Constructors

PU 

Fields

unpickleTree :: t -> UnpickleResult t a
 
pickleTree :: a -> t
 

Instances

data UnpickleResult t a Source

Constructors

UnpickleError UnpickleError 
NoResult Text

Not found, description of element

Result a (Maybe t)

Result and remainder. The remainder is wrapped in Maybe to avoid a Monoid constraint on t.

Invariant: When t is a Monoid, the empty remainder should always be Nothing instead of Just mempty

Instances

Pickler Invocation

pickle :: PU t a -> a -> tSource

pickle a Tree

unpickle :: PU t a -> t -> Either UnpickleError aSource

unpickle a tree

Primitive picklers

xpUnit :: PU [a] ()Source

Doesn't create or consume anything, always succeeds

xpZero :: PU [t] aSource

The zero pickler

Encodes nothing, always fails during unpickling. (Same as xpThrow "got xpZero").

xpThrowSource

Arguments

:: Monoid m 
=> String

Error message

-> PU m a 

No output when pickling, always generates an error with the specified message on unpickling.

xpIso :: (a -> b) -> (b -> a) -> PU a bSource

Isomorphic pickler

Value-preserving picklers

xpId :: PU a aSource

Returns everything (remaining), untouched.

xpFst :: Monoid b => PU t (a, b) -> PU t aSource

xpSnd :: Monoid a => PU t (a, b) -> PU t bSource

xpTrees :: PU a aSource

xpId (compat)

xpHead :: PU [a] aSource

return one element, untouched

xpTree :: PU [a] aSource

xpHead (compat)

xpText0 :: PU Text TextSource

specialised version of xpId (compat)

xpText :: PU Text TextSource

Like xpText0, but fails on non-empty input.

xpString :: PU Text StringSource

Convert text to/from String

xpRoot :: PU [a] b -> PU a bSource

Transforms a pickler on Lists to a pickler on single elements.

N.B. Will error when the given pickler doesn't produce exactly one element

xpPrim :: (Show a, Read a) => PU Text aSource

Convert text to/from any type that implements Read and Show. Fails on unpickle if read fails.

XML specific picklers

Attributes

xpAttribute :: Name -> PU Text a -> PU [Attribute] aSource

pickle to/from attribute

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.

xpAttr :: Name -> PU Text a -> PU [Attribute] aSource

(compat)

Elements

xpElemSource

Arguments

:: Name

name of the Element

-> 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.

xpElemWithNameSource

Arguments

:: PU [Attribute] a

pickler for attributes

-> PU [Node] n

pickler for child nodes

-> PU [Node] (Name, a, n) 

pickle Element without restriction on the name. the name as taken / returned as the first element of the triple

xpElemByNamespaceSource

Arguments

:: 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

xpElemBlank :: Name -> PU [Node] ()Source

Helper for Elements that don't contain anything

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

xpElemsSource

Arguments

:: Name

Name of the elements

-> 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

xpContent :: PU Text a -> PU [Node] aSource

Get the first non-element NodeContent from a node

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 returna 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.

xpMapSource

Arguments

:: 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>

xpAltSource

Arguments

:: (a -> Int)

selector function

-> [PU t a]

list of picklers

-> PU t a 

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.

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 confued 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

xpSubsetAllSource

Arguments

:: (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.

xpList0 :: PU [a] b -> PU [a] [b]Source

xpAll (compat)

xpSeqWhile :: PU [a] b -> PU [a] [b]Source

When unpickling, sucessively 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)

Tuples

Tuple combinators apply their picklers from left to right

xp2Tuple :: PU [a] b1 -> PU [a] b2 -> PU [a] (b1, b2)Source

Combines 2 picklers

xpPair :: PU [a] b1 -> PU [a] b2 -> PU [a] (b1, b2)Source

xp2Tuple (compat)

(<#>) :: PU [a] b1 -> PU [a] b2 -> PU [a] (b1, b2)Source

xp3Tuple :: PU [a] a1 -> PU [a] a2 -> PU [a] a3 -> PU [a] (a1, a2, a3)Source

Combines 3 picklers

xpTriple :: PU [a] a1 -> PU [a] a2 -> PU [a] a3 -> PU [a] (a1, a2, a3)Source

xp3Tuple (compat)

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

xpConst :: a -> PU t () -> PU t aSource

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. xpWrapEither :: (a -> Either String b, b -> a) -> PU t a -> PU t b

not to be confuesd 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.

N.B.: The predicate will only be tested while unpickling. When pickling, this is a noop.

xpMayFail :: PU t a -> PU t aSource

Instead of failing the pickler will return no result

xpUnliftElems :: PU [Node] a -> PU [Element] aSource

Unlift a pickler on Nodes to a Pickler on Elements. Nodes generated during pickling that are not Elements will be silently discarded

Book keeping

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

(<?+>) :: (Text, Text) -> PU t a -> PU t aSource

Add a back trace level to the error report

(<?>) :: (Text, Text) -> PU t a -> PU t aSource

Override the last backtrace level in the error report

helper functions