Instance constraints should be used when deriving on associated data types
Consider this program:
{-# LANGUAGE TypeFamilies, FlexibleContexts #-}
class Eq (Associated a) => Foo a where
data Associated a
instance Foo a => Foo (Maybe a) where
data Associated (Maybe a) = AssociatedMaybe (Associated a)
deriving (Eq)
This does not compile, giving this error message:
/Users/mbolingbroke/Junk/Repro.hs:9:40:
No instance for (Eq (Associated a))
arising from the 'deriving' clause of a data type declaration
at /Users/mbolingbroke/Junk/Repro.hs:9:40-41
Possible fix:
add an instance declaration for (Eq (Associated a))
or use a standalone 'deriving instance' declaration instead,
so you can specify the instance context yourself
When deriving the instance for (Eq (Associated (Maybe a)))
However, this is surprising because I clearly state that a is Foo, and hence (Associated a) has an Eq instance by the superclass constraint on Foo.
If I point this out explicitly using standalone deriving it works:
{-# LANGUAGE TypeFamilies, FlexibleContexts #-}
{-# LANGUAGE StandaloneDeriving, FlexibleInstances #-}
class Eq (Associated a) => Foo a where
data Associated a
instance Foo a => Foo (Maybe a) where
data Associated (Maybe a) = AssociatedMaybe (Associated a)
-- deriving (Eq)
deriving instance Foo a => Eq (Associated (Maybe a))
So I think the default behaviour for "deriving" on an associated data family should be to include the constraints from the enclosing instance. For now the workaround is just to use standalone deriving.
Trac metadata
Trac field | Value |
---|---|
Version | 6.12.3 |
Type | FeatureRequest |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |