[GHC] #10890: Incorrect redundant import warning for type classes

GHC ghc-devs at haskell.org
Thu Sep 17 15:43:19 UTC 2015


#10890: Incorrect redundant import warning for type classes
-------------------------------------+-------------------------------------
        Reporter:  quchen            |                   Owner:
            Type:  bug               |                  Status:  new
        Priority:  normal            |               Milestone:  8.0.1
       Component:  Compiler          |                 Version:  7.10.2
      Resolution:                    |                Keywords:
Operating System:  Unknown/Multiple  |            Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |               Test Case:
      Blocked By:                    |                Blocking:
 Related Tickets:                    |  Differential Revisions:
-------------------------------------+-------------------------------------
Description changed by quchen:

Old description:

> Given the three files below, the import marked with (!!!) is reported as
> redundant. Upon deleting it, GHC reports that "has" is not a visible
> class method of BClass.
>
> This came up in the context of the MFP (#10751), with the correspondences
> Base<->Control.Monad, Extends<->Control.Monad.Fail. We would like to have
> Control.Monad re-export Control.Monad.Fail.MonadFail without its
> (clashing) member "fail" for the time being. For future compatibility,
> some modules should implement MonadFail right now, requiring us to import
> Control.Monad.Fail explicitly in order to write an instance. Said
> procedure leads to the described import warning, which breaks the
> validation script for example.
>
> {{{#!hs
> -- Base.hs
> module Base (AClass(..), BClass()) where
>
> import Extends (BClass())
>
> class AClass a where
>     has :: a
> }}}
>
> {{{#!hs
> -- Extends.hs
> module Extends where
>
> class BClass b where
>     has :: b
> }}}
>
> {{{#!hs
> -- UseSite.hs
> module UseSite where
>
> import Base
> import Extends -- (!!!)
>
> data Bar = Bar
>
> instance AClass Bar where
>     has = Bar
>
> instance BClass Bar where
>     has = Bar
> }}}

New description:

 Given the three files below, the import marked with (!!!) is reported as
 redundant. Upon deleting it, GHC reports that "has" is not a visible class
 method of BClass.

 This came up in the context of the MFP (#10751), with the correspondences
 Base<->Control.Monad, Extends<->Control.Monad.Fail. We would like to have
 Control.Monad re-export Control.Monad.Fail.MonadFail without its
 (clashing) member "fail" for the time being. For future compatibility,
 some modules should implement MonadFail right now, requiring us to import
 Control.Monad.Fail explicitly in order to write an instance. Said
 procedure leads to the described import warning, which breaks the
 validation script for example.

 {{{#!hs
 -- Base.hs
 module Base (AClass(..), BClass()) where

 import Extends (BClass())

 class AClass a where
     has :: a
 }}}

 {{{#!hs
 -- Extends.hs
 module Extends where

 class BClass b where
     has :: b
 }}}

 {{{#!hs
 -- UseSite.hs
 module UseSite where

 import Base
 import Extends -- (!!!)

 data Bar = Bar

 instance AClass Bar where
     has = Bar

 instance BClass Bar where
     has = Bar
 }}}

 We either get

 {{{
 UseSite.hs:12:5: error:
     ‘has’ is not a (visible) method of class ‘BClass’
 }}}

 or

 {{{
 UseSite.hs:4:1: warning:
     The import of ‘Extends’ is redundant
       except perhaps to import instances from ‘Extends’
     To import instances alone, use: import Extends()
 }}}

--

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10890#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list