Poor error message with equational type constraints
GHCi 8.0.1 is giving a poor error message when it can't derive a typeclass when there's an equational type constraint involved. A simple example:
{-# LANGUAGE TypeFamilies #-}
class Foo a where
type FooInner a
fromInner :: FooInner a -> a
newtype Bar = Bar { fromBar::Char } deriving (Show)
instance Foo Bar where
type FooInner Bar = Char
fromInner = Bar
myFunc :: (Foo foo, FooInner foo ~ Char) => String -> foo
myFunc = fromInner . head
Many things work as expected:
ghc> :t myFunc
myFunc :: (FooInner foo ~ Char, Foo foo) => String -> foo
ghc> :t (myFunc "z")
(myFunc "z") :: (FooInner foo ~ Char, Foo foo) => foo
ghc> (myFunc "z") :: Bar
Bar {fromBar = 'z'}
but if I just evaluate the function without the typecast I get an error:
ghc> myFunc "z"
<interactive>:486:1: error:
• Illegal equational constraint FooInner foo ~ Char
(Use GADTs or TypeFamilies to permit this)
• When checking the inferred type
it :: forall foo. (FooInner foo ~ Char, Foo foo) => foo
Now, there should certainly be an error here: GHC doesn't know the exact type of myFunc
so it can't check if it's an instance of Show
. However, unless I'm not understanding what's going on, the error should be something like "Could not deduce Show", not "Illegal equational constraint". Even if that is what's going on, the suggestion to "Use GADTs or TypeFamilies to permit this" is clearly wrong, as I am already using TypeFamilies
.
Trac metadata
Trac field | Value |
---|---|
Version | 8.0.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |