[GHC] #12393: Poor error message with equational type constraints

#12393: Poor error message with equational type constraints --------------------------------------+--------------------------------- Reporter: laneb | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Linux Architecture: x86_64 (amd64) | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+--------------------------------- 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: {{{#!hs {-# 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}}}. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12393 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12393: Poor error message with equational type constraints ---------------------------------+-------------------------------------- Reporter: laneb | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by rwbarton):
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.
Actually, it's technically not wrong: you don't have TypeFamilies turned on ''in GHCi'' which is where the problematic constraint arose. But I certainly agree that GHC should just give the ambiguous type variable error in preference to the one it gave you, and probably shouldn't bother checking the inferred type of `it` at all. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12393#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12393: Poor error message with equational type constraints ---------------------------------+-------------------------------------- Reporter: laneb | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by rwbarton): Also note that there is another ticket somewhere about having flags set in the current module be in effect in ghci also, which would address this case too. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12393#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12393: Poor error message with equational type constraints ---------------------------------+-------------------------------------- Reporter: laneb | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: invalid | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11469 | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Changes (by thomie): * status: new => closed * component: Compiler => GHCi * resolution: => invalid * related: => #11469 Comment: If you turn on `GADTs` or `TypeFamilies` in GHCi, you'll get the error message you were hoping for. {{{ *Test> :set -XGADTs *Test> myFunc "z" <interactive>:3:1: error: • Couldn't match expected type ‘Char’ with actual type ‘FooInner a0’ The type variable ‘a0’ is ambiguous • In the first argument of ‘print’, namely ‘it’ In a stmt of an interactive GHCi command: print it }}} I'm closing this ticket. I agree that the original error message is poor, but #11469 (the ticket referred to in comment:2) will fix the problem. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12393#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC