hexpat-pickle-0.1: XML picklers based on hexpat, almost source code compatible with HXTSource codeContentsIndex
Text.XML.Expat.Pickle
Contents
Pickler primitives
Classes for abstracting parts of the tree
Description
XML picklers based on hexpat which are almost source code compatible with HXT.
Synopsis
data PU_ t a = PU (t -> Either String a) (a -> t -> t)
type PU a = PU_ Node a
pickleXML :: Maybe Encoding -> PU_ Node a -> a -> ByteString
unpickleXML :: PU_ Node a -> Maybe Encoding -> ByteString -> Either String a
class XmlPickler t a where
xpickle :: PU_ t a
pickleTree :: PU a -> a -> Node
unpickleTree :: PU a -> Node -> Either String a
xpReadShow :: (Stringable s, Read n, Show n) => PU_ s n
xpText0 :: Stringable t => PU_ t String
xpText :: Stringable t => PU_ t String
xpElem :: Nodeable t => String -> PU_ Node a -> PU_ t a
xpAttr :: String -> PU_ (String, String) a -> PU_ Node a
xpOption :: PU_ t a -> PU_ t (Maybe a)
xpPair :: PU_ t a -> PU_ t b -> PU_ t (a, b)
xpTriple :: PU_ t a -> PU_ t b -> PU_ t c -> PU_ t (a, b, c)
xp4Tuple :: PU_ t a -> PU_ t b -> PU_ t c -> PU_ t d -> PU_ t (a, b, c, d)
xp5Tuple :: PU_ t a -> PU_ t b -> PU_ t c -> PU_ t d -> PU_ t e -> PU_ t (a, b, c, d, e)
xpList :: PU_ Node a -> PU_ Node [a]
xpWrap :: (a -> b, b -> a) -> PU_ t a -> PU_ t b
xpWrapMaybe :: (a -> Maybe b, b -> a) -> PU_ t a -> PU_ t b
xpWrapEither :: (a -> Either String b, b -> a) -> PU_ t a -> PU_ t b
xpAllAttrs :: Attrable t => PU_ t [(String, String)]
xpAlt :: (a -> Int) -> [PU_ t a] -> PU_ t a
xpUnit :: PU_ t ()
class Show t => Stringable t
class Show t => Nodeable t
class Show t => Attrable t
Documentation
data PU_ t a Source

A two-way pickler/unpickler that pickles a ''t'' to type ''a''. See Text.XML.Expat.Tree for the tree structure as used with ''t''. ''t'' can be Node, [Node], [(String,String)], (String,String) or String.

A PU_ can be composed using the pickler primitives defined in this module.

Constructors
PU (t -> Either String a) (a -> t -> t)
type PU a = PU_ Node aSource
In the most common case, where the part of the tree you're pickling/unpickling is of type Node, you can use PU and maintain source code compatibility with HXT. In other cases you will need to use PU_, which will break compatibility.
pickleXML :: Maybe Encoding -> PU_ Node a -> a -> ByteStringSource
Pickle a Haskell data structure to XML text. Outputs a strict ByteString.
unpickleXML :: PU_ Node a -> Maybe Encoding -> ByteString -> Either String aSource
Unpickle XML text to a Haskell data structure. Takes a lazy ByteString.
class XmlPickler t a whereSource
Takes one more argument than the HXT version of XmlPickler, which is the type of the part of the tree, like PU_ does.
Methods
xpickle :: PU_ t aSource
show/hide Instances
pickleTree :: PU a -> a -> NodeSource
unpickleTree :: PU a -> Node -> Either String aSource
Pickler primitives
xpReadShow :: (Stringable s, Read n, Show n) => PU_ s nSource
Convert an XML string <-> a type that implements Read and Show.
xpText0 :: Stringable t => PU_ t StringSource
Convert XML text <-> String. Handles empty strings.
xpText :: Stringable t => PU_ t StringSource
Convert XML text <-> String. Empty strings result in unpickle failure.
xpElem :: Nodeable t => String -> PU_ Node a -> PU_ t aSource
Create/parse an XML element of the specified name. Fails if an element of this name can't be found at this point in the tree. This implementation unpickles elements of different names in any order, while HXT's xpElem will fail if the XML order doesn't match the Haskell code.
xpAttr :: String -> PU_ (String, String) a -> PU_ Node aSource
Create/parse an XML attribute of the specified name. Fails if the attribute can't be found at this point in the tree.
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.
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.
xpList :: PU_ Node a -> PU_ Node [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).
xpWrap :: (a -> b, b -> a) -> PU_ t a -> PU_ t bSource
Apply a lens to convert the type of your data structure into something that the pickler primitives can handle (such as tuples).
xpWrapMaybe :: (a -> Maybe b, b -> a) -> PU_ t a -> PU_ t bSource
xpWrapEither :: (a -> Either String b, b -> a) -> PU_ t a -> PU_ t bSource
xpAllAttrs :: Attrable t => PU_ t [(String, String)]Source
xpAltSource
::
=> a -> IntSelector
-> [PU_ t a]
-> PU_ t a
Allow alternative picklers. Selector function is used during pickling, but unpickling is done by trying each list element in order until one succeeds.
xpUnit :: PU_ t ()Source
Convert nothing <-> (). Does not output or consume any XML text.
Classes for abstracting parts of the tree
class Show t => Stringable t Source
show/hide Instances
class Show t => Nodeable t Source
Tree parts that can be treated as nodes.
show/hide Instances
class Show t => Attrable t Source
Tree parts that can be treated as attributes.
show/hide Instances
Produced by Haddock version 2.4.1