Reporting a problem with binary-0.5

I've been trying to get in touch with the maintainers of the Binary package, to report an issue. When I emailed the addresses given on Hackage, I got an automated response saying I had used an address that was no longer current. I don't want to put pressure on anyone to fix my bug -- I didn't pay anything for Binary, so it wouldn't be fair for me to have that kind of expectation. At the same time, I don't really want my bug report to go missing just because someone's email address has changed. Does anyone know who I should be talking to? Or is there a bug tracker for the Hackage packages somewhere? I noticed this problem when I ran into some trouble with the network-dns package. It would hang up as soon as I tried to send a query. Eventually I traced the problem to the binary module, and reduced it to this short test case: module Main where import qualified Data.Binary.Get as G import qualified Data.ByteString.Lazy as B main = do urandom <- B.readFile "/dev/urandom" let urandomParser :: G.Get [Int] urandomParser = do v <- G.getWord32be rest <- urandomParser return $ fromIntegral v : rest seeds = G.runGet urandomParser urandom print $ take 4 seeds This code attempts to create an infinite list of random numbers -- a technique also used by network-dns. It turns out that this code works with binary-0.4.4 but not with binary-0.5.0.2. Both were built with ghc-6.12.1 on Ubuntu. (I haven't tested with the intermediate versions of the binary module.) It seems that with binary-0.5.0.2 there is some unwanted strictness; something is evaluated for the whole list, even though it is only the first few elements that are required. Incidentally, if the test case is changed like this: --- get_monad.hs 2010-05-28 11:31:02.399202535 +0100 +++ get_monad2.hs 2010-05-28 13:44:25.515486013 +0100 @@ -1,10 +1,12 @@ module Main where +import Control.Monad + import qualified Data.Binary.Get as G import qualified Data.ByteString.Lazy as B main = do - urandom <- B.readFile "/dev/urandom" + urandom <- liftM (B.take 64) $ B.readFile "/dev/urandom" let urandomParser :: G.Get [Int] urandomParser = do v <- G.getWord32be the program exits with an error: get_monad2.hs: too few bytes. Failed reading at byte position 68 This seems to demonstrate that the program is reading more data than it needs to. Thanks, Pete

Pete Chown <1@234.cx> writes:
This code attempts to create an infinite list of random numbers -- a technique also used by network-dns. It turns out that this code works with binary-0.4.4 but not with binary-0.5.0.2.
There was a deliberate change in strictness in 0.5 making binary strict, which apparently speeds up GHC. I ran into the same problem, but have no better workaround than to require binary < 0.5 in my .cabal. -k (I made a note about this at http://blog.malde.org/index.php/2010/05/22/snagged/) -- If I haven't seen further, it is by standing in the footprints of giants

Ketil Malde wrote:
There was a deliberate change in strictness in 0.5 making binary strict, which apparently speeds up GHC.
Ah okay. I suppose that passes the buck to network-dns. Presumably it could be fixed fairly simply by requiring binary < 0.5 (as you suggested). Ideally, though, the implementation of its infinite random list would be changed. This would avoid having a dependency on a package which is no longer current. Pete

On Fri, Jun 4, 2010 at 8:02 PM, Pete Chown <1@234.cx> wrote:
I've been trying to get in touch with the maintainers of the Binary package, to report an issue. When I emailed the addresses given on Hackage, I got an automated response saying I had used an address that was no longer current.
I don't want to put pressure on anyone to fix my bug -- I didn't pay anything for Binary, so it wouldn't be fair for me to have that kind of expectation. At the same time, I don't really want my bug report to go missing just because someone's email address has changed. Does anyone know who I should be talking to? Or is there a bug tracker for the Hackage packages somewhere?
I noticed this problem when I ran into some trouble with the network-dns package. It would hang up as soon as I tried to send a query. Eventually I traced the problem to the binary module, and reduced it to this short test case:
module Main where
import qualified Data.Binary.Get as G import qualified Data.ByteString.Lazy as B
main = do urandom <- B.readFile "/dev/urandom" let urandomParser :: G.Get [Int] urandomParser = do v <- G.getWord32be rest <- urandomParser return $ fromIntegral v : rest seeds = G.runGet urandomParser urandom
print $ take 4 seeds
This issue was discussed on the list before. Get monad definition was changed in binary 0.5.0.2. It was made strict and evaluation of result of runGet is forced. This increased performance but broke programs which relies on lazyness to work. Here is code I use to work around this issue:
runGetStream :: Get a -> ByteString -> [a] runGetStream getter bs = unfoldr step bs where step bs = case runGetState getOne bs 0 of (Nothing, _, _ ) -> Nothing (Just x, bs', off') -> Just (x, bs') getOne = do empty <- isEmpty if empty then return Nothing else Just <$> getter ... seeds = runGetStream (fromInteger <$> getWord64be) urandom

Alexey Khudyakov
This issue was discussed on the list before. Get monad definition was changed in binary 0.5.0.2. It was made strict and evaluation of result of runGet is forced. This increased performance but broke programs which relies on lazyness to work.
I just found a more detailed writeup by dons on http://donsbot.wordpress.com/2009/09/16/data-binary-performance-improvments-... -k -- If I haven't seen further, it is by standing in the footprints of giants
participants (3)
-
Alexey Khudyakov
-
Ketil Malde
-
Pete Chown