#2356: GHC accepts multiple instances for the same type in different modules
------------------------+---------------------------------------------------
    Reporter:  claus    |       Owner:          
        Type:  bug      |      Status:  new     
    Priority:  normal   |   Component:  Compiler
     Version:  6.8.2    |    Severity:  normal  
    Keywords:           |    Testcase:          
Architecture:  Unknown  |          Os:  Unknown 
------------------------+---------------------------------------------------
 as mentioned by Simon PJ in this thread:

 http://www.haskell.org/pipermail/haskell/2008-June/020436.html

 here is the example, spelled out:
 {{{
 module B0 where
 class C a where c :: a -> String
 data T = T deriving Show

 module B1 where
 import B0
 instance C T where c _ = "B1"
 b = c T

 module B2 where
 import B0
 instance C T where c _ = "B2"
 b = c T

 module Main where
 import B1
 import B2
 main = print (B1.b,B2.b)
 }}}
 this is accepted without flags or errors and prints `("B1","B2")`.

 the [http://haskell.org/onlinereport/decls.html#sect4.3.2 language report,
 section 4.3.2] clearly states:

   A type may not be declared as an instance of a particular class more
 than once in the program.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2356>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to