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

Ross Paterson ross at soi.city.ac.uk
Fri Aug 15 10:34:01 EDT 2008


On Fri, Aug 15, 2008 at 04:17:44PM +0200, Sean Leather wrote:
> 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.

Then that is a GHC bug.  Haskell 98 Report 4.3.2: "A type may not be
declared as an instance of a particular class more than once in the
program."


More information about the Glasgow-haskell-users mailing list