[Haskell-cafe] Reporting a problem with binary-0.5

Alexey Khudyakov alexey.skladnoy at gmail.com
Fri Jun 4 12:31:53 EDT 2010


On Fri, Jun 4, 2010 at 8:02 PM, Pete Chown <1 at 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


More information about the Haskell-Cafe mailing list