[GHC] #9820: Apparently inconsistent behaviour in the presence of OverlappingInstances
GHC
ghc-devs at haskell.org
Fri Nov 21 09:34:18 UTC 2014
#9820: Apparently inconsistent behaviour in the presence of OverlappingInstances
-------------------------------------+-------------------------------------
Reporter: kosmikus | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.3
Keywords: | Operating System:
Architecture: Unknown/Multiple | Unknown/Multiple
Difficulty: Unknown | Type of failure:
Blocked By: | None/Unknown
Related Tickets: | Test Case:
| Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
This report is inspired by http://stackoverflow.com/questions/27051640
/strange-behavior-when-adding-constraint-to-instance
I'm not sure if it is a bug, but it certainly feels strange and
inconsistent to me, so I'd like to get some clarification.
Here's a self-contained example of the behaviour:
{{{#!hs
{-# LANGUAGE FlexibleInstances, OverlappingInstances #-}
module Overlap where
class C a where
foo :: a -> a
instance C a where
foo = id
instance C Int where
foo = (+1)
-- Note that this one does not mention class C anywhere:
class D a where
bar :: a -> a
instance D a where
bar = foo -- this works and picks the 'C a' instance always
-- The following does not compile without IncoherentInstances:
{-
baz :: a -> a
baz = foo
-}
}}}
I'm surprised that the definitions of `bar` and `baz` are treated
differently. Shouldn't they either both require `IncoherentInstances`, or
both work?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9820>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list