
#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