[GHC] #13415: Instance declarations don't recognize named wildcards
GHC
ghc-devs at haskell.org
Mon Mar 20 13:55:59 UTC 2017
#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
More information about the ghc-tickets
mailing list