[GHC] #13512: GHC incorrectly warns that a variable used in a type application is unused
GHC
ghc-devs at haskell.org
Sun Apr 2 14:17:04 UTC 2017
#13512: GHC incorrectly warns that a variable used in a type application is unused
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
(Type checker) |
Keywords: | Operating System: Unknown/Multiple
TypeApplications |
Architecture: | Type of failure: Incorrect
Unknown/Multiple | error/warning at compile-time
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
This bug is reproducible on GHC 8.0.1, 8.0.2, 8.2, and HEAD.
{{{#!hs
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeInType #-}
{-# OPTIONS_GHC -Wunused-foralls #-}
module Bug where
import Data.Proxy
proxy :: forall k (a :: k). Proxy a
proxy = Proxy
data SomeProxy where
SomeProxy :: forall k (a :: k). Proxy a -> SomeProxy
someProxy :: forall k (a :: k). SomeProxy
someProxy = SomeProxy (proxy @k @a)
}}}
{{{
$ /opt/ghc/head/bin/ghci Bug.hs
GHCi, version 8.3.20170327: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug ( Bug.hs, interpreted )
Bug.hs:17:23: warning: [-Wunused-foralls]
Unused quantified type variable ‘(a :: k)’
In the type ‘forall k (a :: k). SomeProxy’
|
17 | someProxy :: forall k (a :: k). SomeProxy
| ^^^^^^^^
Ok, modules loaded: Bug.
}}}
But that `a` is used in `proxy @k @a`!
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13512>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list