[Haskell-cafe] two problems with Data.Binary and Data.ByteString
Tim Newsham
newsham at lava.net
Wed Aug 13 15:56:53 EDT 2008
> Ah, that would be a bug in older ByteString implementations, that were a
> bit incautious about closing handles. This example works for me with
>
> bytestring-0.9.1.0
Yup, thank you Don and Duncan for pointing this out. I updated
my bytestring library and the test case no longer fails. However,
I'm still having problems and not sure why. I was able to
distill the problem down to this:
$ od -x 1word32.bin
0000000 0500 2ca4
$ runhaskell test6.hs
loading...
saving...
test6.hs: 1word32.bin: openFile: resource busy (file is locked)
$ cat test6.hs
module Main where
import Control.Applicative
import Control.Parallel.Strategies (rnf, NFData, using)
import Data.Binary
import qualified Data.ByteString.Lazy.Char8 as B
import Data.Word
stateFile = "1word32.bin"
loadState :: IO Word32
loadState = decode <$> B.readFile stateFile
saveState :: Word32 -> IO ()
saveState db = B.writeFile stateFile $ encode db
{-
-- Works!
loadState = B.readFile stateFile
saveState = B.writeFile stateFile
-}
-- force x = print x >> return x
force = return . (`using` rnf)
main = do
putStrLn "loading..."
d <- force =<< loadState
putStrLn "saving..."
saveState d
I tried this both with "print" and "rnf" to the same effect.
It looks like there still might be some situations where the
file isn't being closed?
Should the file be closed when the last byte is read (in this
case its definitely reading all four bytes) or when the first
byte after that is read (in this case it probably doesn't
attempt to read more than 4 bytes)?
Tim Newsham
http://www.thenewsh.com/~newsham/
More information about the Haskell-Cafe
mailing list