[GHC] #13443: Typeclass resolution errors quite puzzling

#13443: Typeclass resolution errors quite puzzling -------------------------------------+------------------------------------- Reporter: tomjaguarpaw | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This ticket is based on a post I made to haskell-cafe: https://mail.haskell.org/pipermail/haskell-cafe/2016-August/124622.html Here's a program with an odd error message (GHC 8.0.1): {{{ data A a = A a deriving Eq data B = B main :: IO () main = print (A B == A B) test/main.hs:5:15: error: • No instance for (Eq B) arising from a use of ‘==’ • In the first argument of ‘print’, namely ‘(A B == A B)’ In the expression: print (A B == A B) In an equation for ‘main’: main = print (A B == A B) }}} I get an error about `Eq B` even though it's `Eq A` that is manifestly required at the call site. This error is odder when `A` and `B` are defined far away from the use of `==`. This is even odder: {{{ data A a = A a data B = B instance Ord a => Eq (A a) where main :: IO () main = print (A B == A B) test/main.hs:7:15: error: • No instance for (Ord B) arising from a use of ‘==’ • In the first argument of ‘print’, namely ‘(A B == A B)’ In the expression: print (A B == A B) In an equation for ‘main’: main = print (A B == A B) }}} Now not only is the type puzzling (`B` instead of `A`) but the *class* is puzzling (`Ord` instead of `Eq`). This occurred to me in practice because `Data.Graph.Inductive.PatriciaTree.Gr` has `(Eq a, Ord b) => Eq (Gr a b)`. It would have been a lot more helpful to see {{{ * No instance for (Ord B) * arising from (Eq A) * arising from the use of '==' }}} Does anyone agree with me that GHC should produce the full trace when it fails to resolve instances rather than just the proximal failure? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13443 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13443: Typeclass resolution errors quite puzzling -------------------------------------+------------------------------------- Reporter: tomjaguarpaw | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * failure: None/Unknown => Poor/confusing error message * milestone: => 8.4.1 Comment: I think it would be very useful to offer this as an option. Turning it on by default could be quite harmful, however, as context reduction can take many steps (thousands or more in type-heavy code) and we don't want to use a ton of memory unnecessarily. One option might be to let users set a particular maximum depth to report. Another (maybe?) could be to add a feature a bit like `HasCallStack` at the type level. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13443#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13443: Typeclass resolution errors quite puzzling -------------------------------------+------------------------------------- Reporter: tomjaguarpaw | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Old description:
This ticket is based on a post I made to haskell-cafe: https://mail.haskell.org/pipermail/haskell-cafe/2016-August/124622.html
Here's a program with an odd error message (GHC 8.0.1):
{{{ data A a = A a deriving Eq data B = B
main :: IO () main = print (A B == A B)
test/main.hs:5:15: error: • No instance for (Eq B) arising from a use of ‘==’ • In the first argument of ‘print’, namely ‘(A B == A B)’ In the expression: print (A B == A B) In an equation for ‘main’: main = print (A B == A B) }}}
I get an error about `Eq B` even though it's `Eq A` that is manifestly required at the call site. This error is odder when `A` and `B` are defined far away from the use of `==`.
This is even odder:
{{{ data A a = A a data B = B
instance Ord a => Eq (A a) where
main :: IO () main = print (A B == A B)
test/main.hs:7:15: error: • No instance for (Ord B) arising from a use of ‘==’ • In the first argument of ‘print’, namely ‘(A B == A B)’ In the expression: print (A B == A B) In an equation for ‘main’: main = print (A B == A B) }}}
Now not only is the type puzzling (`B` instead of `A`) but the *class* is puzzling (`Ord` instead of `Eq`). This occurred to me in practice because `Data.Graph.Inductive.PatriciaTree.Gr` has `(Eq a, Ord b) => Eq (Gr a b)`.
It would have been a lot more helpful to see
{{{ * No instance for (Ord B) * arising from (Eq A) * arising from the use of '==' }}}
Does anyone agree with me that GHC should produce the full trace when it fails to resolve instances rather than just the proximal failure?
New description: This ticket is based on a post I made to haskell-cafe: https://mail.haskell.org/pipermail/haskell-cafe/2016-August/124622.html Here's a program with an odd error message (GHC 8.0.1): {{{#!hs data A a = A a deriving Eq data B = B main :: IO () main = print (A B == A B) test/main.hs:5:15: error: • No instance for (Eq B) arising from a use of ‘==’ • In the first argument of ‘print’, namely ‘(A B == A B)’ In the expression: print (A B == A B) In an equation for ‘main’: main = print (A B == A B) }}} I get an error about `Eq B` even though it's `Eq A` that is manifestly required at the call site. This error is odder when `A` and `B` are defined far away from the use of `==`. This is even odder: {{{#!hs data A a = A a data B = B instance Ord a => Eq (A a) where main :: IO () main = print (A B == A B) test/main.hs:7:15: error: • No instance for (Ord B) arising from a use of ‘==’ • In the first argument of ‘print’, namely ‘(A B == A B)’ In the expression: print (A B == A B) In an equation for ‘main’: main = print (A B == A B) }}} Now not only is the type puzzling (`B` instead of `A`) but the *class* is puzzling (`Ord` instead of `Eq`). This occurred to me in practice because `Data.Graph.Inductive.PatriciaTree.Gr` has `(Eq a, Ord b) => Eq (Gr a b)`. It would have been a lot more helpful to see {{{ * No instance for (Ord B) * arising from (Eq A) * arising from the use of '==' }}} Does anyone agree with me that GHC should produce the full trace when it fails to resolve instances rather than just the proximal failure? -- Comment: Demilestoning as no one has stepped up to carry this out yet. Do ping if this sounds like the sort of project you would like to try. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13443#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC