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?

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)

force getContents to read until EOF?

On Wed, 13 Aug 2008, Don Stewart wrote:
newsham:
Ok, surely at least everyone must agree that this is a bug:

  force :: Word8 -> IO Word8
  force x = print x >> return x
  -- force = return . (`using` rnf)

  main = do
      d <- force =<< decodeFile stateFile
      encodeFile stateFile d
      where stateFile = "1word32.bin"

test8.hs: 1word32.bin: openBinaryFile: resource busy (file is locked)


Remember that

   decodeFile f = liftM decode (L.readFile f)

and

   readFile :: FilePath -> IO ByteString
   readFile f = openBinaryFile f ReadMode >>= hGetContents

where hGetContents sits in a loop, reading chunks,

   loop = do
       c <- S.hGetNonBlocking h k
       if S.null c
         then do eof <- hIsEOF h
                 if eof then hClose h >> return Empty
                        else hWaitForInput h (-1)
                          >> loop
         else do cs <- lazyRead
                 return (Chunk c cs)

while isEmpty is just,

   isEmpty :: Get Bool
   isEmpty = do
       S s ss _ <- get
       return (B.null s && L.null ss)

That is, it checks the parsed chunk, it doesn't demand any more reading be done.

So the only way you're going to get that Handle closed by readFile is to ensure
you read till EOF is hit. After you decode, just ask keep asking for bytes till 
EOF,
or close it yourself,

   decodeFile f = do
       h  <- openFile f ReadMode
       ss <- L.hGetContents h
       let e = decode ss
       rnf e `seq` hClose h

or some such, where you can confirm the decoding as taken place.


Tim Newsham
http://www.thenewsh.com/~newsham/
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to