[GHC] #10722: GHC generates wrong unused type argument warning(ScopedTypeVariables related)

#10722: GHC generates wrong unused type argument warning(ScopedTypeVariables related) -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE KindSignatures, ScopedTypeVariables #-} {-# OPTIONS_GHC -Wall #-} module Main where import Data.Proxy class Blah (a :: * -> *) where f :: a b -> b instance forall b . Blah [] where f a = let (_ :: Proxy b) = undefined in head a main :: IO () main = return () }}} When I run this using GHC 7.10.1 and GHC HEAD, I'm getting this warnings: {{{ [1 of 1] Compiling Main ( Main.hs, Main.o ) Main.hs:12:17: warning: Unused quantified type variable ‘b’ In the type ‘forall b. Blah []’ In an instance declaration Main.hs:13:13: warning: This pattern-binding binds no variables: (_ :: Proxy b) = undefined Linking Main ... }}} First warning is wrong. `b` is used, and this program doesn't compile if I remove that `b`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10722 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10722: GHC accepts "instance forall b. Blah []" -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * failure: None/Unknown => GHC accepts invalid program Old description:
{{{#!hs {-# LANGUAGE KindSignatures, ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wall #-}
module Main where
import Data.Proxy
class Blah (a :: * -> *) where f :: a b -> b
instance forall b . Blah [] where f a = let (_ :: Proxy b) = undefined in head a
main :: IO () main = return () }}}
When I run this using GHC 7.10.1 and GHC HEAD, I'm getting this warnings:
{{{ [1 of 1] Compiling Main ( Main.hs, Main.o )
Main.hs:12:17: warning: Unused quantified type variable ‘b’ In the type ‘forall b. Blah []’ In an instance declaration
Main.hs:13:13: warning: This pattern-binding binds no variables: (_ :: Proxy b) = undefined Linking Main ... }}}
First warning is wrong. `b` is used, and this program doesn't compile if I remove that `b`.
New description: {{{#!hs {-# LANGUAGE KindSignatures, ScopedTypeVariables #-} {-# OPTIONS_GHC -Wall #-} module Main where import Data.Proxy class Blah (a :: * -> *) where f :: a b -> b instance forall b . Blah [] where f a = let (_ :: Proxy b) = undefined in head a main :: IO () main = return () }}} When I run this using GHC 7.10.1 and GHC HEAD, I'm getting this warnings: {{{ [1 of 1] Compiling Main ( Main.hs, Main.o ) Main.hs:12:17: warning: Unused quantified type variable ‘b’ In the type ‘forall b. Blah []’ In an instance declaration Main.hs:13:13: warning: This pattern-binding binds no variables: (_ :: Proxy b) = undefined Linking Main ... }}} but the program compiles successfully. -- Comment: Assuming you wanted to refer to the type variable `b` in the type of `f`, you should use InstanceSigs as described in section 7.6.3.6 of https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/type- class-extensions.html: {{{ instance Blah [] where f :: forall b. [b] -> b f a = let (_ :: Proxy b) = undefined in head a }}} `instance forall b . Blah []` is meaningless, and should be rejected. I edited the ticket description accordingly. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10722#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10722: GHC accepts "instance forall b. Blah []" -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by osa1): Do you mean this syntax should be rejected by the parser? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10722#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10722: GHC accepts "instance forall b. Blah []" -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Well I don't care exactly how it is implemented, but logically it is a parse error yes. It is the same category of error as {{{ instance Int -> Blah [] where ... }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10722#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10722: GHC accepts "instance forall b. Blah []" -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Actually I suppose you could view it as new syntax enabled by ScopedTypeVariables. It is harmless, but also useless (variables mentioned in the instance head are scoped over the instance body automatically, and variables not mentioned in the instance head will never be forced to be any particular type). I still tend to think the syntax should be invalid. I assume what's going on here is that the parser parses everything between `instance` and `where` as a "type", and then does some sanity checks to make sure the instance declaration isn't too ill-formed. But some stuff falls through the cracks here, like {{{ instance (Eq T) where ... -- should be rejected according to the Report, -- but is accepted by ghc }}} That one might not be worth fixing though. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10722#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10722: GHC accepts "instance forall b. Blah []" -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => invalid Comment: comment:1 isn't right: with `ScopedTypeVariables` the type variables mentioned the instance head are in scope in the instances (see [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/other- type-extensions.html#cls-inst-scoped-tyvars the manual]). Eg {{{ instance Eq a => Eq [a] where (==) (x:xs) (y:ys) = (x::a) == y) && (xs::[a] == ys) }}} should work just fine. You don't even need a forall. (I will add a note to say this.) However the variable `b` is unused in instance head, and there is really no point in having it there; hence the message. If you have a use-case where you want an instance to be quantified over a type that is not mentioned in the instance head, I'd be glad to see it. Meanwhile I'll mark this as invalid. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10722#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10722: GHC accepts "instance forall b. Blah []"
-------------------------------------+-------------------------------------
Reporter: osa1 | Owner:
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 7.11
Resolution: invalid | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC accepts | Unknown/Multiple
invalid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones
participants (1)
-
GHC