7.10. Generic classes

(Note: support for generic classes is currently broken in GHC 5.02).

The ideas behind this extension are described in detail in "Derivable type classes", Ralf Hinze and Simon Peyton Jones, Haskell Workshop, Montreal Sept 2000, pp94-105. An example will give the idea:

  import Generics

  class Bin a where
    toBin   :: a -> [Int]
    fromBin :: [Int] -> (a, [Int])
  
    toBin {| Unit |}    Unit	  = []
    toBin {| a :+: b |} (Inl x)   = 0 : toBin x
    toBin {| a :+: b |} (Inr y)   = 1 : toBin y
    toBin {| a :*: b |} (x :*: y) = toBin x ++ toBin y
  
    fromBin {| Unit |}    bs      = (Unit, bs)
    fromBin {| a :+: b |} (0:bs)  = (Inl x, bs')    where (x,bs') = fromBin bs
    fromBin {| a :+: b |} (1:bs)  = (Inr y, bs')    where (y,bs') = fromBin bs
    fromBin {| a :*: b |} bs	  = (x :*: y, bs'') where (x,bs' ) = fromBin bs
							  (y,bs'') = fromBin bs'

This class declaration explains how toBin and fromBin work for arbitrary data types. They do so by giving cases for unit, product, and sum, which are defined thus in the library module Generics:

  data Unit    = Unit
  data a :+: b = Inl a | Inr b
  data a :*: b = a :*: b

Now you can make a data type into an instance of Bin like this:
  instance (Bin a, Bin b) => Bin (a,b)
  instance Bin a => Bin [a]
That is, just leave off the "where" clause. Of course, you can put in the where clause and over-ride whichever methods you please.

7.10.1. Using generics

To use generics you need to

7.10.2. Changes wrt the paper

Note that the type constructors :+: and :*: can be written infix (indeed, you can now use any operator starting in a colon as an infix type constructor). Also note that the type constructors are not exactly as in the paper (Unit instead of 1, etc). Finally, note that the syntax of the type patterns in the class declaration uses "{|" and "|}" brackets; curly braces alone would ambiguous when they appear on right hand sides (an extension we anticipate wanting).

7.10.3. Terminology and restrictions

Terminology. A "generic default method" in a class declaration is one that is defined using type patterns as above. A "polymorphic default method" is a default method defined as in Haskell 98. A "generic class declaration" is a class declaration with at least one generic default method.

Restrictions:

The option -ddump-deriv dumps incomprehensible stuff giving details of what the compiler does with generic declarations.

7.10.4. Another example

Just to finish with, here's another example I rather like:
  class Tag a where
    nCons :: a -> Int
    nCons {| Unit |}    _ = 1
    nCons {| a :*: b |} _ = 1
    nCons {| a :+: b |} _ = nCons (bot::a) + nCons (bot::b)
  
    tag :: a -> Int
    tag {| Unit |}    _       = 1
    tag {| a :*: b |} _       = 1   
    tag {| a :+: b |} (Inl x) = tag x
    tag {| a :+: b |} (Inr y) = nCons (bot::a) + tag y