[GHC] #10614: Show constraints in ``Found hole...''

#10614: Show constraints in ``Found hole...'' -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.10.1 Component: Compiler | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Currently it is not clear when types are known equal. Consider writing castWith: {{{#!hs {-# LANGUAGE GADTs , TypeOperators #-} import Data.Type.Equality hiding (castWith) castWith :: a :~: b -> a -> b castWith Refl x = _ }}} which results in {{{ TypeEq.hs:5:19: error: Found hole: _ :: b Where: ‘b’ is a rigid type variable bound by the type signature for: castWith :: a :~: b -> a -> b at TypeEq.hs:4:13 Relevant bindings include x :: a (bound at TypeEq.hs:5:15) castWith :: a :~: b -> a -> b (bound at TypeEq.hs:5:1) In the expression: _ In an equation for ‘castWith’: castWith Refl x = _ }}} Filling the hole with x is correct, but it is not clear from the message that GHC knows this. It would be useful to have a section "Constraints include" e.g. {{{ TypeEq.hs:5:19: error: Found hole: _ :: b Where: ‘b’ is a rigid type variable bound by the type signature for: castWith :: a :~: b -> a -> b at TypeEq.hs:4:13 Relevant bindings include x :: a (bound at TypeEq.hs:5:15) castWith :: a :~: b -> a -> b (bound at TypeEq.hs:5:1) Constraints include <------ NEW LINE a ~ b (from Refl :: a :~: a at TypeEq.hs:5:10) <------ NEW LINE In the expression: _ In an equation for ‘castWith’: castWith Refl x = _ }}} And show class constraints (Show a etc.) similarly -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10614 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10614: Show constraints in ``Found hole...'' -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Yes, that would not be hard. Are you sure you want the class constraints too? Why? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10614#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10614: Show constraints in ``Found hole...'' -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): +1. And with the class constraints listed, too. When you're having trouble knowing what type you want, more information is better (to me). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10614#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10614: Show constraints in ``Found hole...'' -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: 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 zyla): +1 for class constraints. This comes up a lot when working with existentials. Consider this (contrived) example: {{{#!hs {-# LANGUAGE GADTs #-} data AnyShow where AnyShow :: Show a => a -> AnyShow foo :: AnyShow -> String foo (AnyShow x) = _ }}} GHC currently (8.1.20161115) gives the following message: {{{ foo.hs:6:19: error: • Found hole: _ :: p Where: ‘p’ is a rigid type variable bound by the inferred type of foo :: AnyShow -> p at foo.hs:6:1-19 • In the expression: _ In an equation for ‘foo’: foo (AnyShow x) = _ • Relevant bindings include x :: a (bound at foo.hs:6:14) foo :: AnyShow -> p (bound at foo.hs:6:1) }}} The situation is even worse here than in OP's example, since `a` appears out of nowhere, and `Show a` isn't mentioned. But I think the decision whether to include them isn't that hard - we could have both `-fprint-equality-constraints` and `-fprint-class- constraints`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10614#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10614: Show constraints in ``Found hole...'' -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: 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 Iceland_jack): Replying to [comment:3 zyla]:
+1 for class constraints. This comes up a lot when working with existentials. Consider this (contrived) example: +1 not so contrived, I have encountered it and more complex examples
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10614#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10614: Show constraints in ``Found hole...'' -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: 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): This would not be hard. * Error messages generation is highly localised, in `TcErrors` * All the info about in-scope constraints is right there in the constraint tree, and is accessible in just the same way that we extract the "relevant bindings". More easily, actually! The only hard bit is deciding exactly what to print, and with what flags to control it. I'm happy to offer guidance. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10614#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10614: Show constraints in ``Found hole...'' -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: 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 zyla): I can work on this. If I understand correctly, the needed information is in `ic_given` of `Implication` in `cec_encl` of the `ReportErrCtxt`. Is this right? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10614#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10614: Show constraints in ``Found hole...'' -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: 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):
If I understand correctly, the needed information is in ic_given of Implication in cec_encl of the ReportErrCtxt
Yes, exactly! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10614#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10614: Show constraints in ``Found hole...'' -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: feature request | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | https://phabricator.haskell.org/D2767 -------------------------------------+------------------------------------- Changes (by zyla): * status: new => patch * differential: => https://phabricator.haskell.org/D2767 Comment: I've submitted a patch to Phabicator. There are some problems though: - `pprSkolInfo` is reused for printing the source of the constraints, and the messages become quite long. - It doesn't yet detect duplicates. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10614#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10614: Show constraints in ``Found hole...''
-------------------------------------+-------------------------------------
Reporter: bjmprice | Owner:
Type: feature request | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: | https://phabricator.haskell.org/D2767
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#10614: Show constraints in ``Found hole...'' -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | https://phabricator.haskell.org/D2767 -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10614#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC