[Haskell] XML Serialization and type constraints

Tomasz Zielonka t.zielonka at students.mimuw.edu.pl
Wed Aug 25 17:44:03 EDT 2004


On Wed, Aug 25, 2004 at 08:38:51PM +0100, Simon D. Foster wrote:
> Ok then, well it looks like this method is going to very cumbersome to
> use; for example a context for a reasonably simple complex data-type
> would be;
> 
> (Hook Element t, Hook Bool t, Hook [ERS] t, Hook (Selection ERS) t, Hook
> ERS t, Hook (Maybe PackedString) t, Hook PackedString t, Hook
> IsQualified t, Hook (Ser t) t, Hook Int t, Hook (Maybe QName) t, Hook
> QName t)

Well, yes, that can be tiresome. You can copy/paste this from compiler
error message, but that won't help you to keep these huge contexts up to
date if you remove some fields of your data types.

Hmmm, it is worse that I thought. The contexts will accumulate, like a
snowball. If you have:

    data A = A Int
    data B = B A
    data C = C B
    data D = D C

then in the instance for D you would have to include context for all
Int, A, B, C and D.

Apparently this solution doesn't scale. I can think about some hack, but
I'm not sure you will like it, because it introduces more type classes,
one per datatype.

  data S = S { sA :: Int, sB :: String, sC :: [Int] }

  class (Mixin Int t, Mixin Char t, Mixin String t, Mixin [Int] t, Mixin S t) => Mixin_S t
  instance (Mixin Int t, Mixin Char t, Mixin String t, Mixin [Int] t, Mixin S t) => Mixin_S t

  instance (Mixin_S t) => Serializer S t where
      encodePrim t s =
	  concat
	      [ "S { "
	      , encode t (sA s)
	      , ", "
	      , encode t (sB s)
	      , ", "
	      , encode t (sC s)
	      , " }"
	      ]

  data R = R { rA :: Int, rS :: S }

  class (Mixin_S t, Mixin Int t, Mixin R t) => Mixin_R t where
  instance (Mixin_S t, Mixin Int t, Mixin R t) => Mixin_R t where

  instance (Mixin_R t) => Serializer R t where
      encodePrim t r =
	  concat
	      [ "R { "
	      , encode t (rA r)
	      , ", "
	      , encode t (rS r)
	      , " }"
	      ]

I am moving this big contexts to superclasses of additional classes
Mixin_S and Mixin_R. This way the contexts don't accumulate. These
class/instance pairs could be easily generated with Template Haskell.
But it's a bit ugly.

> Is there any other way of doing this without another type-class?

That would be interesting.

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links


More information about the Haskell mailing list