[GHC] #11672: Poor error message

#11672: Poor error message -------------------------------------+------------------------------------- Reporter: adamgundry | Owner: adamgundry Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 (Type checker) | Keywords: ErrorMessages | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: #11198 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- [https://mail.haskell.org/pipermail/haskell-cafe/2016-February/123262.html Daniel Díaz recently pointed out] a particularly terrible error message. Here's a reduced example: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE KindSignatures #-} module BadError where import GHC.TypeLits import Data.Proxy f :: Proxy (a :: Symbol) -> Int f _ = f (Proxy :: Proxy (Int -> Bool)) }}} With GHC 8.0 RC2, this leads to the following error: {{{ • Expected kind ‘Proxy ((->) Int Bool)’, but ‘Data.Proxy.Proxy :: Proxy (Int -> Bool)’ has kind ‘Proxy (Int -> Bool)’ • In the first argument of ‘f’, namely ‘(Proxy :: Proxy (Int -> Bool))’ In the expression: f (Proxy :: Proxy (Int -> Bool)) In an equation for ‘f’: f _ = f (Proxy :: Proxy (Int -> Bool)) }}} or with `-fprint-explicit-kinds -fprint-explicit-coercions`: {{{ • Expected kind ‘Proxy Symbol (((->) |> <*>_N -> <*>_N -> U(hole:{aCy}, *, Symbol)_N) Int Bool)’, but ‘(Data.Proxy.Proxy) @ k_aCv @ t_aCw :: Proxy (Int -> Bool)’ has kind ‘Proxy * (Int -> Bool)’ }}} As Iavor, Richard and I discussed, this message has at least three separate problems: * It says `kind` when it should say `type`. * `((->) Int Bool)` is printed instead of `Int -> Bool` (because there is a coercion hiding in the type). * The real error is the insoluble constraint `Symbol ~ *`, which is not reported at all! The first two should be fairly easy to fix. For the third, when reporting insoluble constraints, we should prefer to report those on which no other constraints depend. (In this case, the presence of `hole:{aCy}` in the constraint is an explicit dependency on the other constraint.) I'll try to take a look at this. It is no doubt related to #11198. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11672 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11672: Poor error message -------------------------------------+------------------------------------- Reporter: adamgundry | Owner: adamgundry Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Keywords: Resolution: | ErrorMessages, TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11198 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: ErrorMessages => ErrorMessages, TypeInType -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11672#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11672: Poor error message -------------------------------------+------------------------------------- Reporter: adamgundry | Owner: adamgundry Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Keywords: Resolution: | ErrorMessages, TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11198 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): For reference, here is the current error message in GHC 8.0.1/HEAD: {{{ • Couldn't match type ‘*’ with ‘Symbol’ Expected type: Proxy ((->) Int Bool) Actual type: Proxy (Int -> Bool) Use -fprint-explicit-kinds to see the kind arguments • In the first argument of ‘f’, namely ‘(Proxy :: Proxy (Int -> Bool))’ In the expression: f (Proxy :: Proxy (Int -> Bool)) In an equation for ‘f’: f _ = f (Proxy :: Proxy (Int -> Bool)) }}} This seems to address the first and third bullet points above. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11672#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11672: Poor error message -------------------------------------+------------------------------------- Reporter: adamgundry | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Keywords: Resolution: | ErrorMessages, TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11198 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by adamgundry): * owner: adamgundry => -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11672#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11672: Poor error message -------------------------------------+------------------------------------- Reporter: adamgundry | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Keywords: Resolution: | TypeErrorMessages, TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11198 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: ErrorMessages, TypeInType => TypeErrorMessages, TypeInType -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11672#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11672: Poor error message
-------------------------------------+-------------------------------------
Reporter: adamgundry | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.0.1-rc2
checker) | Keywords:
Resolution: | TypeErrorMessages, TypeInType
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect | Unknown/Multiple
warning at compile-time | Test Case:
Blocked By: | Blocking:
Related Tickets: #11198 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#11672: Poor error message -------------------------------------+------------------------------------- Reporter: adamgundry | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Keywords: Resolution: fixed | TypeErrorMessages, TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | typecheck/should_fail/T11672 Blocked By: | Blocking: Related Tickets: #11198 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * testcase: => typecheck/should_fail/T11672 * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11672#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC