[GHC] #15135: Overlapping typeclass instance selection depends on the optimisation level
GHC
ghc-devs at haskell.org
Wed Oct 24 07:25:08 UTC 2018
#15135: Overlapping typeclass instance selection depends on the optimisation level
-------------------------------------+-------------------------------------
Reporter: nicuveo | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.8.1
Component: Compiler | Version: 8.4.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by baramoglo):
Here is an example that exhibits the same bug (I think) in a single file:
{{{
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
data A = A
deriving (Show)
data B a = B a
deriving (Show)
class Project a b where
project :: b -> Maybe a
instance {-# OVERLAPPING #-} Project a b where
project _ = Nothing
instance {-# OVERLAPPING #-} Project a a where
project = Just
instance {-# OVERLAPPING #-} Project a b => Project a (B b) where
project (B a) = project a
main = print (project (B A) :: Maybe A)
}}}
Prints `Just A` when compiled with `-O0` and `Nothing` when compiled with
`-O1`.
Note that the first instance should really say `{-# OVERLAPPABLE #-}`
(AFAIU). If I change to that, the bug goes away.
Let me know if you think this should be filed as a different bug.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15135#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list