|> Thus I have a typical classes problem, in that I have several
|> implementations of essentially the same function for different
|> circumstances. The problem is, they must all operate on the same
|> data type, so I cannot define them as seperate instances.
|>
|> Anyone got any ideas how to type this?
Annotate the data type using a GADT:
{-# OPTIONS_GHC -fglasgow-exts #-}
module Foo where
data One
data Two
data MyData a where
MyCon :: MyData a
con1 :: MyData One
con1 = MyCon
con2 :: MyData Two
con2 = MyCon
class Display a where
> display :: MyData a -> String
instance Display One where
display _ = "one"
instance Display Two where
display _ = "two"
The annotations will tell you which constructor was used to create the
data, and you can implement destructor functions that can tell the
difference.
/Niklas
_______________________________________________
Haskell mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell