[GHC] #11292: Generics unboxed types: TEST=GEq1 WAY=optasm is failing

GHC ghc-devs at haskell.org
Mon Dec 28 02:24:28 UTC 2015


#11292: Generics unboxed types: TEST=GEq1 WAY=optasm is failing
-------------------------------------+-------------------------------------
        Reporter:  thomie            |                Owner:
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  7.11
      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 RyanGlScott):

 This doesn't appear to be specific to generics. Rather, it's an issue with
 `eqAddr#` and how it's affected by optimization levels. Here's a
 simplified example that takes away the complexity of `GEq1`:

 {{{#!hs
 {-# LANGUAGE MagicHash #-}
 module Main (main) where

 import GHC.Exts (Addr#, isTrue#)
 import GHC.Prim (eqAddr#)

 data A = A { runA :: Addr# }

 a :: A
 a = A "a"#

 main :: IO ()
 main = print (isTrue# (eqAddr# (runA a) (runA a)))
 }}}

 Compiling this with `-O0` makes the program return `True`, but compiling
 with `-O1` or higher returns `False`. Is pointer equality unpredictable
 enough that it can fail the reflexive property if optimized enough? If so,
 I can just modify `GEq1` so as not to include `Addr#`.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11292#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list