[GHC] #13582: Confusing error message with multiparameter type classes.

GHC ghc-devs at haskell.org
Sat Apr 15 23:28:19 UTC 2017


#13582: Confusing error message with multiparameter type classes.
-------------------------------------+-------------------------------------
           Reporter:                 |             Owner:  (none)
  facundo.dominguez                  |
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
           Keywords:  type-checking  |  Operating System:  Unknown/Multiple
  errors                             |
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The following program
 {{{
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE FunctionalDependencies #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE UndecidableInstances #-}

 import Data.Typeable

 class First a b c | c -> b where
   first :: c -> a -> b

 class Second a b where
   second :: a -> b

 instance (Typeable b, First a b c) => Second a c where
   second = undefined

 main :: IO ()
 main = print (second (9 :: Int) :: Int)
 }}}
 produces the following error message
 {{{
 $ runghc-8.0.2 t.hs
 t.hs:18:15: error:
     • No instance for (Typeable b0) arising from a use of ‘second’
     • In the first argument of ‘print’, namely
         ‘(second (9 :: Int) :: Int)’
       In the expression: print (second (9 :: Int) :: Int)
       In an equation for ‘main’: main = print (second (9 :: Int) :: Int)
 }}}
 Note that the message does not explain where `b0` comes from.

 ghc-7.8.3 produced a better error message:
 {{{
 $ runghc-7.8.3 t.hs
 t.hs:18:15:
     No instance for (First Int b Int) arising from a use of ‘second’
     In the first argument of ‘print’, namely
       ‘(second (9 :: Int) :: Int)’
     In the expression: print (second (9 :: Int) :: Int)
     In an equation for ‘main’: main = print (second (9 :: Int) :: Int)
 }}}

 Doing slight modifications changes the error message that ghc-8.0.2. e.g.
 {{{
 - instance (Typeable b, First a b c) => Second a c where
 + instance (First a b c, Typeable b) => Second a c where
 }}}
 gives the same error as ghc-7.8.3.

 In a big program the current error is very puzzling. Is ghc picking the
 wrong error to show? Could it print more errors perhaps?

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13582>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list