#3734: overlapping orphan instances behave like incoherent without warning/error
------------------------------------------+---------------------------------
Reporter: Liskni_si | Owner:
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler (Type checker) | Version: 6.10.4
Resolution: fixed | Keywords:
Difficulty: | Os: Unknown/Multiple
Testcase: | Architecture: Unknown/Multiple
Failure: Incorrect result at runtime |
------------------------------------------+---------------------------------
Changes (by simonpj):
* status: new => closed
* difficulty: =>
* resolution: => fixed
Comment:
Good point. But it's worse than that. You can get incoherence from
overlap without even orphans. I've added an explanation to the user guide,
reproduced below:
{{{
Warning: overlapping instances must be used with care. They
can give rise to incoherence (ie different instance choices are made
in different parts of the program) even without
<option>-XIncoherentInstances</option>. Consider:
<programlisting>
{-# LANGUAGE OverlappingInstances #-}
module Help where
class MyShow a where
myshow :: a -> String
instance MyShow a => MyShow [a] where
myshow xs = concatMap myshow xs
showHelp :: MyShow a => [a] -> String
showHelp xs = myshow xs
{-# LANGUAGE FlexibleInstances, OverlappingInstances #-}
module Main where
import Help
data T = MkT
instance MyShow T where
myshow x = "Used generic instance"
instance MyShow [T] where
myshow xs = "Used more specific instance"
main = do { print (myshow [MkT]); print (showHelp [MkT]) }
</programlisting>
In function <literal>showHelp</literal> GHC sees no overlapping
instances, and so uses the <literal>MyShow [a]</literal> instance
without complaint. In the call to <literal>myshow</literal> in
<literal>main</literal>,
GHC resolves the <literal>MyShow [T]</literal> constraint using the
overlapping
instance declaration in module <literal>Main</literal>. As a result,
the program prints
<programlisting>
"Used more specific instance"
"Used generic instance"
</programlisting>
(An alternative possible behaviour, not currently implemented,
would be to reject module <literal>Help</literal>
on the grounds that a later instance declaration might overlap the local
one.)
</para>
}}}
Simon
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3734#comment:1>
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