[Haskell-cafe] two problems with Data.Binary and Data.ByteString
Don Stewart
dons at galois.com
Wed Aug 13 18:03:43 EDT 2008
newsham:
> >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)?
>
> I'll answer my own question. Both Prelude.readFile and
> Data.ByteString.Lazy.Char8.readFile will keep the file open
> after reading the last byte and close it when trying to
> read further. Proof:
>
> module Main where
> import Control.Applicative
> -- import qualified Data.ByteString.Lazy.Char8 as B
> import Prelude as B
>
> stateFile = "1word32.bin"
> main = do
> x <- B.take 4 <$> B.readFile stateFile
> -- x <- B.take 5 <$> B.readFile stateFile
> print x
> B.writeFile stateFile x
>
> This works for Prelude and ByteString when taking 5 (there are
> exactly 4 bytes in "1word32.bin") and fail when taking 4.
>
> I'm not sure that this behavior is so bad.. there might be some
> advantages... but it might be nice to have it close after the last
> byte is read...
>
> 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...
>
This is perhaps a use case for Data.Binary.Strict then.
-- Don
More information about the Haskell-Cafe
mailing list