[Haskell-cafe] two problems with Data.Binary and Data.ByteString

Don Stewart dons at galois.com
Wed Aug 13 21:02:10 EDT 2008


newsham:
> So am I understanding you correctly that you believe this is not
> a bug?  That the use Data.Binary.decodeFile function leaks a file
> descriptor and this is proper behavior?

It's not a bug. It's lazy IO. If you want the Handle closed, demand all the
input. isEmpty will do this for you, if you're at the end of the file already.

> I still don't understand your explanation of how isEmpty can
> return True without having read to EOF.  The ByteString continues
> to contain more data until an EOF is reached.  Doesn't one of
> 
>          return (B.null s && L.null ss)

isEmpty is perfectly fine. You're just not demanding its result.

Consider,

    {-# LANGUAGE BangPatterns #-}

    import Data.Word
    import Data.Binary
    import Data.Binary.Get
    import qualified Data.ByteString.Lazy as L
    import System.IO

    main = do
        encodeFile stateFile (42 :: Word32)
        d <- strictDecodeFile stateFile :: IO Word32
        encodeFile stateFile d
        print d
      where
        stateFile = "1word32.bin"

    strictDecodeFile :: Binary a => FilePath -> IO a
    strictDecodeFile f = do
        ss <- L.readFile f
        return $! runGet (do v  <- get
                             !m <- isEmpty -- if we're at the end, this will close it
                             return v) ss

Look at strictDecodeFile. It's pretty much identical to the normal decodeFile,
but it assumes 'get' will consume the entire file. It then checks for null,
which will trigger an EOF and close if you are actually at the end.
        
So we just decode the file, and check if the buffer's empty at the end.

    $ ghc --make A.hs
    [1 of 1] Compiling Main             ( A.hs, A.o )
    Linking A ...
    $ ./A            
    42

But if we leave out that bang pattern on isEmpty, the test won't run, and we'll get,

    $ ./A            
    A: 1word32.bin: openBinaryFile: resource busy (file is locked)

So were you just confused about how to use isEmpty?

You could also explicit close in strictDecodeFile,

    strictDecodeFile :: Binary a => FilePath -> IO a
    strictDecodeFile f = do
        h  <- openFile f ReadMode
        ss <- L.hGetContents h f
        let !v = runGet (do v  <- get
                            return v) ss
        hClose h
        return v

Whatever works best for you.

-- Don


More information about the Haskell-Cafe mailing list