GHC duplicates string literals in rodata section and breaks 'Ptr Addr#' equality
-- test-sha256.hs:
{-# LANGUAGE MagicHash #-}
module Main (main) where
import GHC.Prim (Addr#)
import GHC.Ptr (Ptr(..), minusPtr)
bug :: Addr# -> IO ()
bug a = do
print ("cmp:", Ptr a == Ptr a)
print ("delta:", Ptr a `minusPtr` Ptr a)
print ("values:", Ptr a, Ptr a)
main :: IO ()
main = bug "Assumptions are subtle!"#
$ inplace/bin/ghc-stage2 -fforce-recomp -O1 --make test-sha256.hs && ./test-sha256
[1 of 1] Compiling Main ( test-sha256.hs, test-sha256.o )
Linking test-sha256 ...
("cmp:",False)
("delta:",-24)
("values:",0x000000000072fdc0,0x000000000072fda8)
Stg shows that literal gets inlined:
$ inplace/bin/ghc-stage2 -fforce-recomp -O1 --make test-sha256 -ddump-stg -dsuppress-all -dsuppress-uniques 2>&1 | grep Assumptions
eqAddr# ["Assumptions are subtle!"# "Assumptions are subtle!"#]
minusAddr# ["Assumptions are subtle!"# "Assumptions are subtle!"#]
$w$cshowsPrec "Assumptions are subtle!"# w2
$w$cshowsPrec "Assumptions are subtle!"# w2
eqAddr# ["Assumptions are subtle!"# "Assumptions are subtle!"#]
minusAddr# ["Assumptions are subtle!"# "Assumptions are subtle!"#]
$w$cshowsPrec "Assumptions are subtle!"# w2
$w$cshowsPrec "Assumptions are subtle!"# w2
I've found this bug as a SIGSEGV on testsuite cryptohash-sha256-0.11.100.1 from hackage.
Bytestring assumes that address does not change and implements loops over Ptrs https://github.com/haskell/bytestring/blob/master/Data/ByteString.hs#L1171 :
filter :: (Word8 -> Bool) -> ByteString -> ByteString
filter k ps@(PS x s l)
| null ps = ps
| otherwise = unsafePerformIO $ createAndTrim l $ \p -> withForeignPtr x $ \f -> do
t <- go (f `plusPtr` s) p (f `plusPtr` (s + l))
return $! t `minusPtr` p -- actual length
where
go !f !t !end | f == end = return t
| otherwise = do
w <- peek f
if k w
then poke t w >> go (f `plusPtr` 1) (t `plusPtr` 1) end
else go (f `plusPtr` 1) t end
{-# INLINE filter #-}
In case of cryptohash-sha256-0.11.100.1 t <- go (f plusPtr
s) p (f plusPtr
(s + l)) for literal inlined righ at 'f' call which caused testsuite failure.
It seems sensible not to emit the literal more than once into .rodata section.
It won't guard against problems where literal is exported as a part of .hi file but might be good enough for common cases like this.
Trac metadata
Trac field | Value |
---|---|
Version | 8.0.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | duncan |
Operating system | |
Architecture |