[GHC] #13415: Instance declarations don't recognize named wildcards

#13415: Instance declarations don't recognize named wildcards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: #13324 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- While exploring a fix for #13324, I was blocked pretty quickly by this limitation: instance declarations don't properly recognize named wildcards. Here is an example to demonstrate: {{{#!hs {-# LANGUAGE NamedWildCards #-} module Bug where instance _x => Show (Maybe a) }}} {{{ Bug.hs:4:10: error: • Illegal constraint: _x (Use ConstraintKinds to permit this) • In the context: _x While checking an instance declaration In the instance declaration for ‘Show (Maybe a)’ | 4 | instance _x => Show (Maybe a) | ^^^^^^^^^^^^^^^^^^^^ }}} GHC doesn't recognize that `_x` is just a type variable, not a named wildcard. I believe fixing this is just a matter of changing the ASTs for instance declarations to use `LHsSigWcType` instead of `LHsSigType`. Patch incoming. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13415 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13415: Instance declarations don't recognize named wildcards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch 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: #13324 | Differential Rev(s): Phab:D3332 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D3332 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13415#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13415: Instance declarations don't recognize named wildcards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch 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: #13324 | Differential Rev(s): Phab:D3332 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'd like to see whether #13324 can really fly first, and do this change as part of it. If #13324 doesn't fly, this change is just an unnecessary complication. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13415#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13415: Instance declarations don't recognize named wildcards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch 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: #13324 | Differential Rev(s): Phab:D3332 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:2 simonpj]:
If #13324 doesn't fly, this change is just an unnecessary complication.
I don't agree. This ticket demonstrates a somewhat orthogonal bug: the error messages for using named wildcards in instance declarations are wildly misleading! We should be able to fix this, even if it takes longer to make `PartialTypeSignatures` work for arbitrary instances with wildcards. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13415#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13415: Instance declarations don't recognize named wildcards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch 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: #13324 | Differential Rev(s): Phab:D3332 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): What would you like it to say? You get the exact same message from {{{ instance x => Show (Maybe a) }}} namely {{{ Foo.hs:4:10: error: * Illegal constraint: x (Use ConstraintKinds to permit this) * In the context: x While checking an instance declaration In the instance declaration for `Show (Maybe a)' | 4 | instance x => Show (Maybe a) | ^^^^^^^^^^^^^^^^^^^ }}} In any case, making instance declarations have `LHsSIgWcType` sounds as if instnace are ''allowed''' to have wildcards, but they aren't, so that feels like the wrong solution. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13415#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13415: Instance declarations don't recognize named wildcards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch 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: #13324 | Differential Rev(s): Phab:D3332 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:4 simonpj]:
What would you like it to say? You get the exact same message from {{{ instance x => Show (Maybe a) }}}
That isn't using a named wildcard, so I would expect that to give an error message involving `ConstraintKinds`. I wouldn't expect it from a named wildcard `_x`, however.
In any case, making instance declarations have `LHsSIgWcType` sounds as if instnace are ''allowed''' to have wildcards, but they aren't, so that feels like the wrong solution.
It's true that instance heads aren't allowed to have wildcards. But then again, there are many other types in which wildcards are allowed to appear syntactically (e.g., `data Foo _`) but are later rejected, so we're not breaking convention by doing this. Besides, I don't see any simpler solution. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13415#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13415: Instance declarations don't recognize named wildcards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch 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: #13324 | Differential Rev(s): Phab:D3332 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I still don't know what you are trying to achieve. The error message looks spot on to me, and is the same whether you write `x`, `x_`, `_x` or `xx`, just as it is in any other type that does not admit wildcards. What error message do you actually want? What about the other uses of `LHsSigType`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13415#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13415: Instance declarations don't recognize named wildcards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch 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: #13324 | Differential Rev(s): Phab:D3332 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): The point that I'm trying to make is that we're gradually transitioning instance declarations over to recognizing wildcard types, so this is a necessary first step to take in that direction. Having recognized this, we need to `Wc`-ify the `LHsSigType`s used in instance declaration AST types. Having done so, we will get the //immediate// benefit of having better error messages when named wildcards are used, and we will get the knock-on benefit of making it easier for named wildcard to be properly integrated later. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13415#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13415: Instance declarations don't recognize named wildcards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch 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: #13324 | Differential Rev(s): Phab:D3332 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
will get the immediate benefit of having better error messages
Why will the error messages get better? Can you give an example? Is that an argument for putting wildcards everywhere? Why couldn't we just improve the error messages for `LHsSigType`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13415#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13415: Instance declarations don't recognize named wildcards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch 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: #13324 | Differential Rev(s): Phab:D3332 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I feel like we might not be on the same page here, so let me try to clear things up. I might be operating under a misconception here, but isn't it impossible to properly detect wildcards in a type (and integrate it with `-XPartialTypeSignatures`) unless it's a `LHsSigWcType`? That is why the error message you get when you use named wildcards in instance contexts currently is so bizarre--it doesn't even properly //detect// that it's a wildcard, but instead misinterprets it as a type variable (leading to the not-quite-on-the-mark `-XConstraintKinds` error). So given this, if we are to be able to support `-XPartialTypeSignatures` eventually, we need to first transition from the use of `LHsSigType` in instance declarations to `LHsSigWcType`. I chose to do this first in its own Diff since: * It's far easier than adding `-XPartialTypeSignatures` support all in ome go. This is an easily identifiable and necessary component that still requires changing quite a few files, so splitting this task out will make the Diff(s) that //do// deal with `-XPartialTypeSignatures` support less noisy. * It requires a Haddock change, which is somewhat ugly, and I'd rather get it out of the way upfront. * It has the immediate benefit of getting GHC to recognize named wildcards in instance declarations, as noted above. Does that make sense? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13415#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13415: Instance declarations don't recognize named wildcards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch 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: #13324 | Differential Rev(s): Phab:D3332 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
I might be operating under a misconception here, but isn't it impossible to properly detect wildcards in a type
What do you mean by "properly detect"? How would things be better if we did "properly detect" them? Specifically * Why will the error messages get better? Can you give an example? * Is that an argument for putting wildcards everywhere? Why should only instance declarations get the benefit of this error message improvement? * Why couldn't we just improve the error messages for `LHsSigType`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13415#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13415: Instance declarations don't recognize named wildcards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch 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: #13324 | Differential Rev(s): Phab:D3332 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:10 simonpj]:
What do you mean by "properly detect"?
I'll once again point you to the original example that I reported: {{{#!hs {-# LANGUAGE NamedWildCards #-} module Bug where instance _x => Show (Maybe a) }}} {{{ Bug.hs:4:10: error: • Illegal constraint: _x (Use ConstraintKinds to permit this) • In the context: _x While checking an instance declaration In the instance declaration for ‘Show (Maybe a)’ | 4 | instance _x => Show (Maybe a) | ^^^^^^^^^^^^^^^^^^^^ }}} In this example, **`_x` is a named wildcard, and GHC is not detecting this.** The error message //should// be that we're using a named wildcard without having `-XPartialTypeSignatures` on.
How would things be better if we did "properly detect" them? Specifically
* Why will the error messages get better? Can you give an example?
Yes. Please refer to [https://phabricator.haskell.org/D3332#e4a3ef42 this test case] in Phab:D3332. Instead of the completely misleading error message about `-XConstraintKinds` that it currently gives, it now detects the use of a named wildcard and says: {{{#!hs Wildcard ‘_x’ not allowed in an instance declaration for ‘Show’ }}} It doesn't suggest turning on `-XPartialTypeSignatures` yet because that's the subject of #13324, and as I noted in comment:9, even getting GHC to recognize the use of a wildcard in instance declarations is a somewhat significant task, which is why I opened a separate ticket for it in the first place.
* Is that an argument for putting wildcards everywhere? Why should only instance declarations get the benefit of this error message improvement?
That's not at all what I'm trying to advocate for here. The point (which I tried to articulate in comment:9, but I'll restate here) is that we have identified a place where we'd //like// to have wildcard constraints, so in order to accomplish that goal, we need to: 1. Change the use of `LHsSigType` in instance declarations to `LHsSigWcType` so that we can use wildcards there in the first place 2. Change the typechecker code so that it fills in wildcard constraints when typechecking instance contexts Doing both in one go would be an enormous change, so I'm trying to do this piecemeal and tackle (1) on its own first. That's it. (I originally made an appeal to having better error messages from this change, but now I thoroughly regret doing so, because it has completely derailed the discussion.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13415#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13415: Instance declarations don't recognize named wildcards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch 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: #13324 | Differential Rev(s): Phab:D3332 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): OK so there are two separate things * Error messages. You say "_x is a named wildcard and GHC is not detecting it". So perhaps, with `NamedWildCards` we should complain about `_x` in any `LHsSigType`, rather than treating it as an ordinary type variable. Good plan: that would nail the error message issue. * Extending instance declarations to support wildcards. You want to do this in two steps. I'd prefer to take the second step (getting the payoff) before committing the first. Step 2 may turn out to influence Step 1. (E.g. the only wildcard we want to allow is in the context.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13415#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13415: Instance declarations don't recognize named wildcards -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: #13324 | Differential Rev(s): Phab:D3332 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * resolution: => invalid Comment: Very well, I'll stop pursuing this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13415#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC