
Hi all, The DeriveGeneric language extension in ghc 7.4 does not support data families, so the following will not compile:
data family D a data instance D Int = DInt deriving Generic data instance D Bool = DBool deriving Generic
On http://hackage.haskell.org/trac/ghc/ticket/5936, I provided a patch for ghc which makes the above compile, giving the (approximately) the following instances for Rep and Generic:
type instance Rep (D Int) = D1 DIntInfo_D (C1 DIntInfo_C U1) type instance Rep (D Bool) = D1 DBoolInfo_D (C1 DBoolInfo_C U1)
instance Generic (D Int) where ... instance Generic (D Bool) where ...
Note in particular that D Int and D Bool are considered completely distinct types as far as generics are concerned. Is this the right approach to take to handle generics for data families? Are there alternative approaches? On the Trac ticket linked above, Pedro suggested we discuss these questions here. Regards, Reiner

Hi all, I am of the opinion that the approach I described in my previous email is reasonable. To me, the key point is that the Generic class (as opposed to the Generic1 class) is for types of kind *. Since D Bool and D Int are different types of kind *, it is reasonable for them to have unrelated instances for Generic. (The situation would be different for Generic1, once GHC supports deriving that). A similar question is what the following should do:
{-# LANGUAGE DeriveGeneric, FlexibleInstances, StandaloneDeriving #-} import GHC.Generics data T a = T a deriving instance Generic (T Bool)
Surprisingly, it currently generates the following instances:
instance Generic (T Bool) where ... type instance Rep (T a) = ...
This means, for instance, that the following does not compile:
{-# LANGUAGE DeriveGeneric, FlexibleInstances, StandaloneDeriving #-} import GHC.Generics data T a = T a deriving instance Generic (T Bool) deriving instance Generic (T Int)
because the "type instance Rep (T a) = ..." declarations conflict. I would say it should generate the following instances:
instance Generic (T Bool) where ... type instance Rep (T Bool) = ...
Note that these instances are of exactly the same form as the data family instances of my previous email. Regards, Reiner On 14/03/2012, at 9:57 AM, Reiner Pope wrote:
Hi all,
The DeriveGeneric language extension in ghc 7.4 does not support data families, so the following will not compile:
data family D a data instance D Int = DInt deriving Generic data instance D Bool = DBool deriving Generic
On http://hackage.haskell.org/trac/ghc/ticket/5936, I provided a patch for ghc which makes the above compile, giving the (approximately) the following instances for Rep and Generic:
type instance Rep (D Int) = D1 DIntInfo_D (C1 DIntInfo_C U1) type instance Rep (D Bool) = D1 DBoolInfo_D (C1 DBoolInfo_C U1)
instance Generic (D Int) where ... instance Generic (D Bool) where ...
Note in particular that D Int and D Bool are considered completely distinct types as far as generics are concerned.
Is this the right approach to take to handle generics for data families? Are there alternative approaches?
On the Trac ticket linked above, Pedro suggested we discuss these questions here.
Regards, Reiner

Hi Reiner,
On Wed, Mar 14, 2012 at 00:30, Reiner Pope
A similar question is what the following should do:
{-# LANGUAGE DeriveGeneric, FlexibleInstances, StandaloneDeriving #-} import GHC.Generics data T a = T a deriving instance Generic (T Bool)
Surprisingly, it currently generates the following instances:
instance Generic (T Bool) where ... type instance Rep (T a) = ...
Oh, this is a bug. I'll open a ticket for it and fix it soon. Thanks, Pedro
participants (2)
-
José Pedro Magalhães
-
Reiner Pope