#3734: overlapping orphan instances behave like incoherent without warning/error
---------------------------------+------------------------------------------
    Reporter:  Liskni_si         |       Owner:                             
        Type:  bug               |      Status:  new                        
    Priority:  normal            |   Component:  Compiler (Type checker)    
     Version:  6.10.4            |    Keywords:                             
          Os:  Unknown/Multiple  |    Testcase:                             
Architecture:  Unknown/Multiple  |     Failure:  Incorrect result at runtime
---------------------------------+------------------------------------------
 Consider these three modules:

 {{{
 module A where

 class (Show a) => A a

 data A' = A' deriving (Show)
 instance A A'

 data A'' = A'' deriving (Show)
 instance A A''

 print_a :: (A a) => a -> IO ()
 print_a a = print a
 }}}

 {{{
 {-# LANGUAGE FlexibleInstances, OverlappingInstances #-}
 module B where

 import A

 data B a = B a deriving (Show)
 instance (A a) => A (B a)
 }}}

 {{{
 {-# LANGUAGE FlexibleInstances, OverlappingInstances #-}
 module Main where

 import A
 import B

 instance Show (B A') where
     show _ = "kokodak"

 instance Show (B A'') where
     show _ = "brekeke"

 instance A (B A'')

 main :: IO ()
 main = do
     print   (B A')
     print_a (B A')
     putStrLn ""
     print   (B A'')
     print_a (B A'')
 }}}

 Without understanding a thing about dictionaries, I would expect that if
 this actually compiles (which I now understand it should not), I'd get
 `"kokodak kokodak brekeke brekeke"` as output, but I got `"kokodak B A'
 brekeke brekeke"` instead.

 I figured that even though I redefined `Show (B A')`, the `A (B a)`
 instance was defined in module `B` and consisted of the original `Show`
 dictionary. If I move the `Show (B A')` instance to module B, ghc
 complains that the definition of `A (B a)` depends on the instatiation of
 `a` and refuses to compile it, unless I enable `IncoherentInstances`.

 The problem here is that if the `Show (B A')` instance is orphan, I get
 the `IncoherentInstances` behaviour for free without any warning or error,
 giving me the false feeling that the code is actually OK. Is it possible
 that ghc gives an error in this case, and may the documentation mention
 that Overlapping + Orphan => Incoherent?

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

Reply via email to