hexpat-pickle-0.6: XML picklers based on hexpat, source-code-similar to those of the HXT package

Safe HaskellSafe-Infered

Text.XML.Expat.Pickle

Contents

Description

hexpat-pickle provides XML picklers that plug into the parse tree of the hexpat package, giving XML serialization with excellent performance. Picklers are source code similar to those of the HXT package. The concept and design was lifted entirely from HXT.

The API differences between HXT and hexpat-pickle are:

  • PU and XmlPickler take one extra argument, indicating the part of the XML tree we are working with.
  • xpElem takes three arguments to HXT's two, because we treat attributes and child nodes separately, while HXT groups them together.
  • Two type adapters (absent in HXT), xpRoot and xpContent are needed in certain places. See below.
  • These HXT picklers are missing: xpCondSeq, xpSeq, xpChoice, xpList1 (xpListMinLen may be substituted), xpElemWithAttrValue

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.

The t argument (absent in HXT) represents the part of the XML tree that this PU works on. t has three possible values. These are the most general types, and your picklers should not use any other types for t. Here they are, assuming we are using the String type for our strings:

  • PU [Node String String] a (for working with an XML element)
  • PU String a (for working with text content)
  • PU (Attributes String String) a (for working with attributes)

The reason why you a list of Node instead of just one when working with a single element is because the unpickler of xpElem needs to see the whole list of nodes so that it can 1. skip whitespace, and 2. search to match the specified tag name.

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.

The type for text content works for attribute values directly, but if you want to use it as the text content of an element, you need to adapt it by wrapping with xpContent.

hexpat-pickle can work with the following string types:

  • String
  • Data.ByteString
  • Data.Text

and it is extensible to any other string type by making it an instance of GenericXMLString. We select the type for XML tag and text separately in our four "tree part" types as follows:

  • PU [Node tag text] a (for working with an XML element)
  • PU text a (for working with text content)
  • PU (Attributes tag text) a (for working with attributes)

tag may be a string type, or it may be a QName type defined in the Qualified module. (Or you can extend it any way you like.)

The Text.XML.Expat.Tree and Text.XML.Expat.Qualified provide the follow useful shortcuts for common cases of Node and Attributes:

The type class XmlPickler is used to extend a polymorphic xpickle function to provide a pickler for a new type, in a similar way to Read and Show.

Here is a simple and complete example to get you started:

 import Text.XML.Expat.Pickle
 import Text.XML.Expat.Tree
 import qualified Data.ByteString.Lazy as L
 
 -- Person name, age and description
 data Person = Person String Int String
 
 xpPerson :: PU [UNode String] 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" xpText0)
             (xpAttr "age" xpickle))
         (xpContent xpText0)
 
 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
     L.putStrLn $
         pickleXML (xpRoot $ xpElemNodes "people" $ xpList xpPerson) people

Program output:

 <?xml version="1.0" encoding="UTF-8"?>
 <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>

Synopsis

Primary interface

data PU t a Source

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.

Constructors

PU 

Fields

unpickleTree :: t -> a

Lazily convert a t XML tree part into a Haskell value of type a. In the event of an error, it throws UnpickleException.

unpickleTree' :: t -> Either String a

strictly convert a t XML tree part into a Haskell value of type a, or give an unpickling error message as Left error.

pickleTree :: a -> t

Convert a Haskell value of type a to a t XML tree part.

type Node tag text = NodeG [] tag text

A pure tree representation that uses a list as its container type.

In the hexpat package, a list of nodes has the type [Node tag text], but note that you can also use the more general type function ListOf to give a list of any node type, using that node's associated list type, e.g. ListOf (UNode Text).

class XmlPickler t a whereSource

Define a generalized pickler for converting a Haskell data of type a to/from a t tree part, analogous to Read / Show.

Methods

xpickle :: PU t aSource

Instances

GenericXMLString text => XmlPickler text Integer 
GenericXMLString text => XmlPickler text Int 
(XmlPickler [Node tag text] a, Show tag) => XmlPickler [Node tag text] [a] 

data UnpickleException Source

An exception indicating an error during unpickling, using by the lazy variants.

unpickleXML :: (GenericXMLString tag, GenericXMLString text) => ParseOptions tag text -> PU (Node tag text) a -> ByteString -> aSource

A helper that combines parseXML with unpickleTree to unpickle from an XML document - lazy version. In the event of an error, it throws either XMLParseException or UnpickleException.

unpickleXML' :: (GenericXMLString tag, GenericXMLString text) => ParseOptions tag text -> PU (Node tag text) a -> ByteString -> Either String aSource

A helper that combines parseXML with unpickleTree to unpickle from an XML document - strict version.

pickleXML :: (GenericXMLString tag, GenericXMLString text) => PU (Node tag text) a -> a -> ByteStringSource

A helper that combines pickleTree with formatXML to pickle to an XML document. Lazy variant returning lazy ByteString.

pickleXML' :: (GenericXMLString tag, GenericXMLString text) => PU (Node tag text) a -> a -> ByteStringSource

A helper that combines pickleTree with formatXML to pickle to an XML document. Strict variant returning strict ByteString.

Re-exported types

type UNode text = Node text text

Type alias for a node with unqualified tag names where tag and text are the same string type.

type QNode text = Node (QName text) text

Type alias for a node where qualified names are used for tags

type NNode text = Node (NName text) text

Type alias for a node where namespaced names are used for tags

type Attributes tag text = [(tag, text)]

Type shortcut for attributes

type UAttributes text = Attributes text text

Type shortcut for attributes with unqualified names where tag and text are the same string type.

type QAttributes text = Attributes (QName text) text

Type shortcut for attributes with qualified names

type NAttributes text = Attributes (NName text) text

Type shortcut for attributes with namespaced names

data ParseOptions tag text

Constructors

ParseOptions 

Fields

overrideEncoding :: Maybe Encoding

The encoding parameter, if provided, overrides the document's encoding declaration.

entityDecoder :: Maybe (tag -> Maybe text)

If provided, entity references (i.e. &nbsp; and friends) will be decoded into text using the supplied lookup function

Pickler adapters

xpRoot :: PU [Node tag text] a -> PU (Node tag text) aSource

Adapts a list of nodes to a single node. Generally used at the top level of an XML document.

xpContent :: GenericXMLString text => PU text a -> PU [Node tag text] aSource

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.

Pickler primitives

xpUnit :: PU [t] ()Source

Convert nothing <-> (). Does not output or consume any XML text.

xpZero :: PU [t] aSource

The zero pickler

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

xpLift :: a -> PU [t] aSource

Convert nothing <-> constant value. Does not output or consume any XML text.

xpElemSource

Arguments

:: (Eq tag, Show tag) 
=> tag

Element name

-> PU [(tag, text)] a

Pickler for attributes

-> PU [Node tag text] b

Pickler for child nodes

-> PU [Node tag text] (a, b) 

Pickle (a,b) to/from an XML element of the specified name, where a is passed to a specified pickler for attributes and b to a pickler for child nodes. Unpickle fails if an element of this name can't be found at this point in the tree.

This implementation differs from HXT in that it unpickles elements of different names in any order, while HXT's xpElem will fail if the XML order doesn't match the Haskell code.

It also differs from HXT in that it takes two pickler arguments, one for attributes and one for child nodes. When migrating from HXT, often you can substitute just xpElemAttrs or xpElemNodes for HXT's xpElem, but where your element has both attributes and child nodes, you must split your data into a 2-tuple with xpWrap, and separate the child picklers accordingly.

xpElemAttrsSource

Arguments

:: (Eq tag, Show tag) 
=> tag

Element name

-> PU (Attributes tag text) a

Pickler for attributes

-> PU [Node tag text] a 

A helper variant of xpElem for elements that contain attributes but no child tags.

xpElemNodesSource

Arguments

:: (Eq tag, Show tag) 
=> tag

Element name

-> PU [Node tag text] a

Pickler for child nodes

-> PU [Node tag text] a 

A helper variant of xpElem for elements that contain child nodes but no attributes.

xpAttr :: (Eq tag, Show tag) => tag -> PU text a -> PU (Attributes tag text) aSource

Create/parse an XML attribute of the specified name. Fails if the attribute can't be found at this point in the tree.

xpAttrImplied :: (Eq tag, Show tag) => tag -> PU text a -> PU (Attributes tag text) (Maybe a)Source

Optionally add an attribute, unwrapping a Maybe value.

xpAttrFixed :: (Eq tag, Show tag, GenericXMLString text) => tag -> text -> PU (Attributes tag text) ()Source

Pickle an attribute with the specified name and value, fail if the same attribute is not present on unpickle.

xpAddFixedAttr :: (Eq tag, Show tag, GenericXMLString text) => tag -> text -> PU (Attributes tag text) a -> PU (Attributes tag text) aSource

Add an attribute with a fixed value.

Useful e.g. to declare namespaces. Is implemented by xpAttrFixed

xpText0 :: PU text textSource

Convert XML text content <-> String. Handles empty strings.

xpText :: GenericXMLString text => PU text textSource

Convert XML text content <-> String. Empty strings result in unpickle failure (Be warned!).

xpPrim :: (Read n, Show n, GenericXMLString text) => PU text nSource

Convert XML text content <-> any type that implements Read and Show. Fails on unpickle if read fails.

Pickler combinators

xpPair :: PU [t] a -> PU [t] b -> PU [t] (a, b)Source

Convert XML text <-> a 2-tuple using the two arguments.

xpTriple :: PU [t] a -> PU [t] b -> PU [t] c -> PU [t] (a, b, c)Source

Convert XML text <-> a 3-tuple using the three arguments.

xp4Tuple :: PU [t] a -> PU [t] b -> PU [t] c -> PU [t] d -> PU [t] (a, b, c, d)Source

Convert XML text <-> a 4-tuple using the four arguments.

xp5Tuple :: PU [t] a -> PU [t] b -> PU [t] c -> PU [t] d -> PU [t] e -> PU [t] (a, b, c, d, e)Source

Convert XML text <-> a 5-tuple using the five arguments.

xp6Tuple :: PU [t] a -> PU [t] b -> PU [t] c -> PU [t] d -> PU [t] e -> PU [t] f -> PU [t] (a, b, c, d, e, f)Source

Convert XML text <-> a 6-tuple using the six arguments.

xpList0 :: Show tag => PU [Node tag text] a -> PU [Node tag text] [a]Source

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

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.

xpListMinLen :: Show tag => Int -> PU [Node tag text] a -> PU [Node tag text] [a]Source

Like xpList, but only succeed during deserialization if at least a minimum number of elements are unpickled.

xpMapSource

Arguments

:: (Eq tag, Show tag, Ord k) 
=> tag

Element name (elt)

-> tag

Attribute name (attr)

-> PU text k

Pickler for keys (key)

-> PU [Node tag text] v

Pickler for values (value)

-> PU [Node tag text] (Map k v) 

Standard pickler for maps

This pickler converts a map into a list of pairs of the form

 <elt attr="key">value</elt>

Pickler type conversion

xpWrap :: (a -> b, b -> a) -> PU t a -> PU t bSource

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

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.

xpWrapEither :: (a -> Either String b, b -> a) -> PU t a -> PU t bSource

Like xpWrap, except it strips Right (and treats Left as a failure) during unpickling.

Pickler conditionals

xpOption :: PU [t] a -> PU [t] (Maybe a)Source

Convert XML text <-> a Maybe type. During unpickling, Nothing is returned if there's a failure during the unpickling of the first argument. A typical example is:

 xpElemAttrs "score" $ xpOption $ xpAttr "value" xpickle

in which Just 5 would be encoded as <score value="5"/> and Nothing would be encoded as <score/>.

Note on lazy unpickle: The argument is evaluated strictly.

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 fails

Note on lazy unpickle: The child is evaluated strictly.

xpWithDefault :: a -> PU t a -> PU t aSource

Attempt to use a pickler. On failure, return a default value.

Unlike xpDefault, the default value is encoded in the XML document.

Note on lazy unpickle: The child is evaluated strictly.

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

Note on lazy unpickle: Because we're using a failure to pickle a child as the end condition it means children of xpAlt are evaluated strictly.

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.

Note on lazy unpickle: The first argument is evaluated strictly.

xpThrowSource

Arguments

:: String

Error message

-> PU [t] a 

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

Pickler other

xpAttrs :: PU [(tag, text)] [(tag, text)]Source

Insert/extract an attribute list literally in the xml stream.

xpTree :: PU [Node tag text] (Node tag text)Source

Insert/extract a tree node literally in the xml stream.

xpTrees :: PU [Node tag text] [Node tag text]Source

Insert/extract a list of tree nodes literally in the xml stream.

class (Monoid s, Eq s) => GenericXMLString s where

An abstraction for any string type you want to use as xml text (that is, attribute values or element text content). If you want to use a new string type with hexpat, you must make it an instance of GenericXMLString.

Methods

gxNullString :: s -> Bool

gxToString :: s -> String

gxFromString :: String -> s

gxFromChar :: Char -> s

gxHead :: s -> Char

gxTail :: s -> s

gxBreakOn :: Char -> s -> (s, s)

gxFromByteString :: ByteString -> s

gxToByteString :: s -> ByteString