newsham:
> >I'm starting to wonder if this isn't an issue with
> >Data.ByteString.Lazy.Char8.{read,write}File.
>
> This simple test case fails:
>
> module Main where
> import qualified Data.ByteString.Lazy.Char8 as B
> main = do
> print =<< B.readFile "xxx"
> B.writeFile "xxx" =<< B.readFile "test.hs"
>
> If you replace B.readFile with readFile and B.writeFile with writeFile
> it works properly. ByteString bug?
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
You're looking for a post-Dec 19, 2007 release, after the patch,
Wed Dec 19 22:06:13 PST 2007 Don Stewart
* For lazy IO operations, be sure to hClose the resource on EOF
-- Don
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe