Type error when deriving Generic for an associated data type

Hi, I'm hitting on an issue when deriving Generic for an associated data type: {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DeriveGeneric #-} import GHC.Generics class Foo a where data T a :: * instance Foo Int where data T Int = Bla deriving Generic Couldn't match type `Rep (T Int)' with `M1 t0 t1 (M1 t2 t3 U1)' Expected type: Rep (T Int) x Actual type: M1 t0 t1 (M1 t2 t3 U1) x In the pattern: M1 (M1 U1) In an equation for `to': to (M1 (M1 U1)) = Bla In the instance declaration for `Generic (T Int)' The GHC trac seems to be down. Is this a known issue? Cheers, Bas

Hi Bas.
I'm hitting on an issue when deriving Generic for an associated data type:
[...] Your example compiles for me with HEAD (but fails with 7.4.1 and 7.4.2, yes). I've not tested if it also "works". Cheers, Andres -- Andres Löh, Haskell Consultant Well-Typed LLP, http://www.well-typed.com

Hi Bas,
On Thu, Jul 12, 2012 at 11:27 AM, Bas van Dijk
Hi,
I'm hitting on an issue when deriving Generic for an associated data type:
...
The GHC trac seems to be down. Is this a known issue?
Yes, and it's supposed to be fixed in HEAD. Can you try it with HEAD? Thanks, Pedro
participants (3)
-
Andres Löh
-
Bas van Dijk
-
José Pedro Magalhães