#5628: Deriving Eq on bottom types breaks reflexivity of (==)
---------------------------------+------------------------------------------
Reporter: tinctorius | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.0.3 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: Incorrect result at runtime
---------------------------------+------------------------------------------
Related to #4220 and #4302.
{{{
{-# LANGUAGE EmptyDataDecls, StandaloneDeriving #-}
data Z
deriving instance Eq Z
g :: Z
g = g
main :: IO ()
main = print (g == g)
}}}
Observed output (`(==)` not reflexive anymore?):
{{{
False
}}}
Expected output (this is what `TcGenDeriv.mkRdrFunBind` does for `Show`
etc.):
{{{
"*** Exception: Void (==)
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5628>
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