[GHC] #12585: GHC duplicates string literals in rodata section and breaks 'Ptr Addr#' equality
GHC
ghc-devs at haskell.org
Fri Sep 9 22:19:52 UTC 2016
#12585: GHC duplicates string literals in rodata section and breaks 'Ptr Addr#'
equality
-------------------------------------+-------------------------------------
Reporter: slyfox | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
{{{#!hs
-- 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
:
{{{#!hs
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.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12585>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list