[GHC] #10521: Wrong results in strict Word8 storage on x64
GHC
ghc-devs at haskell.org
Tue Jun 16 15:54:40 UTC 2015
#10521: Wrong results in strict Word8 storage on x64
-------------------------------------+-------------------------------------
Reporter: VincentBerthoux2 | Owner:
Type: bug | Status: new
Priority: highest | Milestone: 7.10.2
Component: Compiler | Version: 7.10.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: x86_64
Type of failure: Incorrect result | (amd64)
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by rwbarton):
The commit that merged F1 and D1 was
e2f6bbd3a27685bc667655fdb093734cb565b4cf which is in 7.8 but not 7.6. Here
is a reproducer for 7.8 too:
{{{
{-# LANGUAGE MagicHash #-}
import GHC.Exts
f :: Float# -> Float#
f x = x
{-# NOINLINE f #-}
g :: Double# -> Double#
g x = x
{-# NOINLINE g #-}
h :: Float -> Float
h (F# x) = let a = F# (f x)
b = D# (g (2.0##))
in a `seq` (b `seq` a)
main = print (h 1.0) -- with ghc -O, prints 0.0
}}}
Not sure yet whether it is better to revert (parts of) that commit or to
try to account for STG global registers overlapping in the cmmSink pass
and wherever else it might be necessary.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10521#comment:6>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list