How to disable warning for "export item 'module ...' exports nothing"?

Sean Leather leather at cs.uu.nl
Fri Aug 15 10:17:44 EDT 2008


Ross Paterson wrote:

> On Fri, Aug 15, 2008 at 03:09:16PM +0200, Sean Leather wrote:
> > Ross Paterson wrote:
> >     With implicit import, it just doesn't work to have different
> instances in
> >     different places.  Suppose two modules use your library in the
> different
> >     ways you envisage.  Then those modules cannot be used together in the
> >     same program.  Your library will not be re-usable.
> >
> > It is not true that those modules cannot be used in the same program. It
> is
> > possibly true that they cannot both be imported by another module. (It
> depends
> > on how the instances are used.)
>
> If they're in the same program, there will be chains of imports from Main
> to each of them, so Main will implicitly import conflicting instances and
> will be rejected by the compiler.
>

module A where
class A t where
  a :: t

module B where
import A
instance A Int where
  a = 0
a0 :: Int
a0 = a

module C where
import A
instance A Int where
  a = 1
a1 :: Int
a1 = a

module Main where
import A
import B
import C
main = do putStrLn $ "a0=" ++ show a0
          putStrLn $ "a1=" ++ show a1

This works, because of the way the instances are used. While overlapping
instances are imported into Main, they are not used in Main.

Sean
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20080815/7d017325/attachment.htm


More information about the Glasgow-haskell-users mailing list