[GHC] #14629: Seemingly unused qualified import affects method visibility

GHC ghc-devs at haskell.org
Wed Jan 3 02:48:30 UTC 2018


#14629: Seemingly unused qualified import affects method visibility
-------------------------------------+-------------------------------------
           Reporter:  gelisam        |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.2
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Poor/confusing
  Unknown/Multiple                   |  error message
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:  ticket:3992,
                                     |  ticket:10890
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Here is a simple test case:

 {{{#!hs
 module MyLib where

 class MyClass a where
   myMethod :: a -> a
 }}}

 {{{#!hs
 module MyModule where
 import MyLib (MyClass)
 --import qualified MyLib as L

 data Foo = Foo

 instance MyClass Foo where
   -- error: ‘myMethod’ is not a (visible) method of class ‘MyClass’
   myMethod Foo = Foo
 }}}

 Since I have only imported `MyClass` and not its methods (that would be
 `import MyLib (MyClass(..))`), the error is correct, `myMethod` is not
 visible. But if I uncomment the `import qualified MyLib as L` line, the
 error disappears even though I do not use `L` anywhere. Writing
 `L.myMethod Foo = Foo` is not even legal!

 -----

 I filed this under "confusing error message", so let me show you the
 conditions under which the above behaviour was confusing. We were using
 [https://hackage.haskell.org/package/classy-
 prelude-1.3.1/docs/ClassyPrelude.html classy-prelude] instead of
 `Prelude`, but we were not familiar with all the differences between the
 two preludes. We started with code like this, which did not compile:

 {{{#!hs
 {-# LANGUAGE NoImplicitPrelude #-}
 module MyModule
 import ClassyPrelude

 data Foo a = Foo

 instance Foldable Foo where
   -- 'foldMap' is not a (visible) method of class 'Foldable'
   foldMap = undefined
 }}}

 So we clarified that we meant `Prelude.Foldable`, in case
 `ClassyFoldable.Foldable` meant something different.

 {{{#!hs
 {-# LANGUAGE NoImplicitPrelude #-}
 module MyModule
 import ClassyPrelude
 import qualified Prelude

 data Foo a = Foo

 instance Prelude.Foldable Foo where
   foldMap = undefined
 }}}

 This compiled, so we first thought that `Prelude.Foldable` and
 `ClassyPrelude.Foldable` were two different type classes, but we later
 discovered that `ClassyPrelude.Foldable` is a re-export of
 `Prelude.Foldable`. So the following means the same thing and also
 compiles:

 {{{#!hs
 {-# LANGUAGE NoImplicitPrelude #-}
 module MyModule
 import ClassyPrelude
 import qualified Prelude

 data Foo a = Foo

 instance ClassyPrelude.Foldable Foo where
   foldMap = undefined
 }}}

 At this point, the qualified `Prelude` import doesn't seem used anywhere,
 so we thought it was safe to remove it:

 {{{#!hs
 {-# LANGUAGE NoImplicitPrelude #-}
 import ClassyPrelude

 data Foo a = Foo

 instance ClassyPrelude.Foldable Foo where
   -- 'foldMap' is not a (visible) method of class 'Foldable'
   foldMap = undefined
 }}}

 But `ClassyPrelude.foldMap` is ''not'' the same as `Prelude.foldMap`, so
 this did not compile and it wasn't clear why.

 One way to make this less confusing would be to allow qualified method
 names; this way, we would have tried both `Prelude.foldMap = undefined`
 and `ClassyPrelude.foldMap = undefined`, and we would have discovered the
 source of the problem.

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


More information about the ghc-tickets mailing list