[GHC] #13064: Incorrect redudant imports warning

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | 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: -------------------------------------+------------------------------------- With a simple package: issue.cabal: {{{ name: issue version: 0 cabal-version: >= 1.10 build-type: Simple library build-depends: base, binary, binary-orphans==0.1.5.2 exposed-modules: Issue }}} Issue.hs: {{{ {-# LANGUAGE DeriveGeneric #-} {-# OPTIONS_GHC -Wall #-} module Issue (T (..)) where import Prelude () import Data.Binary.Orphans import Data.Binary (Binary (..)) import GHC.Generics (Generic) import Data.Aeson (Value) data T = T Value deriving (Generic) instance Binary T }}} GHC 7.10.3 correctly reports: {{{ Issue.hs:7:1: Warning: The import of ‘Data.Binary’ is redundant except perhaps to import instances from ‘Data.Binary’ To import instances alone, use: import Data.Binary() }}} GHC 8.0.1 incorrectly (!!!) reports: {{{ Issue.hs:6:1: warning: [-Wunused-imports] The import of ‘Data.Binary.Orphans’ is redundant except perhaps to import instances from ‘Data.Binary.Orphans’ To import instances alone, use: import Data.Binary.Orphans( }}} but `Binary Value` instance is imported from `Data.Binary.Orphans`. --- In real life while compiling https://github.com/futurice/haskell-mega- repo/blob/93c3f111f39c973769c35725d90c9b8ef9a57de3/futurice- github/src/Futurice/GitHub.hs the `Data.Binary` redundant import isn't reported, as `Futurice.Prelude` exports other stuff, which is used. See https://gist.github.com/phadej/bb26df19c611260ab8f867729def39b9 for minimal imports reported with `-ddump-minimal-imports`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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 rwbarton): I'm afraid I'm lost. You say "but `Binary Value` instance is imported from `Data.Binary.Orphans`"; but the error message explicitly says {{{ except perhaps to import instances from ‘Data.Binary.Orphans’ }}} so I don't see a problem. In general given a set of imports that is redundant, there isn't a unique way to remove imports to eliminate the redundancy. For example if I import modules `A` and `B` which both export `f` and I use `f` but nothing else from either `A` or `B`, then either the import of `A` or of `B` can be removed, but not both. In such cases GHC has to make a choice about which import to report as redundant. In your example it seems that GHC's choice changed between versions, probably having to do with the fact that you mentioned `Binary` in an explicit import list. I'm pretty sure that if you reverse the order of your two `import Data.Binary` lines, GHC 7.10.3 will give the same error you are getting with GHC 8.0.1. In any case the solution is to add an empty import list as the error message suggests. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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 phadej): If I reverse `Data.Binary` and `Data.Binary.Orphans` imports the error messages stay exactly the same. What I see, is that GHC 8.0.1 doesn't follow the spec in https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/UnusedImports
- import Foo dominates import Foo(x). (You could also argue that the reverse should hold.) - Otherwise choose the textually first one.
`import Data.Binary.Orphans` should dominate `import Data.Binary (Binary (..))` when we check where from `Binary` is imported. Either commentary or implementation is incorrect. I suspect the latter. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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 rwbarton):
If I reverse `Data.Binary` and `Data.Binary.Orphans` imports the error messages stay exactly the same.
Even in GHC 7.10.3? If so, then doesn't 7.10.3 also violate that spec? Then again, that spec is 8 years old and the intended behavior may have changed in that time. Better to check the User's Guide. (I haven't checked myself to see whether it has anything to say about this, but I hope so--if not that's also a bug.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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 rwbarton): Sorry, my first two sentences are nonsense. I still would not go by that old wiki page, though. What does the User's Guide say? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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 phadej): https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/using- warnings.html#ghc-flag--Wunused-imports not much. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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 rwbarton): Well, that's not very helpful. But considering that the User's Guide does not document the exact heuristics used to select which imports are unused, the behavior of GHC seems to be correct here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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 phadej): That's unfortunate. But if it's not documented, I'd like to try to fix heuristics to be more of 7.10, does anyone have a pointers to where to look? The warnings really help refactoring with big (and constantly growing) company-prelude. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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 mpickering): The right function to look at is `warnUnusedImportDecls` in `RnNames`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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): Thanks for looking at this. The first thing to do is to work out the ''specification''. The current spec is indeed the one at [wiki:Commentary/Compiler/UnusedImports]. If you are happy with the spec, but the code does not implement it, then produce a small test case (preferably not depending on a complicated library) that demonstrates the problem. Then you are set to look for what is going wrong. Thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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 ezyang): (I also gave a new proposal for redundant imports at https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/RelaxedUnusedImpor... which is not implemented yet but might be worth looking at.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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 rwbarton): Sorry if I am being dense here. I still don't understand why you care ''which'' import is reported as redundant. If you are only importing a module for its instances, writing an empty import list is the standard way to express that explicitly. It seems like the reason has to do with the fact that `Data.Binary.Orphans` provides instances you want that are not provided by `Data.Binary`, while `Data.Binary` does not provide any instances you want that are not provided by `Data.Binary.Orphans`. In the case of a custom prelude, "want" might even just mean that you want to make them available to your importers. So, there is no way for GHC to divine your intent in general. It certainly doesn't seem like this distinction between the two modules is related to whether or not you provide a (nonempty) explicit import list. So if you change the heuristics to handle this case to your satisfaction, it will just break a symmetric case for someone else. All in all, it seems like a lot of effort to avoid typing `()`. The RelaxedUnusedImports proposal is rather different in intent, since there the goal is to make it easier to write warning-free code across a range of versions of dependencies, while this issue is not about whether to issue a warning, but which warning to issue. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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 phadej): I found even more minimal examples, they aren't tied to instances: {{{ % cat Next.hs import Control.Applicative import Prelude (IO, pure) main :: IO () main = pure () % cat Next2.hs import Control.Applicative import Prelude (IO, pure) main :: IO () main = () <$ pure () % $(ghc-select ghc-7.10.3) % ghc -Wall -fforce-recomp Next.hs [1 of 1] Compiling Main ( Next.hs, Next.o ) Next.hs:2:1: Warning: The import of ‘pure’ from module ‘Prelude’ is redundant Linking Next ... % ghc -Wall -fforce-recomp Next2.hs [1 of 1] Compiling Main ( Next2.hs, Next2.o ) Next2.hs:2:1: Warning: The import of ‘pure’ from module ‘Prelude’ is redundant Linking Next2 ... % $(ghc-select ghc-8.0.1) % ghc -Wall -fforce-recomp Next.hs [1 of 1] Compiling Main ( Next.hs, Next.o ) Next.hs:1:1: warning: [-Wunused-imports] The import of ‘Control.Applicative’ is redundant except perhaps to import instances from ‘Control.Applicative’ To import instances alone, use: import Control.Applicative() Linking Next ... % ghc -Wall -fforce-recomp Next2.hs [1 of 1] Compiling Main ( Next2.hs, Next2.o ) Linking Next2 ... }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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): Helpful example, thank you. Just for context, in comment:12, I guess `Control.Applicative` exports `pure` and `<$`. * So the use of `<$` needs `import Control.Applicative` * The use of `pure` could come from `import Prelude( IO, pure )` or from `import Control.Applicative`; but for some reason GHC 8 chooses the former, whereas the rules in wiki:Commentary/Compiler/UnusedImports says the latter. Is that your reasoning? Are you saying "I like the rules in wiki:Commentary/Compiler/UnusedImports, but they aren't being implemented", or are you saying "I'd like different rules"? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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 phadej): That's exactly my reasoning. And: I like the rules in [wiki:Commentary/Compiler/UnusedImports]. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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): Great. Next: would you like to peer at the code in `RnNames.warnUnusedImportDecls` to see what is going wrong? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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 phadej): I'll do that, not right now though. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: low | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: 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 dfeuer): * priority: normal => low * milestone: => 8.2.1 Comment: I'm setting a low priority for this, even though it's a regression. As Reid indicates, it doesn't affect whether there's a redundant import warning, or whether the warning is correct, but only precisely which import is reported as redundant. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #15393 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I have fixed this on `wip/T13064`; Ben will complete. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: core-libraries-committee@… (added) * milestone: => 8.8.1 Comment: I admit I'm a bit nervous about merging this. The fact that the new scheme results in so many warnings even in GHC's core libraries is deeply concerning. I suspect that this new scheme may break the guidance that the Core Libraries Committee (or, at very least, Ed Kmett) has long offered for dealing with additions to `Prelude`: adding a (seemingly redundant) import of `Prelude`. For instance, consider the case of the Semigroup/Monoid proposal (SMP), where `(<>)` was added to `Prelude`. Imagine that before SMP a user had a module with, {{{#!hs import Data.Semigroup (Semigroup, (<>)) squash :: Semigroup a => a -> a -> a squash = (<>) }}} However, post-SMP the import of `Data.Semigroup` is redundant, leading to a warning which would cause failures with `-Wall`. Of course, the user could drop the `import`, but only at the expense of compatibility with earlier GHC releases. One way around this is to guard the import with CPP, {{{#!hs #if MIN_VERSION_base(4,11,0) import Data.Semigroup (Semigroup, (<>)) #endif squash :: Semigroup a => a -> a -> a squash = (<>) }}} However, requiring this sort of refactoring stands in violation of the CLC's [[https://prime.haskell.org/wiki/Libraries/3-Release-Policy|Three Release Policy]] which states that no library change will cause `-Wall` failures that are avoidable only with CPP. This is why the CLC has instead recommended this solution instead: {{{#!hs import Data.Semigroup (Semigroup, (<>)) import Prelude squash :: Semigroup a => a -> a -> a squash = (<>) }}} Under the current redundancy check this throws no warnings (assuming something is used from `Prelude`). However, under the new scheme GHC deems the `Data.Semigroup` to be redundant. Moreover, under the new semantics I don't see any way to recover the previous level of compatibility short of CPP guards. Note that I'm not saying that either behavior is more correct; rather, I'm merely saying that a truly massive amount of code may be relying on the status quo and we should be very careful before making changes here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Well I'm entirely open to changing the rules. They are documented here: [wiki:Commentary/Compiler/UnusedImports]. But for some time GHC has claimed to follow the rules, but has simply failed to do so. And we have bug reports asking that we fix that. It's unfortunate that this `SemiGroup` business has (inadvertently) relied on this bug in GHC. The truth is that the warning is spot-on: the import is redundant. What rules would we like instead? Perhaps we want to warn about some redundant imports bu not all? But which redundant imports should not be warned about? The obvious thing is to make a special case for the Prelude, since it is implicitly imported. For example * Never warn about an import declaration (or import item) that is unnecessary because of the implicit Prelude import. For example {{{ import Data.List( null ) -- Already imported by Prelude }}} Views? The status quo is bad; see #15393 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by phadej): Thanks Simon for doing this! Ben: I want to point out, that this is a regression between 7.10 and 8.0. The change to less strict version as is currently where done pre-GHC- proposal process, but it really should been scrutinized in something like that. For AMP, the 7.10.3 (which works correctly) warns about {{{ {-# OPTIONS_GHC -Wall #-} import Control.Applicative (Applicative (..), (<$>)) import Prelude mult :: Applicative f => f a -> f b -> f (a, b) mult x y = (,) <$> x <*> y }}} but not about {{{ {-# OPTIONS_GHC -Wall #-} import Control.Applicative import Prelude mult :: Applicative f => f a -> f b -> f (a, b) mult x y = (,) <$> x <*> y }}} Similarly, GHC-8.4.3 doesn't warn, but the wip/T13064 does about: {{{ {-# OPTIONS_GHC -Wall #-} import Data.Semigroup (Semigroup, (<>)) import Prelude squash :: Semigroup a => a -> a -> a squash = (<>) }}} However, neither warns about (open imports) {{{ {-# OPTIONS_GHC -Wall #-} import Data.Semigroup import Prelude squash :: Semigroup a => a -> a -> a squash = (<>) }}} or (at least single qualified use) {{{ {-# OPTIONS_GHC -Wall #-} import Data.Semigroup (Semigroup (..)) import Prelude squash :: Data.Semigroup.Semigroup a => a -> a -> a squash = (<>) }}} S 3-release-policy is easily satisfied. You'll need to do "something" in your code, but it's not "use CPP". I hope that CLC agrees. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): **Replying to comment:24:**
Ben: I want to point out, that this is a regression between 7.10 and 8.0.
Right, I don't dispute that that there is a regression here; rather, I want to point out that there may be a significant amount of code that (unfortunately) now relies on that regression.
or (at least single qualified use) {{{#!hs {-# OPTIONS_GHC -Wall #-} import Data.Semigroup (Semigroup (..)) import Prelude
squash :: Data.Semigroup.Semigroup a => a -> a -> a squash = (<>) }}}
Right; this is a reasonable option, albeit a bit ugly. However, it seems like this should serve as motivation to consider what mechanisms we could add to GHC to allow us to accomodate this sort of API reshuffling more easily and with fewer hacks in the future. For instance, wiki:Design/LocalWarningPragmas. **Replying to comment:23**
Never warn about an import declaration (or import item) that is unnecessary because of the implicit `Prelude` import. For example
I suppose this is a possibility, although it seems to be me that we should rather try to introduce a mechanism to allow the user to state explicitly what they mean. That is: the import is known to be redundant but added for compatibility's sake. This could either be a general mechanism (e.g. wiki:Design/LocalWarningPragmas) or something more specifically designed to address import redundancy. (e.g. a `{-# USED #-}` pragma which could be attached to an import to silence the redundancy checker), -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

**Replying to comment:24:**
I suppose this is a possibility, although it seems to be me that we should rather try to introduce a mechanism to allow the user to state explicitly what they mean. That is: the import is known to be redundant but added for compatibility's sake. This could either be a general mechanism (e.g. wiki:Design/LocalWarningPragmas) or something more specifically designed to address import redundancy. (e.g. a `{-# USED #-}`
#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by phadej): Replying to [comment:25 bgamari]: pragma which could be attached to an import to silence the redundancy checker), We shouldn't need to go through GHC-proposal process for a bug fix. We should fix a bug, and then the interested people will either polish https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/RelaxedUnusedImpor... into a proposal, or propose some other way around (e.g. more granular warning toggles, then per-module). I'm for sure **implicitly** depend on this bug behavior for warning free builds, but I don't like it. For example: the tool `weeder` (to purge dependencies) isn't as useful now, as one might have an import which isn't necessary, but it retains the dependency. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * cc: ekmett@… (added) Comment: I had forgotten all about [wiki:Commentary/Compiler/RelaxedUnusedImports]. Thanks: you are right to point to it as a possible design. We quite often fix a bug that forces libraries to change in some minor way; library authors are (perhaps reluctantly) used to this. In this case, the change affects only warnings, perhaps the least bad way to break a library. (Worse ways are: the library is now type incorrect; or (worse still) compiles cleanly but gives the wrong answers.) I think the awkward thing here is that library authors like to produce an updated version of the library that will work with many versions of GHC. For that they resort to CPP. Thus in `containers:Data.Map.Internal.hs` we see {{{ #if __GLASGOW_HASKELL__ >= 708 import qualified GHC.Exts as GHCExts #endif }}} The [https://prime.haskell.org/wiki/Libraries/3-Release-Policy three release policy says] ''Changes '''to basic libraries''' are planned and implemented so that, at any time, it is possible to write code that works with the latest three releases of GHC and base, without resorting to CPP, and without causing warnings even when compiled with -Wall.'' Note "to basic libraries". I don't see how it's possible to apply this policy to the compiler itself. Suppose a library compiles with GHC 12.0, and we want to make a change in the warnings the compiler produces. We could defer the change to 12.6; but then the author could just apply the policy starting at 12.6, so we'd have to defer to 12.12, and so on. I feel I must be missing something. Also as comment:24 points out, there is a non-CPP way to adapt too. Let's see what the CLC (cc'd) says. I'm adding Edward to cc as well. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Dear Core Libraries Committee, and Edward. Could you give an opinion on the change I propose in this ticket? Thanks -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:28 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I'll chime in one opinion as a member of the CLC. If I'm reading comment:24 correctly, then there still exists a solution (two solutions, even, depending on how verbose you want to be) to avoiding redundant imports warnings that is compliant with the three-release policy. Moreover, the less verbose of these solutions: {{{#!hs {-# OPTIONS_GHC -Wall #-} import Data.Semigroup import Prelude squash :: Semigroup a => a -> a -> a squash = (<>) foo :: Int foo = 42 }}} Isn't terribly different from the usual advice that we give for avoiding redundant imports on old GHCs, so it wouldn't be //too// far of a break from convention to espouse this advice instead. The only thing we'd have to be conscious of is that code like this, where explicit imports are used: {{{#!hs {-# OPTIONS_GHC -Wall #-} import Data.Semigroup (Semigroup, (<>)) import Prelude squash :: Semigroup a => a -> a -> a squash = (<>) foo :: Int foo = 42 }}} Will now start emitting warnings, so there will likely need to be some migration to mitigate these warnings once they start popping up in the wild. The question is: exactly how much migration can we expect? I'm unsure of what the answer to this question is, so to help get an approximate answer, I'm going to build the `wip/T13064` branch and try building a slew of Hackage libraries with it in order to see which new warnings appear. Regardless of what this experiment produces, I still lean towards the side of applying this change, since it fixes an outright bug. It helps that one can migrate any code to adapt to this new warning scheme without too much trouble as well. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:29 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ekmett): I'm leaning on the side of applying this change and my reasoning pretty closely follows Ryan's. Between the ability to explicitly qualify use in the presence of a conflict and the fact that the common "open" import of all things in a module still work out of the box, I'm pretty happy to say we should fix the bug and change programming styles slightly. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:30 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by andrewthad): As a member of the CLC, I'm in favor of fixing GHC so that it conforms to the spec. I agree with Ryan and Edward's reasoning on this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:31 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Thanks both. Edward, if you could, over the next week or two, lead the CLC to make a decision -- or take an executive decision yourself -- then we can act. Thanks! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:32 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I don't think this patch should be merged if there is any risk of destabilising the branch. This has already happened once this release cycle with the `MonadFail` desugaring patch being merged very late in the day. If this causes any additional warnings then proactive package maintainers are going to have to cut a third new release of their package. The release is over a month overdue and still have a number of high priority bugs to fix #15544 and #15541 in particular. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:33 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): To be clear, I'm proposing that this fix be introduced in 8.8 and shouldn't be merged into 8.6. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:34 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Indeed: there is no suggestion of putting this in 8.6! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:35 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): To follow up on my proposed experiment (in comment:29), I built about 143 commonly used Hackage libraries using the `wip/T13064` GHC branch. Of those 143, I noticed new warnings being emitted in 31 of them (~22%): {{{ - adjunctions-4.4 - aeson-1.4.0.0 - ansi-wl-pprint-0.6.8.2 - asn1-encoding-0.9.5 - async-2.2.1 - attoparsec-0.13.2.2 - blaze-builder-0.4.1.0 - cassava-0.5.1.0 - conduit-1.3.0.3 - cookie-0.4.4 - foundation-0.0.21 - Glob-0.9.2 - haskell-src-exts-1.20.2 - hspec-core-2.5.6 - lens-4.17 - math-functions-0.3.0.2 - memory-0.14.16 - microstache-1.0.1.1 - mono-traversable-1.0.9.0 - network-2.8.0.0 - primitive-0.6.4.0 - resourcet-1.2.1 - scientific-0.3.6.2 - tasty-1.1.0.3 - th-orphans-0.13.6 - unordered-containers-0.2.9.0 - uuid-types-1.0.3 - x509-1.7.4 - x509-store-1.6.6 - x509-system-1.6.6 - yaml-0.10.1.1 }}} I still advocate adopting this change, but it is worth noting that a non- trivial number of existing libraries will need to be updated in order to accommodate the new warnings. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:36 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ekmett): The CLC has a pretty clear consensus on making this happen. Let's do it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:37 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Alright, is that to say we want this in 8.8? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:38 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: low | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I think yes, put it in 8.8. Why would 8.10 be any better? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:39 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: low => high Comment: Oh, I don't think 8.10 would be any better. I was just clarifying. We will need to take a bit of time to bring the core libraries up to date but otherwise I see no reason why this wouldn't be feasible. Bumping priority to ensure that this happens. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:40 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: davide Type: bug | Status: new Priority: high | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => davide Comment: David, do you think you could push the necessary changes to the core libraries and merge `wip/T13064`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:41 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: davide Type: bug | Status: new Priority: high | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by davide): Absolutely. I'll post an update on Monday, but it seems fairly straightforward. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:42 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: davide Type: bug | Status: new Priority: high | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by davide): I've submitted some PRs to fix the impending unused import warnings: * https://github.com/haskell/cabal/pull/5673 * https://github.com/kolmodin/binary/pull/159 * https://github.com/haskell/bytestring/pull/168 * https://github.com/haskell/containers/pull/576 * https://github.com/haskell/text/pull/240 I've also added a new ghc patch here: https://phabricator.haskell.org/D5312 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:43 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: davide Type: bug | Status: new Priority: high | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by davide: Old description:
With a simple package:
issue.cabal: {{{ name: issue version: 0 cabal-version: >= 1.10 build-type: Simple
library build-depends: base, binary, binary-orphans==0.1.5.2 exposed-modules: Issue }}}
Issue.hs: {{{ {-# LANGUAGE DeriveGeneric #-} {-# OPTIONS_GHC -Wall #-} module Issue (T (..)) where
import Prelude () import Data.Binary.Orphans import Data.Binary (Binary (..)) import GHC.Generics (Generic) import Data.Aeson (Value)
data T = T Value deriving (Generic)
instance Binary T }}}
GHC 7.10.3 correctly reports: {{{ Issue.hs:7:1: Warning: The import of ‘Data.Binary’ is redundant except perhaps to import instances from ‘Data.Binary’ To import instances alone, use: import Data.Binary() }}}
GHC 8.0.1 incorrectly (!!!) reports:
{{{ Issue.hs:6:1: warning: [-Wunused-imports] The import of ‘Data.Binary.Orphans’ is redundant except perhaps to import instances from ‘Data.Binary.Orphans’ To import instances alone, use: import Data.Binary.Orphans( }}}
but `Binary Value` instance is imported from `Data.Binary.Orphans`.
---
In real life while compiling https://github.com/futurice/haskell-mega- repo/blob/93c3f111f39c973769c35725d90c9b8ef9a57de3/futurice- github/src/Futurice/GitHub.hs the `Data.Binary` redundant import isn't reported, as `Futurice.Prelude` exports other stuff, which is used. See https://gist.github.com/phadej/bb26df19c611260ab8f867729def39b9 for minimal imports reported with `-ddump-minimal-imports`.
New description: With a simple package: issue.cabal: {{{ name: issue version: 0 cabal-version: >= 1.10 build-type: Simple library build-depends: base, binary, binary-orphans==0.1.5.2 exposed-modules: Issue }}} Issue.hs: {{{ {-# LANGUAGE DeriveGeneric #-} {-# OPTIONS_GHC -Wall #-} module Issue (T (..)) where import Prelude () import Data.Binary.Orphans import Data.Binary (Binary (..)) import GHC.Generics (Generic) import Data.Aeson (Value) data T = T Value deriving (Generic) instance Binary T }}} GHC 7.10.3 correctly reports: {{{ Issue.hs:7:1: Warning: The import of ‘Data.Binary’ is redundant except perhaps to import instances from ‘Data.Binary’ To import instances alone, use: import Data.Binary() }}} GHC 8.0.1 incorrectly (!!!) reports: {{{ Issue.hs:6:1: warning: [-Wunused-imports] The import of ‘Data.Binary.Orphans’ is redundant except perhaps to import instances from ‘Data.Binary.Orphans’ To import instances alone, use: import Data.Binary.Orphans( }}} but `Binary Value` instance is imported from `Data.Binary.Orphans`. --- In real life while compiling https://github.com/futurice/haskell-mega- repo/blob/93c3f111f39c973769c35725d90c9b8ef9a57de3/futurice- github/src/Futurice/GitHub.hs the `Data.Binary` redundant import isn't reported, as `Futurice.Prelude` exports other stuff, which is used. See https://gist.github.com/phadej/bb26df19c611260ab8f867729def39b9 for minimal imports reported with `-ddump-minimal-imports`. ## Status I've submitted some PRs to fix the impending unused import warnings: * https://github.com/haskell/cabal/pull/5673 * https://github.com/kolmodin/binary/pull/159 * MERGED https://github.com/haskell/bytestring/pull/168 * https://github.com/haskell/containers/pull/576 * MERGED https://github.com/haskell/text/pull/240 I've also added a new ghc patch here: * https://phabricator.haskell.org/D5312 -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:44 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: davide Type: bug | Status: new Priority: high | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by davide: Old description:
With a simple package:
issue.cabal: {{{ name: issue version: 0 cabal-version: >= 1.10 build-type: Simple
library build-depends: base, binary, binary-orphans==0.1.5.2 exposed-modules: Issue }}}
Issue.hs: {{{ {-# LANGUAGE DeriveGeneric #-} {-# OPTIONS_GHC -Wall #-} module Issue (T (..)) where
import Prelude () import Data.Binary.Orphans import Data.Binary (Binary (..)) import GHC.Generics (Generic) import Data.Aeson (Value)
data T = T Value deriving (Generic)
instance Binary T }}}
GHC 7.10.3 correctly reports: {{{ Issue.hs:7:1: Warning: The import of ‘Data.Binary’ is redundant except perhaps to import instances from ‘Data.Binary’ To import instances alone, use: import Data.Binary() }}}
GHC 8.0.1 incorrectly (!!!) reports:
{{{ Issue.hs:6:1: warning: [-Wunused-imports] The import of ‘Data.Binary.Orphans’ is redundant except perhaps to import instances from ‘Data.Binary.Orphans’ To import instances alone, use: import Data.Binary.Orphans( }}}
but `Binary Value` instance is imported from `Data.Binary.Orphans`.
---
In real life while compiling https://github.com/futurice/haskell-mega- repo/blob/93c3f111f39c973769c35725d90c9b8ef9a57de3/futurice- github/src/Futurice/GitHub.hs the `Data.Binary` redundant import isn't reported, as `Futurice.Prelude` exports other stuff, which is used. See https://gist.github.com/phadej/bb26df19c611260ab8f867729def39b9 for minimal imports reported with `-ddump-minimal-imports`.
## Status
I've submitted some PRs to fix the impending unused import warnings:
* https://github.com/haskell/cabal/pull/5673 * https://github.com/kolmodin/binary/pull/159 * MERGED https://github.com/haskell/bytestring/pull/168 * https://github.com/haskell/containers/pull/576 * MERGED https://github.com/haskell/text/pull/240
I've also added a new ghc patch here: * https://phabricator.haskell.org/D5312
New description: With a simple package: issue.cabal: {{{ name: issue version: 0 cabal-version: >= 1.10 build-type: Simple library build-depends: base, binary, binary-orphans==0.1.5.2 exposed-modules: Issue }}} Issue.hs: {{{ {-# LANGUAGE DeriveGeneric #-} {-# OPTIONS_GHC -Wall #-} module Issue (T (..)) where import Prelude () import Data.Binary.Orphans import Data.Binary (Binary (..)) import GHC.Generics (Generic) import Data.Aeson (Value) data T = T Value deriving (Generic) instance Binary T }}} GHC 7.10.3 correctly reports: {{{ Issue.hs:7:1: Warning: The import of ‘Data.Binary’ is redundant except perhaps to import instances from ‘Data.Binary’ To import instances alone, use: import Data.Binary() }}} GHC 8.0.1 incorrectly (!!!) reports: {{{ Issue.hs:6:1: warning: [-Wunused-imports] The import of ‘Data.Binary.Orphans’ is redundant except perhaps to import instances from ‘Data.Binary.Orphans’ To import instances alone, use: import Data.Binary.Orphans( }}} but `Binary Value` instance is imported from `Data.Binary.Orphans`. --- In real life while compiling https://github.com/futurice/haskell-mega- repo/blob/93c3f111f39c973769c35725d90c9b8ef9a57de3/futurice- github/src/Futurice/GitHub.hs the `Data.Binary` redundant import isn't reported, as `Futurice.Prelude` exports other stuff, which is used. See https://gist.github.com/phadej/bb26df19c611260ab8f867729def39b9 for minimal imports reported with `-ddump-minimal-imports`. ## Status I've submitted some PRs to fix the impending unused import warnings: * MERGED https://github.com/haskell/cabal/pull/5673 * https://github.com/kolmodin/binary/pull/159 * MERGED https://github.com/haskell/bytestring/pull/168 * https://github.com/haskell/containers/pull/576 * MERGED https://github.com/haskell/text/pull/240 I've also added a new ghc patch here: * https://phabricator.haskell.org/D5312 -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:45 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: davide Type: bug | Status: new Priority: high | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Old description:
With a simple package:
issue.cabal: {{{ name: issue version: 0 cabal-version: >= 1.10 build-type: Simple
library build-depends: base, binary, binary-orphans==0.1.5.2 exposed-modules: Issue }}}
Issue.hs: {{{ {-# LANGUAGE DeriveGeneric #-} {-# OPTIONS_GHC -Wall #-} module Issue (T (..)) where
import Prelude () import Data.Binary.Orphans import Data.Binary (Binary (..)) import GHC.Generics (Generic) import Data.Aeson (Value)
data T = T Value deriving (Generic)
instance Binary T }}}
GHC 7.10.3 correctly reports: {{{ Issue.hs:7:1: Warning: The import of ‘Data.Binary’ is redundant except perhaps to import instances from ‘Data.Binary’ To import instances alone, use: import Data.Binary() }}}
GHC 8.0.1 incorrectly (!!!) reports:
{{{ Issue.hs:6:1: warning: [-Wunused-imports] The import of ‘Data.Binary.Orphans’ is redundant except perhaps to import instances from ‘Data.Binary.Orphans’ To import instances alone, use: import Data.Binary.Orphans( }}}
but `Binary Value` instance is imported from `Data.Binary.Orphans`.
---
In real life while compiling https://github.com/futurice/haskell-mega- repo/blob/93c3f111f39c973769c35725d90c9b8ef9a57de3/futurice- github/src/Futurice/GitHub.hs the `Data.Binary` redundant import isn't reported, as `Futurice.Prelude` exports other stuff, which is used. See https://gist.github.com/phadej/bb26df19c611260ab8f867729def39b9 for minimal imports reported with `-ddump-minimal-imports`.
## Status
I've submitted some PRs to fix the impending unused import warnings:
* MERGED https://github.com/haskell/cabal/pull/5673 * https://github.com/kolmodin/binary/pull/159 * MERGED https://github.com/haskell/bytestring/pull/168 * https://github.com/haskell/containers/pull/576 * MERGED https://github.com/haskell/text/pull/240
I've also added a new ghc patch here: * https://phabricator.haskell.org/D5312
New description: With a simple package: issue.cabal: {{{ name: issue version: 0 cabal-version: >= 1.10 build-type: Simple library build-depends: base, binary, binary-orphans==0.1.5.2 exposed-modules: Issue }}} Issue.hs: {{{ {-# LANGUAGE DeriveGeneric #-} {-# OPTIONS_GHC -Wall #-} module Issue (T (..)) where import Prelude () import Data.Binary.Orphans import Data.Binary (Binary (..)) import GHC.Generics (Generic) import Data.Aeson (Value) data T = T Value deriving (Generic) instance Binary T }}} GHC 7.10.3 correctly reports: {{{ Issue.hs:7:1: Warning: The import of ‘Data.Binary’ is redundant except perhaps to import instances from ‘Data.Binary’ To import instances alone, use: import Data.Binary() }}} GHC 8.0.1 incorrectly (!!!) reports: {{{ Issue.hs:6:1: warning: [-Wunused-imports] The import of ‘Data.Binary.Orphans’ is redundant except perhaps to import instances from ‘Data.Binary.Orphans’ To import instances alone, use: import Data.Binary.Orphans( }}} but `Binary Value` instance is imported from `Data.Binary.Orphans`. --- In real life while compiling https://github.com/futurice/haskell-mega- repo/blob/93c3f111f39c973769c35725d90c9b8ef9a57de3/futurice- github/src/Futurice/GitHub.hs the `Data.Binary` redundant import isn't reported, as `Futurice.Prelude` exports other stuff, which is used. See https://gist.github.com/phadej/bb26df19c611260ab8f867729def39b9 for minimal imports reported with `-ddump-minimal-imports`. ## Status I've submitted some PRs to fix the impending unused import warnings: * MERGED https://github.com/haskell/cabal/pull/5673 * https://github.com/kolmodin/binary/pull/159 * MERGED https://github.com/haskell/bytestring/pull/168 * MERGED https://github.com/haskell/containers/pull/576 * MERGED https://github.com/haskell/text/pull/240 I've also added a new ghc patch here: * https://phabricator.haskell.org/D5312 -- Comment (by davide): Just waiting on the [https://github.com/kolmodin/binary/pull/159 binary PR] to be merged, then I'll update the ghc patch and we'll be on our way. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:46 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: davide Type: bug | Status: new Priority: high | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): D5367 Wiki Page: | -------------------------------------+------------------------------------- Changes (by davide): * differential: => D5367 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:47 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: davide Type: bug | Status: new Priority: high | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): D5312 Wiki Page: | -------------------------------------+------------------------------------- Changes (by davide): * differential: D5367 => D5312 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:48 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: davide Type: bug | Status: new Priority: high | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Phab:D5312 Wiki Page: | -------------------------------------+------------------------------------- Changes (by potato44): * differential: D5312 => Phab:D5312 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:49 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning
-------------------------------------+-------------------------------------
Reporter: phadej | Owner: davide
Type: bug | Status: new
Priority: high | Milestone: 8.8.1
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect | Unknown/Multiple
error/warning at compile-time | Test Case:
Blocked By: | Blocking:
Related Tickets: #15393 | Differential Rev(s): Phab:D5312
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: davide Type: bug | Status: closed Priority: high | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Phab:D5312 Wiki Page: | -------------------------------------+------------------------------------- Changes (by davide): * status: new => closed * resolution: => fixed Old description:
With a simple package:
issue.cabal: {{{ name: issue version: 0 cabal-version: >= 1.10 build-type: Simple
library build-depends: base, binary, binary-orphans==0.1.5.2 exposed-modules: Issue }}}
Issue.hs: {{{ {-# LANGUAGE DeriveGeneric #-} {-# OPTIONS_GHC -Wall #-} module Issue (T (..)) where
import Prelude () import Data.Binary.Orphans import Data.Binary (Binary (..)) import GHC.Generics (Generic) import Data.Aeson (Value)
data T = T Value deriving (Generic)
instance Binary T }}}
GHC 7.10.3 correctly reports: {{{ Issue.hs:7:1: Warning: The import of ‘Data.Binary’ is redundant except perhaps to import instances from ‘Data.Binary’ To import instances alone, use: import Data.Binary() }}}
GHC 8.0.1 incorrectly (!!!) reports:
{{{ Issue.hs:6:1: warning: [-Wunused-imports] The import of ‘Data.Binary.Orphans’ is redundant except perhaps to import instances from ‘Data.Binary.Orphans’ To import instances alone, use: import Data.Binary.Orphans( }}}
but `Binary Value` instance is imported from `Data.Binary.Orphans`.
---
In real life while compiling https://github.com/futurice/haskell-mega- repo/blob/93c3f111f39c973769c35725d90c9b8ef9a57de3/futurice- github/src/Futurice/GitHub.hs the `Data.Binary` redundant import isn't reported, as `Futurice.Prelude` exports other stuff, which is used. See https://gist.github.com/phadej/bb26df19c611260ab8f867729def39b9 for minimal imports reported with `-ddump-minimal-imports`.
## Status
I've submitted some PRs to fix the impending unused import warnings:
* MERGED https://github.com/haskell/cabal/pull/5673 * https://github.com/kolmodin/binary/pull/159 * MERGED https://github.com/haskell/bytestring/pull/168 * MERGED https://github.com/haskell/containers/pull/576 * MERGED https://github.com/haskell/text/pull/240
I've also added a new ghc patch here: * https://phabricator.haskell.org/D5312
New description: With a simple package: issue.cabal: {{{ name: issue version: 0 cabal-version: >= 1.10 build-type: Simple library build-depends: base, binary, binary-orphans==0.1.5.2 exposed-modules: Issue }}} Issue.hs: {{{ {-# LANGUAGE DeriveGeneric #-} {-# OPTIONS_GHC -Wall #-} module Issue (T (..)) where import Prelude () import Data.Binary.Orphans import Data.Binary (Binary (..)) import GHC.Generics (Generic) import Data.Aeson (Value) data T = T Value deriving (Generic) instance Binary T }}} GHC 7.10.3 correctly reports: {{{ Issue.hs:7:1: Warning: The import of ‘Data.Binary’ is redundant except perhaps to import instances from ‘Data.Binary’ To import instances alone, use: import Data.Binary() }}} GHC 8.0.1 incorrectly (!!!) reports: {{{ Issue.hs:6:1: warning: [-Wunused-imports] The import of ‘Data.Binary.Orphans’ is redundant except perhaps to import instances from ‘Data.Binary.Orphans’ To import instances alone, use: import Data.Binary.Orphans( }}} but `Binary Value` instance is imported from `Data.Binary.Orphans`. --- In real life while compiling https://github.com/futurice/haskell-mega- repo/blob/93c3f111f39c973769c35725d90c9b8ef9a57de3/futurice- github/src/Futurice/GitHub.hs the `Data.Binary` redundant import isn't reported, as `Futurice.Prelude` exports other stuff, which is used. See https://gist.github.com/phadej/bb26df19c611260ab8f867729def39b9 for minimal imports reported with `-ddump-minimal-imports`. ## Status I've submitted some PRs to fix the impending unused import warnings: * MERGED https://github.com/haskell/cabal/pull/5673 * MERGED https://github.com/kolmodin/binary/pull/159 * MERGED https://github.com/haskell/bytestring/pull/168 * MERGED https://github.com/haskell/containers/pull/576 * MERGED https://github.com/haskell/text/pull/240 I've also added a new ghc patch here: * MERGED https://phabricator.haskell.org/D5312 -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:51 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: davide Type: bug | Status: closed Priority: high | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Phab:D5312 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Can someone amend wiki:Migration/8.8 with information about this change? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:52 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13064: Incorrect redudant imports warning -------------------------------------+------------------------------------- Reporter: phadej | Owner: davide Type: bug | Status: closed Priority: high | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #15393 | Differential Rev(s): Phab:D5312 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I've added some text to the 8.8 Migration Guide in wiki:Migration/8.8?version=7. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13064#comment:53 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC