
23 Sep
2008
23 Sep
'08
12:07 p.m.
Hello, please consider the following code:
{-# LANGUAGE GADTs, MultiParamTypeClasses, FunctionalDependencies #-}
data GADT a where
GADT :: GADT ()
class Class a b | a -> b
instance Class () ()
fun :: (Class a b) => GADT a -> b fun GADT = ()
I’d expect this to work but unfortunately, using GHC 6.8.2, it fails with the following message:
FDGADT.hs:12:11: Couldn't match expected type `b' against inferred type `()' `b' is a rigid type variable bound by the type signature for `fun' at FDGADT.hs:11:16 In the expression: () In the definition of `fun': fun GADT = ()
What’s the reason for this? Is there a workaround? Does this work in 6.8.3 or 6.10.1? Thank you in advance. Best wishes, Wolfgang