[GHC] #10347: Spurious "unused constructor" warning with Coercible

#10347: Spurious "unused constructor" warning with Coercible -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- When I say {{{ {-# LANGUAGE RoleAnnotations #-} module Bug (N, twiddle) where import Data.Coerce newtype N a = MkN Int type role N representational twiddle :: N a -> N b twiddle = coerce }}} I get {{{ Bug.hs:7:15: warning: Defined but not used: data constructor ‘MkN’ }}} But the constructor ''is'' used, in order to do the coercion. The role annotation is to force GHC to use the constructor to do the coercion -- otherwise, it might not have. This bug exists in 7.10 and in HEAD. I will fix. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10347 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10347: Spurious "unused constructor" warning with Coercible -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Turns out this is harder to fix than I thought. The problem is that usage information for locally defined things is in `tcg_dus :: [DefUse]` in the `TcGblEnv`. Deep within the solver, there is no way to change this field, and threading the information back up to the top seems horrendous. It seems the only way forward is to change `tcg_dus` to be a `TcRef [DefUse]`, but that makes me a bit sad. Any ideas? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10347#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10347: Spurious "unused constructor" warning with Coercible -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): In the example how could you ever construct a value of type `N a` (other than bottom)? You might add: {{{ makeN :: Int -> N a makeN = N }}} and bingo you've used `N`. So actually the error message seems somewhat reasonable to me. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10347#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10347: Spurious "unused constructor" warning with Coercible -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Good point. Here's a revised test case: {{{ module T10347 (N, mkN) where import Data.Coerce newtype N a = MkN Int mkN :: Int -> N a mkN = coerce }}} Now you ''can'' make an `N a`, but the warning still appears. This is actually much simpler than the original test case. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10347#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10347: Spurious "unused constructor" warning with Coercible -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Meh. Good point. I think this might signal a re-evaluation of the whole `DefUse` thing, which is quite complicated to manage, and isn't paying its way. For top-level-bound things, something more like `tcg_used_rdrnames` (but for `Name`s) might work better. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10347#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10347: Spurious "unused constructor" warning with Coercible -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * owner: goldfire => Comment: In that case, I'm forgoing ownership of the ticket. Perhaps once my branch is merged, I'll have the energy to look at a redesign of the whole `DefUse` thing, but not now. In any case, this only happened while building a test case -- not in "real code" -- so I don't think it's too important. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10347#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10347: Spurious "unused constructor" warning with Coercible
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect | Unknown/Multiple
warning at compile-time | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#10347: Spurious "unused constructor" warning with Coercible -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): I actually had this test case sitting in my tree for a while. Thought I would push. I haven't looked at this ticket at all otherwise. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10347#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10347: Spurious "unused constructor" warning with Coercible -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | typecheck/should_compile/T10347 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * testcase: => typecheck/should_compile/T10347 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10347#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10347: Spurious "unused constructor" warning with Coercible
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: Incorrect | Test Case:
warning at compile-time | typecheck/should_compile/T10347
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#10347: Spurious "unused constructor" warning with Coercible -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | typecheck/should_compile/T10347 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * cc: dfeuer (added) Comment: One partial solution would be a pragma disabling the usage warning for a particular binding. {{{#!hs newtype N = N Int test :: N -> N test = ... {-# Ignore-Usage type N, N, test #-} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10347#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10347: Spurious "unused constructor" warning with Coercible -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | typecheck/should_compile/T10347 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): I ran into this issue in real code yesterday. We can now write {{{#!hs class (forall a b. Coercible a b => Coercible (f a) (f b)) => Representational f instance (forall a b. Coercible a b => Coercible (f a) (f b)) => Representational f }}} But to sort of simulate that in older versions, I used {{{#!hs data Skolem newtype Skolem' = Skolem' Skolem class Representational f instance (Coercible (f Skolem) (f Skolem')) => Representational f }}} GHC complained because the `Skolem'` data constructor isn't used directly. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10347#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10347: Spurious "unused constructor" warning with Coercible -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | typecheck/should_compile/T10347 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by -Jie-): We ran into the same issue in our project. Simplified version: {{{ module Test (test) where import Data.Coerce (coerce) newtype N = N Int data Test = Test N test :: Test test = Test $ coerce (0 :: Int) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10347#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10347: Spurious "unused constructor" warning with Coercible -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | typecheck/should_compile/T10347 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I wonder if you get an unused-import warning if you say {{{ import Foo( N( N ) ) where test :: Test test = Test $ coerce (0::Int) }}} That is, does the problem apply to imported newtype constructors too? I took at quick look at what to do. The obvious thing to do is * Make `tcg_dus` into a `TcRef` (like `tcg_keep` and `tcg_used_gres`) * Make the constraint solve add a use to `tcg_dus` when solving `Coercible` constraints. (We'd need to change the representation of `tcg_dus` from a list to an `OrdList` or something, else we'd bet inefficient appends.) * Move `reportUnusedNames` after the type checker. Standing back a bit, we carefully gather `tcg_dus :: [DefUse]`, were `type DefUse = (Maybe Defs, Uses)`. So from {{{ type S = Int type T = S -> R }}} we the `DefUse` pairs `(Just S, {})`, and `(Just T, {S,R})`. The idea is that if `T` is unused we can report `S` as unused too. A simpler alternative is simply to gather all the binders `{S,T}` and all the occurrences `{S,R}` and report things that are defined but not referred to. That would report `T` but not `S`. If you deleted `T` you'd get a new warning about `S`. But it's debatable whether reporting `S` unused is a feature or a bug. It certainly confusing -- you can see a reference to `S` -- and if the lack of a reference to `T` was a mistake, then the unused-S warning is simply distracting. So my thought is this: * Suppose instead of gathering `[DefUse]` we simply gather a `NameSet` of things that are referred to; and report as unused anything that it not referred to. That would be significantly simpler. The defs are the declarations themselves, of course. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10347#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC