hxt-9.3.1.22: A collection of tools for processing XML with Haskell.
CopyrightCopyright (C) 2005-2021 Uwe Schmidt
LicenseMIT
MaintainerUwe Schmidt (uwe@fh-wedel.de)
Stabilitystable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.XML.HXT.Arrow.Pickle.Xml

Description

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 ( https://www.microsoft.com/en-us/research/wp-content/uploads/2004/01/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.

Old: Therefore the unpickler has a Maybe result type. Failure is used to unpickle optional elements (Maybe data) and lists of arbitray length.

Since hxt-9.2.0: The unpicklers are implemented as a parser monad with an Either err val result type. This enables appropriate error messages , when unpickling XML stuff, that is not generated with the picklers and which contains some elements and/or attributes that are not handled when unpickling.

There is an example program demonstrating the use of the picklers for a none trivial data structure. (see "examples/arrows/pickle" directory in the hxt distribution)

Synopsis

Documentation

data St Source #

Constructors

St 

Instances

Instances details
Show St Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

showsPrec :: Int -> St -> ShowS #

show :: St -> String #

showList :: [St] -> ShowS #

MonadState St Unpickler Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

get :: Unpickler St #

put :: St -> Unpickler () #

state :: (St -> (a, St)) -> Unpickler a #

MonadError UnpickleErr Unpickler Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

data PU a Source #

Constructors

PU 

type Pickler a = a -> St -> St Source #

newtype Unpickler a Source #

Constructors

UP 

Fields

Instances

Instances details
Monad Unpickler Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

(>>=) :: Unpickler a -> (a -> Unpickler b) -> Unpickler b #

(>>) :: Unpickler a -> Unpickler b -> Unpickler b #

return :: a -> Unpickler a #

Functor Unpickler Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

fmap :: (a -> b) -> Unpickler a -> Unpickler b #

(<$) :: a -> Unpickler b -> Unpickler a #

Applicative Unpickler Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

pure :: a -> Unpickler a #

(<*>) :: Unpickler (a -> b) -> Unpickler a -> Unpickler b #

liftA2 :: (a -> b -> c) -> Unpickler a -> Unpickler b -> Unpickler c #

(*>) :: Unpickler a -> Unpickler b -> Unpickler b #

(<*) :: Unpickler a -> Unpickler b -> Unpickler a #

MonadState St Unpickler Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

get :: Unpickler St #

put :: St -> Unpickler () #

state :: (St -> (a, St)) -> Unpickler a #

MonadError UnpickleErr Unpickler Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

mchoice :: Unpickler a -> (a -> Unpickler b) -> Unpickler b -> Unpickler b Source #

Choice combinator for unpickling

first 2 arguments are applied sequentially, but if the 1. one fails the 3. arg is applied

liftMaybe :: String -> Maybe a -> Unpickler a Source #

Lift a Maybe value into the Unpickler monad.

The 1. arg is the attached error message

liftUnpickleVal :: UnpickleVal a -> Unpickler a Source #

Lift an Either value into the Unpickler monad

putAtt :: QName -> [XmlTree] -> St -> St Source #

findElem :: (a -> Bool) -> [a] -> Maybe (a, [a]) Source #

formatSt :: St -> String Source #

Format the context of an error message.

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.

unpickleElem' :: PU a -> Int -> XmlTree -> UnpickleVal a Source #

The main entry for unpickling, called by unpickleDoc

showPickled :: XmlPickler a => SysConfigList -> a -> String Source #

Pickles a value, then writes the document to a string.

xpZero :: String -> PU a Source #

The zero pickler

Encodes nothing, fails always during unpickling

xpUnit :: PU () Source #

unit pickler

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.

xpCheckEmptyAttributes :: PU a -> PU a Source #

Like xpCheckEmptyContents, but checks the attribute list

xpCheckEmpty :: PU a -> PU a Source #

Composition of xpCheckEmptyContents and xpCheckAttributes

xpLift :: a -> PU a Source #

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.

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.

xpChoice :: PU b -> PU a -> (a -> PU b) -> Unpickler b Source #

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

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.

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

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

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

xpTriple :: PU a -> PU b -> PU c -> PU (a, b, c) Source #

Like xpPair but for triples

xp4Tuple :: PU a -> PU b -> PU c -> PU d -> PU (a, b, c, d) Source #

Like xpPair and xpTriple but for 4-tuples

xp5Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU (a, b, c, d, e) Source #

Like xpPair and xpTriple but for 5-tuples

xp6Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU (a, b, c, d, e, f) Source #

Like xpPair and xpTriple but for 6-tuples

xp7Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU (a, b, c, d, e, f, g) Source #

Like xpPair and xpTriple but for 7-tuples

Thanks to Tony Morris for doing xp7Tuple, ..., xp24Tuple.

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

xpText :: PU String Source #

Pickle a string into an XML text node

One of the most often used primitive picklers. Attention: For pickling empty strings use xpText0. If the text has a more specific datatype than xsd:string, use xpTextDT

xpTextDT :: Schema -> PU String Source #

Pickle a string into an XML text node

Text pickler with a description of the structure of the text by a schema. A schema for a data type can be defined by scDT. In Schema there are some more functions for creating simple datatype descriptions.

xpText0 :: PU String Source #

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.

xpText0DT :: Schema -> PU String Source #

Pickle a possibly empty string with a datatype description into an XML node.

Like xpText0 but with extra Parameter for datatype description as in xpTextDT.

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

xpInt :: PU Int Source #

Pickle an Int

xpTree :: PU XmlTree Source #

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.

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

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

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

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

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

xpElemQN :: QName -> PU a -> PU a Source #

Pickler for wrapping/unwrapping data into an XML element

Extra parameter is the element name given as a QName. THE pickler for constructing nested structures

Example:

xpElemQN (mkName "number") $ xpickle

will map an (42::Int) onto

<number>42</number>

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)

xpAttrQN :: QName -> PU a -> PU a Source #

Pickler for storing/retreiving data into/from an attribute value

The attribute is inserted in the surrounding element constructed by the xpElem pickler

xpAttr :: String -> PU a -> PU a Source #

convenient Pickler for xpAttrQN

xpAttr n = xpAttrQN (mkName n)

xpAttrNS :: String -> String -> String -> PU a -> PU a Source #

convenient Pickler for xpAttrQN

xpAttr ns px lp = xpAttrQN (mkQName px lp ns)

xpTextAttr :: String -> PU String Source #

A text attribute.

xpAttrImplied :: String -> PU a -> PU (Maybe a) Source #

Add an optional attribute for an optional value (Maybe a).

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)

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.

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.

xpIgnoreInput :: (([XmlTree] -> [XmlTree]) -> St -> St) -> LA XmlTree XmlTree -> PU () Source #

class XmlPickler a where Source #

The class for overloading xpickle, the default pickler

Methods

xpickle :: PU a Source #

Instances

Instances details
XmlPickler Int Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU Int Source #

XmlPickler Integer Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

XmlPickler () Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU () Source #

XmlPickler a => XmlPickler [a] Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU [a] Source #

XmlPickler a => XmlPickler (Maybe a) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (Maybe a) Source #

(XmlPickler l, XmlPickler r) => XmlPickler (Either l r) Source #

Pickler for an arbitrary datum of type Either.

Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (Either l r) Source #

(XmlPickler a, XmlPickler b) => XmlPickler (a, b) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b) Source #

(XmlPickler a, XmlPickler b, XmlPickler c) => XmlPickler (a, b, c) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d) => XmlPickler (a, b, c, d) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e) => XmlPickler (a, b, c, d, e) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d, e) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f) => XmlPickler (a, b, c, d, e, f) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d, e, f) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f, XmlPickler g) => XmlPickler (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d, e, f, g) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f, XmlPickler g, XmlPickler h) => XmlPickler (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d, e, f, g, h) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f, XmlPickler g, XmlPickler h, XmlPickler i) => XmlPickler (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d, e, f, g, h, i) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f, XmlPickler g, XmlPickler h, XmlPickler i, XmlPickler j) => XmlPickler (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d, e, f, g, h, i, j) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f, XmlPickler g, XmlPickler h, XmlPickler i, XmlPickler j, XmlPickler k) => XmlPickler (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d, e, f, g, h, i, j, k) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f, XmlPickler g, XmlPickler h, XmlPickler i, XmlPickler j, XmlPickler k, XmlPickler l) => XmlPickler (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d, e, f, g, h, i, j, k, l) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f, XmlPickler g, XmlPickler h, XmlPickler i, XmlPickler j, XmlPickler k, XmlPickler l, XmlPickler m) => XmlPickler (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f, XmlPickler g, XmlPickler h, XmlPickler i, XmlPickler j, XmlPickler k, XmlPickler l, XmlPickler m, XmlPickler n) => XmlPickler (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f, XmlPickler g, XmlPickler h, XmlPickler i, XmlPickler j, XmlPickler k, XmlPickler l, XmlPickler m, XmlPickler n, XmlPickler o) => XmlPickler (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f, XmlPickler g, XmlPickler h, XmlPickler i, XmlPickler j, XmlPickler k, XmlPickler l, XmlPickler m, XmlPickler n, XmlPickler o, XmlPickler p) => XmlPickler (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f, XmlPickler g, XmlPickler h, XmlPickler i, XmlPickler j, XmlPickler k, XmlPickler l, XmlPickler m, XmlPickler n, XmlPickler o, XmlPickler p, XmlPickler q) => XmlPickler (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f, XmlPickler g, XmlPickler h, XmlPickler i, XmlPickler j, XmlPickler k, XmlPickler l, XmlPickler m, XmlPickler n, XmlPickler o, XmlPickler p, XmlPickler q, XmlPickler r) => XmlPickler (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f, XmlPickler g, XmlPickler h, XmlPickler i, XmlPickler j, XmlPickler k, XmlPickler l, XmlPickler m, XmlPickler n, XmlPickler o, XmlPickler p, XmlPickler q, XmlPickler r, XmlPickler s) => XmlPickler (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f, XmlPickler g, XmlPickler h, XmlPickler i, XmlPickler j, XmlPickler k, XmlPickler l, XmlPickler m, XmlPickler n, XmlPickler o, XmlPickler p, XmlPickler q, XmlPickler r, XmlPickler s, XmlPickler t) => XmlPickler (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f, XmlPickler g, XmlPickler h, XmlPickler i, XmlPickler j, XmlPickler k, XmlPickler l, XmlPickler m, XmlPickler n, XmlPickler o, XmlPickler p, XmlPickler q, XmlPickler r, XmlPickler s, XmlPickler t, XmlPickler u) => XmlPickler (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f, XmlPickler g, XmlPickler h, XmlPickler i, XmlPickler j, XmlPickler k, XmlPickler l, XmlPickler m, XmlPickler n, XmlPickler o, XmlPickler p, XmlPickler q, XmlPickler r, XmlPickler s, XmlPickler t, XmlPickler u, XmlPickler v) => XmlPickler (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

xpickle :: PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source #

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f, XmlPickler g, XmlPickler h, XmlPickler i, XmlPickler j, XmlPickler k, XmlPickler l, XmlPickler m, XmlPickler n, XmlPickler o, XmlPickler p, XmlPickler q, XmlPickler r, XmlPickler s, XmlPickler t, XmlPickler u, XmlPickler v, XmlPickler w) => XmlPickler (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

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

(XmlPickler a, XmlPickler b, XmlPickler c, XmlPickler d, XmlPickler e, XmlPickler f, XmlPickler g, XmlPickler h, XmlPickler i, XmlPickler j, XmlPickler k, XmlPickler l, XmlPickler m, XmlPickler n, XmlPickler o, XmlPickler p, XmlPickler q, XmlPickler r, XmlPickler s, XmlPickler t, XmlPickler u, XmlPickler v, XmlPickler w, XmlPickler x) => XmlPickler (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 # 
Instance details

Defined in Text.XML.HXT.Arrow.Pickle.Xml

Methods

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