Error when deriving Typeable for associated type
Bas van Dijk
v.dijk.bas at gmail.com
Mon Jan 30 20:26:42 CET 2012
Hello,
Given the following program:
-----------------------------------------------------------
{-# LANGUAGE DeriveDataTypeable, TypeFamilies #-}
import Data.Typeable
class C a where
data T a :: *
data MyType1 = MyType1 deriving Typeable
data MyType2 = MyType2 deriving Typeable
instance C MyType1 where
data T MyType1 = A1 deriving (Typeable)
instance C MyType2 where
data T MyType2 = A2 deriving (Typeable)
-----------------------------------------------------------
I get the following unexpected error:
TF_Data.hs:12:34:
Duplicate instance declarations:
instance Typeable1 T -- Defined at TF_Data.hs:12:34
instance Typeable1 T -- Defined at TF_Data.hs:15:34
When looking at the output of -ddump-deriv I see that the following
instance is generated:
instance Typeable1 T where ...
I would have expected that the following instances were generated instead:
instance Typeable1 (T MyType1) where ...
instance Typeable1 (T MyType2) where ...
Is this a bug in GHC?
Thanks,
Bas
More information about the Glasgow-haskell-users
mailing list