[GHC] #10722: GHC generates wrong unused type argument warning(ScopedTypeVariables related)
GHC
ghc-devs at haskell.org
Sat Aug 1 02:58:48 UTC 2015
#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
More information about the ghc-tickets
mailing list