[GHC] #11672: Poor error message

GHC ghc-devs at haskell.org
Fri Mar 4 09:12:06 UTC 2016


#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


More information about the ghc-tickets mailing list