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

#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

#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 Resolution: | Keywords: type-checking | errors multiparameter type classes Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by facundo.dominguez): * keywords: type-checking errors => type-checking errors multiparameter type classes -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13582#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | Keywords: type-checking | errors multiparameter type classes Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by facundo.dominguez: @@ -45,1 +45,2 @@ - Doing slight modifications changes the error message that ghc-8.0.2. e.g. + Doing slight modifications changes the error message that ghc-8.0.2 shows. + e.g. New description: 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 shows. 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#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | Keywords: type-checking | errors multiparameter type classes Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Are you saying that GHC 7.8's error message is better because it mentions `b` rather than `b0`? HEAD also use `b0` rather than `b`. Really there are two unsolved constraint: {{{ [WD] $dFirst_a2yX {1}:: First Int b0_a2yW[tau:1] Int (CDictCan) [WD] $dTypeable_a2yY {1}:: Typeable b0_a2yW[tau:1] (CDictCan) }}} Both mention the same unification variable. I don't know why 7.8 reports it differently. But you are right. The Big Thing is that ''unification variables currently do not record their origin''. Would it be better to say this? {{{ b0 is a unification variable arising from instantiating the call to 'second' on line 18 }}} But actually even that is not right. `b0` arises from using the instance declaration to simplify the constraint `Second Int Int`, which itself arises from the call to `second`. What would you LIKE it to say? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13582#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | Keywords: type-checking | errors multiparameter type classes Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by facundo.dominguez):
Are you saying that GHC 7.8's error message is better because it mentions b rather than b0?
No. It is better because it gives you a clue of how to fix it: Add an instance of `First Int b Int`. In contrast: {{{ No instance for (Typeable b0) arising from a use of ‘second’ }}} gives no clue of what the problem is. How does the user infer from this that the instance `First Int b Int` is missing? Consider that: * Even if `b0` is renamed to `b`, the user stays wondering which of all the `b`s in the program it might be. The class hierarchy might have multiple levels. * Even if we understood which class is introducing the constraint, we might not know which instantiation of the other type class parameters is being attempted.
What would you LIKE it to say?
{{{ No instance for (Typeable b0) arising from a use of ‘second’ from instance 'Second Int Int' which needs missing instances 'Typeable b' and 'First Int b Int'. }}} If there are more levels in the class hierarchy, the whole path to the missing instances should be reported from the method that the user called. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13582#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | Keywords: type-checking | errors multiparameter type classes Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
No. It is better because it gives you a clue of how to fix it: Add an instance of First Int b Int.
Alas, all that will happen then is that the missing `Typeable b` constraint will be reported. There really are two missing constraints, but GHC tries to avoid saturating the user by reporting only one per birth site. Reporting the entire path to a constraint is quite painful/voluminous, but I can see the point. Good ideas in here for better error messages. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13582#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Resolution: | Keywords: type-checking | errors multiparameter type classes, | TypeErrorMessages Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: type-checking errors multiparameter type classes => type- checking errors multiparameter type classes, TypeErrorMessages -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13582#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC