#4896: Deriving Data does not work for attached code
---------------------------------+------------------------------------------
Reporter: mitar | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.1
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
Comment(by dreixel):
Let me sketch quickly how I think this should work. We have a type family
`T` and a data family `D`:
{{{
type family T :: * -> *
type instance T Int = ()
...
data family D a
data instance D Int = DInt Float
...
}}}
Regarding the type family `T`, I don't think deriving instances makes much
sense. We want `typeOf (() :: T Int) == typeOf ()`, because `T Int ~ ()`.
The same goes for `Data` and any other class, I guess: we just use the
instance of the synonym, if there is one, and complain if there isn't.
Data families are more interesting. For `Typeable`, I guess it is sensible
to allow deriving at the declaration spot:
{{{
-- deriving instance Typeable1 D
-- Should generate
instance Typeable1 D where
typeOf1 _ = mkTyConApp (mkTyCon "Test.D") []
}}}
Although I find the empty list above a bit suspicious, this seems to be
similar to the instance given for lists as well, for instance. The
`Typeable` instance follows automatically from this `Typeable1` instance.
`Data` is another story. We certainly cannot derive anything at the
declaration point, since we know nothing about the constructors. For each
instance, however, we know something:
{{{
instance Data (D Int) where
toConstr (DInt f) = dintConstr
dataTypeOf _ = dDatatype
gfoldl k z (DInt f) = z DInt `k` f
gunfold k z c = case constrIndex c of
_ -> undefined -- what do we do here?
dintConstr :: Constr
dintConstr = mkConstr dDatatype "DInt" [] Prefix
dDatatype :: DataType
dDatatype = mkDataType "Test.D" [dintConstr] -- trouble!
}}}
But there is one major problem (which raises the two issues above in the
derived code). In the datatype description `dDatatype` we have to list all
the constructors, but the set of constructors of a data family is open, so
we can't do this.
Interestingly, `gfoldl` doesn't seem problematic. So I guess there are
three options here:
1) Allow deriving `Data` for data family instances filling out only
`gfoldl` and throwing errors for the others.
2) Refuse to generate `Data` instances for data families, as this is not
possible in general.
3) Redesign `syb` such that it allows such instances.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4896#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs