Subtle bug in Data.ByteString and/or GHC (perhaps)

Hi, The following program prints different outputs depending on whether optimisations are turned on or not (using GHC 6.6.1 and binary 0.3): module Bug (main) where import Data.Binary import Data.Binary.Put import Data.Binary.Get import Data.Binary.Builder import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Base as BB append' :: BL.ByteString -> BL.ByteString -> BL.ByteString append' = BL.append -- append' (BB.LPS xs) (BB.LPS ys) = BB.LPS (xs ++ ys) encode' :: Char -> BL.ByteString encode' x = encode (st `seq` 'a') `append'` toLazyByteString builder where (st, builder) = unPut (put x) decode' :: BL.ByteString -> Char decode' s = decode s' where (_, s', _) = runGetState (get :: Get Char) s 0 main :: IO () main = mapM_ (print . test) "abc" where test x = decode' (encode' x) == x $ ghc --make -O Bug.hs -main-is Bug.main -o bug [...] $ ./bug True False False $ rm Bug.o; ghc --make Bug.hs -main-is Bug.main -o bug [...] $ ./bug True True True If the commented-out version of append' (which is a bit lazier than the other one) is used instead, then this problem disappears. The commented-out version is the one used in the darcs version of Data.ByteString, so the problem above has, in a sense, already been fixed. However, it is disconcerting that the result of a program can depend on optimisation flags, and changing the strictness of a function should only make a (pure) program more or less defined, not change a result from True to False. Hence I wonder if anyone knows the real cause of this bug, and what the risk of encountering similar bugs in the future is. It took lots of time to find and fix the problem above (which of course came up in a larger piece of code), so I hope that I won't encounter similar problems again. My guess is that the problem has something to do with unsound rewrite rules in Data.ByteString, by the way. Or maybe the problem lies in GHC's optimiser. -- /NAD

Very intersting. Possibly something unsafe happening in there. Duncan, care to take a look? -- Don nad:
Hi,
The following program prints different outputs depending on whether optimisations are turned on or not (using GHC 6.6.1 and binary 0.3):
module Bug (main) where
import Data.Binary import Data.Binary.Put import Data.Binary.Get import Data.Binary.Builder import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Base as BB
append' :: BL.ByteString -> BL.ByteString -> BL.ByteString append' = BL.append -- append' (BB.LPS xs) (BB.LPS ys) = BB.LPS (xs ++ ys)
encode' :: Char -> BL.ByteString encode' x = encode (st `seq` 'a') `append'` toLazyByteString builder where (st, builder) = unPut (put x)
decode' :: BL.ByteString -> Char decode' s = decode s' where (_, s', _) = runGetState (get :: Get Char) s 0
main :: IO () main = mapM_ (print . test) "abc" where test x = decode' (encode' x) == x
$ ghc --make -O Bug.hs -main-is Bug.main -o bug [...] $ ./bug True False False $ rm Bug.o; ghc --make Bug.hs -main-is Bug.main -o bug [...] $ ./bug True True True
If the commented-out version of append' (which is a bit lazier than the other one) is used instead, then this problem disappears. The commented-out version is the one used in the darcs version of Data.ByteString, so the problem above has, in a sense, already been fixed.
However, it is disconcerting that the result of a program can depend on optimisation flags, and changing the strictness of a function should only make a (pure) program more or less defined, not change a result from True to False. Hence I wonder if anyone knows the real cause of this bug, and what the risk of encountering similar bugs in the future is. It took lots of time to find and fix the problem above (which of course came up in a larger piece of code), so I hope that I won't encounter similar problems again.
My guess is that the problem has something to do with unsound rewrite rules in Data.ByteString, by the way. Or maybe the problem lies in GHC's optimiser.
-- /NAD
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I note that today we also had a report of a bug related to non-evaluatoin of a check in 'binary', meaning an error condition wouldn't be spotted, and a short-read value would be returned. Possibly related. -- Don dons:
Very intersting. Possibly something unsafe happening in there.
Duncan, care to take a look?
-- Don
nad:
Hi,
The following program prints different outputs depending on whether optimisations are turned on or not (using GHC 6.6.1 and binary 0.3):
module Bug (main) where
import Data.Binary import Data.Binary.Put import Data.Binary.Get import Data.Binary.Builder import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Base as BB
append' :: BL.ByteString -> BL.ByteString -> BL.ByteString append' = BL.append -- append' (BB.LPS xs) (BB.LPS ys) = BB.LPS (xs ++ ys)
encode' :: Char -> BL.ByteString encode' x = encode (st `seq` 'a') `append'` toLazyByteString builder where (st, builder) = unPut (put x)
decode' :: BL.ByteString -> Char decode' s = decode s' where (_, s', _) = runGetState (get :: Get Char) s 0
main :: IO () main = mapM_ (print . test) "abc" where test x = decode' (encode' x) == x
$ ghc --make -O Bug.hs -main-is Bug.main -o bug [...] $ ./bug True False False $ rm Bug.o; ghc --make Bug.hs -main-is Bug.main -o bug [...] $ ./bug True True True
If the commented-out version of append' (which is a bit lazier than the other one) is used instead, then this problem disappears. The commented-out version is the one used in the darcs version of Data.ByteString, so the problem above has, in a sense, already been fixed.
However, it is disconcerting that the result of a program can depend on optimisation flags, and changing the strictness of a function should only make a (pure) program more or less defined, not change a result from True to False. Hence I wonder if anyone knows the real cause of this bug, and what the risk of encountering similar bugs in the future is. It took lots of time to find and fix the problem above (which of course came up in a larger piece of code), so I hope that I won't encounter similar problems again.
My guess is that the problem has something to do with unsound rewrite rules in Data.ByteString, by the way. Or maybe the problem lies in GHC's optimiser.
-- /NAD
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Tue, 05 Jun 2007, dons@cse.unsw.edu.au (Donald Bruce Stewart) wrote:
I note that today we also had a report of a bug related to non-evaluatoin of a check in 'binary', meaning an error condition wouldn't be spotted, and a short-read value would be returned. Possibly related.
I tried the most recent darcs version of binary, and the problem appears to have been fixed, presumably by the patch replacing inlinePerformIO with unsafePerformIO. -- /NAD

On Mon, 18 Jun 2007, Nils Anders Danielsson
I tried the most recent darcs version of binary, and the problem appears to have been fixed, presumably by the patch replacing inlinePerformIO with unsafePerformIO.
It turns out that, although the code I posted earlier in this thread now works, the larger piece of code which I am actually interested in running does not... I guess this is the price you pay for using libraries which make use of RULES pragmas and unsafePerformIO and friends. -- /NAD

nad:
On Mon, 18 Jun 2007, Nils Anders Danielsson
wrote: I tried the most recent darcs version of binary, and the problem appears to have been fixed, presumably by the patch replacing inlinePerformIO with unsafePerformIO.
It turns out that, although the code I posted earlier in this thread now works, the larger piece of code which I am actually interested in running does not...
I guess this is the price you pay for using libraries which make use of RULES pragmas and unsafePerformIO and friends.
Please submit an updated bug report. -- Don

nad:
On Mon, 18 Jun 2007, Nils Anders Danielsson
wrote: I tried the most recent darcs version of binary, and the problem appears to have been fixed, presumably by the patch replacing inlinePerformIO with unsafePerformIO.
It turns out that, although the code I posted earlier in this thread now works, the larger piece of code which I am actually interested in running does not...
I guess this is the price you pay for using libraries which make use of RULES pragmas and unsafePerformIO and friends.
I'm keen to identify what your problem is, however, Duncan is on vacation, and I'm writing up my dissertation. Possibly Lennart can track this down if its a Data.Binary issue. If its a ByteString issue, Duncan or I can investigate it soonish. However, we'll need a test case, so more info please! :-) Also, the first place to look would be Data.Binary (and also try out the stable branch of Data.ByteString). -- Don

On Tue, 19 Jun 2007, dons@cse.unsw.edu.au (Donald Bruce Stewart) wrote:
nad:
It turns out that, although the code I posted earlier in this thread now works, the larger piece of code which I am actually interested in running does not...
However, we'll need a test case, so more info please! :-)
I took a closer look at the issue today, and apparently the problem yesterday was caused by me. Hence you can disregard the second bug report. :) Thanks for the bug fix. Was the problem caused by code breaking the documented "rules" for safe usage of some unsafe function? If not, maybe some documentation should be updated to avoid similar problems in the future. -- /NAD

nad:
On Tue, 05 Jun 2007, dons@cse.unsw.edu.au (Donald Bruce Stewart) wrote:
I note that today we also had a report of a bug related to non-evaluatoin of a check in 'binary', meaning an error condition wouldn't be spotted, and a short-read value would be returned. Possibly related.
I tried the most recent darcs version of binary, and the problem appears to have been fixed, presumably by the patch replacing inlinePerformIO with unsafePerformIO.
There was also the fix related to a lazy 'when' not being evaluated. It might have been that. -- Don

| My guess is that the problem has something to do with unsound rewrite | rules in Data.ByteString, by the way. Or maybe the problem lies in | GHC's optimiser. It'd be nice to know if it's the latter -- someone please yell if so. GHC's optimiser should never change semantics. Simon
participants (3)
-
dons@cse.unsw.edu.au
-
Nils Anders Danielsson
-
Simon Peyton-Jones