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)
the built-in Data.Binary.decodeFile function doesn't close
its handle when it is done (same reason as my earlier examples).
However, I think probably the real blame here should probably go
to Data.Binary which doesn't attempt to check that it has consumed
all of its input after doing a "decode". If "decode" completes
and there is unconsumed data, it should probably raise an error
(it already raises errors for premature EOF). There's no reason
for it not to, since it does not provide the unconsumed data to
the caller when its done, anyway...
I would have expected this to fix my problems:
binEof :: Get ()
binEof = do
more <- not <$> isEmpty
when more $ error "expected EOF"
decodeFully :: Binary b => B.ByteString -> b
decodeFully = runGet (get << binEof)
where a << b = a >>= (\x -> b >> return x)
but even when using decodeFully, it still doesn't close the handle.
Shouldn't Data.Binary.Get.isEmpty force a file handle close in
the case that it returns True?
Tim Newsham
http://www.thenewsh.com/~newsham/
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe