[GHC] #11451: Inconsistent warnings for unused binders

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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: -------------------------------------+------------------------------------- Consider compiling this with `-Wunused-matches`: {{{ class C a where op :: a -> a instance C (Maybe a) where op x = x }}} We get no warnings, even though `a` is patently unused. But suppose we add an associated type {{{ class C a where type T a op :: a -> a instance C (Maybe a) where type T (Maybe a) = Int -- Warning on this line op x = x }}} Now we get a warning for an unused binding for `a` on the `type instance`. Edward complained about this inconsistent behaviour in [https://mail.haskell.org/pipermail/glasgow-haskell- users/2016-January/026114.html this email thread]. My thoughts: * Currently GHC does not warn about type variables bound in the instance head but unused in the `where` part. Fixing that might be a good idea, but would be a new feature. * However, given that we don't warn about them, we should definitely not warn about instance type variables being unused in an associated type. But we could warn about ones specific to the associated type itself. Eg {{{ class C2 a where type T2 a b instance C2 (Maybe a) where type T2 (Maybe a) x = Int -- Line XXX }}} Here, on line `XXX`, we might reasonably warn about the unused `x`, but not about the unused `a`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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 Lemming): I think that if a type variable is mentioned in an instance head this should count as usage. Then the according type patterns in associated types should be literally equal and should not get a warning. Thus I go with your second thought. Sure, this is somehow inconsistent with the value level, however, warning about unused type variables in this cases means I have to rewrite lots of code, even Haskell 98 code, to get rid of warnings and I guess, that `instance C (Maybe _)` is not even valid Haskell 98. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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: | -------------------------------------+------------------------------------- Changes (by kosmikus): * cc: kosmikus (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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 goldfire): Let's look more closely at {{{ instance C (Maybe a) where op x = x }}} Simon says that `a` is patently unused. I disagree: `a` is used in the instance head! The head of an instance is a type, and thus that `a` is a ''use'' site, not a ''binding'' site. The point of confusion is that we use usage sites to infer the implicit bindings. Contrast to a class declaration, where the type variables are indeed binding sites. Separately, I'm agreed with Simon's very last point about warning about `x` but not `a`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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): I see what you mean. After all, you could imagine that it is "really" {{{ instance forall a. C (Maybe a) where ... }}} BUT for `type instance` declarations we do allow {{{ type instance F (Maybe _) = Int }}} even though it's "really" {{{ type instance forall a. F (Maybe a) = Int }}} And here it really is persuasive to use `_`, in just the same way that we do in patterns in term-level function definitions. Why should the type patterns in a class instance declaration be treated differently than those in a type-family instance declaration? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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 goldfire): Good point. They shouldn't be different. It's just that it seems so natural to say `instance C (Maybe a)`. But perhaps it shouldn't. In any case, this discovery subtly redefines the goal of the warning: 1. Warn when a type variable is bound explicitly but never used. 2. Warn when a type variable is bound implicitly but used in only one place. Refining the goal with point (2) clarifies why there should be no warning in `type instance Equals x x = True`. What do we think about `length :: [_] -> Int`? According to my goals above, that should be the correct type signature, as opposed to `length :: [a] -> Int` which should emit a warning. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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):
What do we think about `length :: [_] -> Int`?
No, this is not a use in a ''type pattern'' (as are all they cases discussed above). It's an occurrence, pure and simple. This is explicitly covered by `PartialTypeSignatures` and I don't want to change all of that. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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 Lemming): From a software engineering point of view a warning about `instance C (Maybe a) where` could be useful to alert the programmer that he might have forgotten to add superclass constraints on `a`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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 ekmett): It is worth noting that we've developed a sort of culture of signaling intent with the names of those variables, when a Haskell programmer sees 'a' or 'b' they usually expect something of kind *, f as something of kind * -> *, etc. Is it right? Arguably not, but it is useful. If we're forced to replace all of those with _'s a lot of signal will be lost. There is also a concern that a warning here is something users won't be able to act on if they want to work at all on older compilers that didn't allow _s there. I don't have a concrete counter-proposal, but I do feel ill at ease. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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): You can always use `_f` to signal your intent. Just like at the term level. We never warn about unused variables starting with an underscore. Does that address your concern? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Currently GHC does not warn about type variables bound in the instance
#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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 ekmett): That can be used to work around this particular concern somewhat, though the mangled names will show up in haddocks and :t and the like, making things a lot noisier. In contrast, the stuff that happens at the value level doesn't make it into the documentation. I'm much more concerned by the mention that we may want to start applying this reasoning to instances, however. head but unused in the where part. Fixing that might be a good idea [snip] There one can argue that those type variables are serving multiple roles. Consider that {{{ instance Foo (a,a) }}} is quite different than {{{ instance a ~ b => Foo (a,b) }}} The fact that there are multiple type variables is actually providing information about what is required to unify with what. The instance head interacts with 'itself' in that way. The relationships between the type variables that show up in the signature matter, even if they never appear in the body itself. At the value level patterns are forced to be linear, multiple uses aren't a concern, but at least in instance heads non-linear patterns arise rather frequently, so that may make it more palatable to not try to shoehorn instance heads into this same uniform handling. Also, if dealing with the fact that every type family is going to start setting off alarm bells is bad, forcing a change on probably 95% of the instances out there is likely to cause panic in the streets. ;) It'd also show up in mangled form throughout the haddocks, creating an uncomfortable tension between seeing the warning and providing pretty documentation. That is less of a concern for type instances and class associated types, but mostly just because there are a lot fewer of those. My primary concern is that it isn't obvious to me that even a single user error in the wild will actually be caught by the change, in exchange for all of this mangling. I'm concerned that it seems like a lot of make-work for users and the end state isn't really any nicer than the one we started in, hence my unease above. We make things a little more strict for library authors, but make things uglier for users. I'd personally be okay with changing all my code around to work with these type families and type synonym warnings. That said, doing the same with instances seems like it would be a pretty radical departure from existing practice, and I think once we start doing this to `type`, we'll start eyeballing `data` and `newtype` next, and I can see a lot of code and documentation getting uglier with little upside and it getting worse the farther down that road we travel. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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): All that you say is true about type function too. In {{{ type instance F a a = Int }}} the `a` is definitely not unused becuase it is repeated. In both your examples the type variables patently are used, and no one is suggesting they are reported as unused: {{{ instance C a a where ... instance D a b => C (a,b) where... }}} But it really does seem useful an convenient to be able to write {{{ type instance F (Maybe _) = Int }}} to stress that the argument to `Maybe` plays no further role in matching or on the RHS. Isn't it? Similarly would it not be reasonable to allow {{{ instance C (Maybe _) where ... }}} to stress that the argument type of the `Maybe` plays no further role in resolving this class instance. So let me be more concrete. Here's a proposal: * If a type variable (a) is bound in a type pattern (b) appears at exactly once anywhere in its scope, then it is reported as unused. * A "type pattern" is * a type on the LHS of a `type instance` or * a type in the head of a class `instance` (i.e. the bit after the `=>`) * a type in a pattern type signature e.g. `case x of Just (x :: (a,b)) -> blah` Now, can you give me an example where that would be annoying? Mabye you are right, but let's see. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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 ekmett):
Now, can you give me an example where that would be annoying? Mabye you are right, but let's see.
Let's look at what happens to a real instance list for a data type that I have open on my screen, the haddocks would then show the following instances and class associated types. {{{#!hs Category * (Indexed _i) (~) * i j => Indexable i (Indexed j) Arrow (Indexed _i) ArrowChoice (Indexed _i) ArrowApply (Indexed _i) ArrowLoop (Indexed _i) Representable (Indexed _i) Corepresentable (Indexed _i) Choice (Indexed _i) Closed (Indexed _i) Strong (Indexed _i) Costrong (Indexed _i) Profunctor (Indexed _i) Conjoined (Indexed _i) Bizarre (Indexed Int) Mafic Sieve (Indexed i) ((->) i) Cosieve (Indexed i) ((,) i) Sellable (Indexed i) (Molten i) Bizarre (Indexed i) (Molten i) Monad (Indexed _i _a) Functor (Indexed _i _a) MonadFix (Indexed _i _a) Applicative (Indexed _i _a) Apply (Indexed _i _a) Bind (Indexed _i _a) type Rep (Indexed i) = (->) i type Corep (Indexed i) = (,) i }}} It seems to me the vast majority of instances I have lying around would get almost all of their arguments mangled. Using that as an entirely unscientific survey, 19/27 or ~70% of those instances would have to have their code changed, to get uglier haddocks. Ramped up to cut across the ~10000 instances in my active maintenance directory instead of the 27 in this single source file, that would be annoying. =/ ''Allowing'' the use of _'s in those positions seems perfectly fine to me, but requiring it would create tension between being able to provide clean- looking haddocks and avoiding this warning, or doing something cheesy like writing unnecessary, brittle, `InstanceSigs`. Ultimately, no user of `MonadState` cares about the fact that `s` isn't used in the body of {{{#!hs instance MonadReader r m => MonadReader r (StateT _s m) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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 Lemming): For me the warning could be as pedantic as Simon suggests, if it is not part of -Wall. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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): What I'm missing is this: why would it not be more perspicuous to say {{{ Category * (Indexed _) }}} That doesn't look like mangling to me. It looks like explaining that `Indexed` of anything is an instance. Similarly {{{ instance MonadReader r m => MonadReader r (StateT _ m) }}} Is that bad? If it is, why do you not object to the warning you get (for unused `y`) when you write this? {{{ f x y = x }}} I'm not arguing against you, just trying to understand. Are you also saying that you do not like {{{ type instance F (Maybe _) = Int }}} and that you want to be able to write {{{ type instance F (Maybe x) = Int }}} without a warning? That is, do you see class instances and type-function instances the same? It would be easier NOT to issue warnings. But if we do sometimes and not at other similar-looking times, I'd like to have a principled explanation. Can you give a general rule that informs your choices? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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 ekmett):
What I'm missing is this: why would it not be more perspicuous to say
{{{#!hs Category * (Indexed _) }}} So that in 3-4 years when I can stop supporting older compilers, I can finally lose the signaling of intent that comes from the conventions that we follow elsewhere of `f` and `m` and `a`? There is a lot of information packed in those conventions. Nobody reading the documentation cares whether the instance uses the argument or not, but this warning would force everyone to put that front and center in the documentation users see and seems to clutter about 70% of the variables in instances out there with a perl-like `_` sigil. I like having names for things rather than Miranda's `*`, `**`, `***`. That said, one of the biggest sources of teasing from the outside world about haskell is how short our type variable names tend to be, getting rid of them entirely like this ''is'' one way to avoid the argument. ;)
If it is, why do you not object to the warning you get (for unused y) when you write this?
{{{#!hs f x y = x }}} Nothing we do at the value level is reflected in the documentation; everything we do at the type level is reflected in the documentation. The fact that the value-level unused binding warning is on or not is invisible to the user of the library. Whether I turn on the warning about unused bindings at the value level or not the user never sees this fact. It remains entirely internal to the source file as a local concern.
That is, do you see class instances and type-function instances the same?
Going from the current state where ''can't'' use `_` in that position at all, to a new state where you ''must'' use `_` or `_a` in a place that affects generated documentation and affects the vast majority of instances that have ever been written seems like a big jump, when the existing style has been in use for 20+ years. This seems to indicate to me that doing this to instances is quite a big deal and the amount of work for the user community boggles my mind. As for type instances, this then hoists you on the dilemma of copying the value level warning style or matching the behavior of instances. The resolution you seem to be reaching for is to change the behavior of instances to match, and it would cleanly resolve the dilemma, but at a rather great cost. In many ways the same "it shows up in the documentation" argument applies to the `type instance` case as well, now that haddock actually shows type families, but there is a lot less code affected. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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): So the principle you are suggesting is that if it shows up in documentation you do not want to have a warning for unused variables. That's a fine principle; I just want to articulate it clearly. If so we should ensure that {{{ type instance F (Maybe a) = Int }}} does not give a warning. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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 ekmett): I think that adopting that principle would work and neatly encodes existing practice. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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 goldfire): I like Simon's proposal in comment:16. Nice and neat. But it still might be nice to get the full pedantic thing if we want it, with no intention, ever, of putting it in `-Wall`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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): Fine. Now we just need someone to implement it! Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders in type and instance declarations -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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: | -------------------------------------+------------------------------------- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders in type and instance declarations -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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 RyanGlScott): I'd be willing to implement this, but let me make sure I understand what's being proposed. My understanding is that: * `-Wunused-matches` should no longer warn about unused type variables. Instead, a different flag (I propose `-Wunused-type-variables`) should trigger this separately. * `-Wunused-type-variables` shouldn't be enabled when `-Wall` is on. (Do we want a `-pedantic` flag which implies `-Wunused-type-variables`?) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders in type and instance declarations -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1825 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D1825 Comment: A first shot at fixing this is Phab:D1825. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders in type and instance declarations -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1825 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I thought `-Wunused-type-variables` could be on with `-Wall`. But we just won't warn in situations where the type variable could appear in documentation. And then (optional extension for extra credit) we'd have a separate `-Wpedantic-unused-type-variables` that warned in all cases. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders in type and instance declarations -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1825 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I'm confused. Under what scenarios would type variables in instances ''not'' appear as documentation? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders in type and instance declarations -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1825 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): In a type signature in a term-level pattern, I suppose. But I agree that maybe there aren't enough places like this to motivate separating out the behavior. I guess you're design is closer to the spec than I thought. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders in type and instance declarations -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1825 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.0.1 Comment: So I guess there are no objections to moving ahead with this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders in type and instance declarations -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1825 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I've thought of a simpler spec still * If a type variable bound by an explicit, user-written `forall` is unused, we warn. * But it it is bound only by a type pattern (in a class or type instance declaration), we don't warn even if it is otherwise unused. That's nice and precise. I'm agnostic about what flags control this. I suppose you might want to say A. No warnings at all B. Warn about unused `forall`-bound variables C. Warn about those and unused pattern-bound variables (maybe) It's not clear that implementing C is worth it. (Yes that's what we currently have, more or less, but inconsistently.) I don't have a strong opinion about what flags should switch between A and B, or A/B/C. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders in type and instance declarations -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1825 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Simon, I believe we will have precisely what you described with Phab:D1825. `-Wname-shadowing` controls unused `forall`-ed type variables, and `Wtype-variables` controls unused type patterns separately. You can enable different combinations of them to achieve A, B, and C. The only remaining question is if we want a single flag that implies C (my previous name suggestion was `-pedantic`). This would be pretty easy to implement if we wanted it, since it would just enable a superset of the flags implied by `-Wall`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:28 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders in type and instance declarations -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1825 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Sorry, I'm wrong, it's also `-Wunused-matches` which warns about unused quantified type variables. Do you think it's worth having two separate flags for warning about term-level patterns vs. quantified type variables? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:29 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders in type and instance declarations -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1825 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Replying to [comment:28 RyanGlScott]:
Simon, I believe we will have precisely what you described with Phab:D1825. `-Wname-shadowing` controls unused `forall`-ed type variables, and `-Wtype-variables` controls unused type patterns separately. You can enable different combinations of them to achieve A, B, and C.
OK good. Minor suggestions: * Personally I think `-Wunused-matches` is a bit surprising as a control for `forall`'d type variables. I suggest `-Wunused-foralls`. Having one more warning flag is low overhead. * The documentation for `-Wunused-matches` is out of date. * I really like the specification that: "if a type variable bound by an explicit, user-written forall is unused, we warn". Let's use it for `-Wunused-foralls`. And mention it in the section on explicit `forall` (9.14.1). * In the documentation for `-Wunused-type-variables` I think it is helpful to speak of "type patterns", and contrast with `-Wunused-foralls` (cross- ref in manual). * No one is pushing for extending `-Wunused-type-variables` to class instances. It's a little inconsistent but I think fair enough. Maybe in the documentation for `-Wunused-type-varaibles` mention this point.
The only remaining question is if we want a single flag that implies C (my previous name suggestion was `-pedantic`). This would be pretty easy to implement if we wanted it, since it would just enable a superset of the flags implied by `-Wall`.
Separately [wiki:Design/Warnings] is debating sets of flags. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:31 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders in type and instance declarations -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1825 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I wholeheartedly agree with your points, although if we introduce a `-Wunused-foralls` flag, it will probably be confusing to also have `-Wunused-type-variables`, since `forall`-ed variables ''are'' type variables, after all. I think it might be better to rename `-Wunused-type- variables` to `-Wunused-type-patterns` in light of this (especially since you want to emphasize the distinction from `-Wunused-foralls`). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:32 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders in type and instance declarations -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1825 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): OK -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:33 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders in type and instance declarations -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1825 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I've updated Phab:D1825 to incorporate Simon's suggestions. Feedback is appreciated, since much of the changes are documentation-related (and you might want me to be more explicit about something you care about). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:34 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders in type and instance declarations -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1825 Wiki Page: | -------------------------------------+------------------------------------- Changes (by WrenThornton): * cc: wren@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:35 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders in type and instance declarations
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: patch
Priority: normal | Milestone: 8.0.1
Component: Compiler | Version: 7.10.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect | Unknown/Multiple
warning at compile-time | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1825
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott

#11451: Inconsistent warnings for unused binders in type and instance declarations -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1825 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => merge Comment: I've updated [https://ghc.haskell.org/trac/ghc/wiki/Design/Warnings Design/Warnings] to include the changes here and bring up the idea of `-Wpedantic`, if someone wants to implement that. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:37 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11451: Inconsistent warnings for unused binders in type and instance declarations -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1825 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged as 2d3f277817b3a173a5651fc8d10601851485302f. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11451#comment:38 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC