[GHC] #13064: Incorrect redudant imports warning

GHC ghc-devs at haskell.org
Wed Jan 4 12:28:11 UTC 2017


#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


More information about the ghc-tickets mailing list