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

Pete Chown 1 at 234.cx
Fri Jun 4 12:02:24 EDT 2010


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



More information about the Haskell-Cafe mailing list