[GHC] #13512: GHC incorrectly warns that a variable used in a type application is unused

#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

#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 (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications, newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * keywords: TypeApplications => TypeApplications, newcomer -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13512#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications, newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Ugh, yes, quite right. To fix this the renamer needs to propagate usages of type variables in a binding to their binding sites in the corresponding type signature. That is somewhat fiddly,and would require some refactoring in `RnBinds.rnValBindsRHS`. Volunteers welcome! Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13512#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications, newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Similarly, using a scoped type variable in a type annotation doesn't count as a use: {{{#!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 :: Proxy a) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13512#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: TypeApplications, newcomer => TypeApplications Comment: By the way, at one point I looked into how one might fix this bug, but I didn't get very far. There's chicken-and-egg problem: the `Unused quantified type variable` analysis (and subsequent warning) are done entirely within `bindLHsTyVarBndrs`, which is called from `rnValBindsLHS`. However, to account for uses of type variables from type annotations or visible type applications, we'd need the results of `rnValBindsRHS`, but this must be run //after// `rnValBindsLHS`! This leads me to believe that either: * This `Unused quantified type variable` check shouldn't belong in `bindLHsTyVarBndrs`. * We need to somehow make `bindLHsTyVarBndrs` aware of function RHSes as well for warning purposes. Either way, I don't think is quite a newcomer bug :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13512#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ulysses4ever): @RyanGlScott How did you trace usage of `bindLHsTyVarBndrs` to `rnValBindsLHS`? I was only able to trace it to `rnValBindsRHS` as @simonpj told: {{{ -- RnTypes.hs warnUnusedForAll ← bindLHsTyVarBndrs ← rnHsTyKi ← rnLHsType ← rnHsSigType ← -- RnBinds.hs renameSig ← rnValBindsRHS }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13512#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Ah, you're right, it is in fact `rnValBindsRHS` that handles the renaming of function type signatures, not `rnValBindsLHS`. My mistake. But my point about there being a chicken-and-egg problem is still relevant, I believe. Here is the [http://git.haskell.org/ghc.git/blob/14457cf6a50f708eecece8f286f08687791d51f7... current definition] of `rnValBindsRHS`: {{{#!hs rnValBindsRHS :: HsSigCtxt -> HsValBindsLR GhcRn GhcPs -> RnM (HsValBinds GhcRn, DefUses) rnValBindsRHS ctxt (ValBindsIn mbinds sigs) = do { (sigs', sig_fvs) <- renameSigs ctxt sigs ; binds_w_dus <- mapBagM (rnLBind (mkSigTvFn sigs')) mbinds ; let !(anal_binds, anal_dus) = depAnalBinds binds_w_dus ; let patsyn_fvs = foldr (unionNameSet . psb_fvs) emptyNameSet $ getPatSynBinds anal_binds valbind'_dus = anal_dus `plusDU` usesOnly sig_fvs `plusDU` usesOnly patsyn_fvs ; return (ValBindsOut anal_binds sigs', valbind'_dus) } rnValBindsRHS _ b = pprPanic "rnValBindsRHS" (ppr b) }}} Notice that the call to `renameSigs` (in which all `Unused quantified type variable` warnings are emitted) occurs before the call to `rnLBind` (which would handle, e.g., `SomeProxy (proxy @k @a)`). Moreover, this has to be the case, since the result of `renameSigs` is fed into `rnLBind`. This makes me believe that the `Unused quantified type variable` analysis needs to be moved out of `bindLHsTyVarBndrs` and somewhere that can take into account the results of `rnValBindsRHS`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13512#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ulysses4ever): * cc: ulysses4ever (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13512#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13512: GHC incorrectly warns that a variable used in a type application is unused -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: sighingnow Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sighingnow): * owner: (none) => sighingnow -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13512#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sighingnow): * owner: sighingnow => (none) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13512#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC