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

Don Stewart dons at galois.com
Wed Aug 13 20:29:46 EDT 2008


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.


More information about the Haskell-Cafe mailing list