[Haskell] XML Serialization and type constraints

Simon D. Foster u1sf at dcs.shef.ac.uk
Tue Aug 24 14:35:46 EDT 2004


I'm trying to implement an extensible XML De/Serializer in Haskell for
use with SOAP and XML Schema (using the Haskell XML Toolbox). The idea
is you have a type-class, which is instantiated for each type you want
to encode/de-encode. This class (atm) takes the form;

class XMLSerializer a where
    encodeElements    :: NamespaceTable -> Flags -> a -> [XmlFilter]
    encodeAttributes  :: NamespaceTable -> Flags -> a -> [XmlFilter]
    encodeTree  :: NamespaceTable -> String -> Flags -> a -> XmlFilter
    encodeTrees :: NamespaceTable -> String -> Flags -> a -> [XmlFilter]
    
    decodeAttribute   :: String -> XmlTree -> Maybe a
    decodeElement     :: XmlTree -> Maybe a
    decodeTree        :: XmlTree -> Maybe a
    decodeTrees       :: XmlTrees -> Maybe a

(and a few default instances)

This type-class can then be used recursively to build XML
representations of Haskell data.

I now want to expand this system to make is more extensible. For
starters, to make it useful with SOAP, I need to add optional explicit
typing of data. To this end I have another class; XSDType, which stores
the XSD equivalent name and name-space for a particular Haskell type.
This is what is used to add explicit type data to the XML documents.
Adding this data involves adding an extra attribute to each node in the
tree. More generally however each "Hook", which adds extra data at each
node has type NamespaceTable -> Flags -> a -> ([XmlFilter],
[XmlFilter]), where a is the type of the value.

However, this is where the problem comes. How do I go about expressing
that a has a constraint XSDType a? I don't want to add this constraint
to the Serializer class itself since an XML tree may not be typed by
XSD. Somehow I need a way of adding extra constraints to a dynamically.

My first idea was to create another class Encoder;

class Encoder e a where
    encode :: NamespaceTable -> Flags -> e -> a -> ([XmlFilter],
[XmlFilter])

Encoder is parameterized over two types; the first being a type to
represent the hook itself and the second is the type of the value being
serialized. Thus if I introduced this new class into the Serializer
class non parametrically; eg for encodeElements;

encodeElements :: Encoder e a => NamespaceTable -> Flags -> e -> a ->
[XmlFilter]

I can create a dummy type SOAPEnc and an instance of Encoder for it with
the appropriate constraint;

data SOAPEnc = SOAPEnc
instance XSDType a => Encoder SOAPEnc a where
    encode ... = ...

and passing SOAPEnc to encodeElements as the e parameter would force the
constraint XSDType onto a. This system works fine in theory, but the
problem comes when I actually try to call encodeElements on any value
parameterised across a. For example lets say we wanted to Serialize a
list of Serializeables;

instance Serializable a => Serializable [a] where
    encodeTrees nst n f e x = map (encodeTree nst n f e) x

This does not work because Encoder is parameterized over e and [a] and I
get;

Could not deduce (Encoder e a, XMLSerializer a) 
from the context (XMLSerializer [a], Encoder e [a])

The obvious way to fix this would be with an extra constraint on the
instance; instance (Encoder e a, Serializable a) => Serializable [a].
But since e is not parameterized in Serializable this doesn't help. I
could add an extra parameter to Serializable but this would mean that
for every different hook, I'd need to duplicate all the serializer
functions and the decode functions would all require to be passed an
encoding parameter even though they don't need one. This frankly defeats
the whole objective of a hook system.

My question is this; Is there any way of "inserting" extra constraints
on 'a' by passing some form of extra parameter to the appropriate
function or by another method and is there anyway of making the above
method work?

-Si.

(Please CC me replies as I'm not subscribed).

-- 
Simon D. Foster <u1sf at dcs.shef.ac.uk>
Sheffield University



More information about the Haskell mailing list