
one more piece of email pollution:
import Control.Exception (bracket)
import System.IO
import Data.Binary
import qualified Data.ByteString.Lazy as B
strictDecodeFile :: Binary a => FilePath -> IO a
strictDecodeFile path =
bracket (openBinaryFile path ReadMode) hClose $ \h -> do
c <- B.hGetContents h
return $! decode c
seems to work like Data.Binary.decodeFile but explicitly closes the handle.
take care, ben
On Sun, Apr 20, 2008 at 4:35 PM, Ben
FWIW, installed bytestring-0.9.1.0, ran ghc-pkg hide bytestring-0.9.0.1, recompiled and reinstalled binary-0.4.1. then i played around with all that you suggested, and came to the conclusion that i don't understand seq!
import Control.Exception (bracket) import System.Directory import System.IO import Data.Binary import Data.ByteString.Lazy as B
strictDecodeFile :: Binary a => FilePath -> (a -> b) -> IO () strictDecodeFile path force = bracket (openFile path ReadMode) hClose $ \h -> do c <- B.hGetContents h force (decode c) `seq` return ()
strictDecodeFile' :: Binary a => FilePath -> (a -> IO b) -> IO ()
strictDecodeFile' path force = bracket (openFile path ReadMode) hClose $ \h -> do c <- B.hGetContents h force (decode c) return ()
main = do let dat = [1..10]::[Int] fname = "foo.dat" encodeFile fname dat h <- openFile fname ReadMode c <- B.hGetContents h let dat2 = decode c print (dat == dat2) hClose h removeFile fname
encodeFile fname dat strictDecodeFile fname (\x -> do print "strict 1" print (x == dat)) removeFile fname
encodeFile fname dat strictDecodeFile' fname (\x -> do print "strict 2" print (x == dat)) removeFile fname
encodeFile fname dat dat4 <- decodeFile fname print (dat == dat4) removeFile fname
running main outputs
True "strict 2" True True *** Exception: foo.dat: removeFile: permission denied (Permission denied)
e.g. the handle version works, Bryan's original strictDecodeFile appears to not run "force", the modified strictDecodeFile' does run "force" (i didn't use seq, just an additional line in the monad), and the encodeFile / decodeFile / removeFile appears to still not work with the latest bytestring. what's the difference between the seq and non-seq versions?
for now i can use strictDecodeFile' but at least something should be said in the docs about decodeFile et al holding handles. (i understand this is not the fault of binary per se as much as haskell's non-strict semantics, but a reminder for noobs like me would be helpful.) and finally something like strictDecodeFile' might be useful in the library?
thanks for the help, ben
On Sun, Apr 20, 2008 at 2:34 PM, Duncan Coutts
wrote: On Sun, 2008-04-20 at 14:24 -0700, Bryan O'Sullivan wrote:
Doh! For all that I wrote about encodeFile, substitute decodeFile.
Indeed the version of encodeFile you wrote should be exactly identical to the original because the lazy bytestring writeFile already uses bracket like that:
writeFile :: FilePath -> ByteString -> IO () writeFile f txt = bracket (openBinaryFile f WriteMode) hClose (\hdl -> hPut hdl txt)
strictDecodeFile :: Binary a => FilePath -> (a -> b) -> IO () strictDecodeFile path force = bracket (openFile path ReadMode) hClose $ \h -> do c <- L.hGetContents h force (decode c) `seq` return ()
Yes, the problem with Ben's program was that decodeFile is lazily reading the file and lazily decoding. If the decoding consumes all the input then it should be possible to avoid rewriting decodeFile and use:
dat2 <- decodeFile fname evaluate dat2 removeFile fname
It's not immediately clear to me if we can make the decodeFile behave like your version. I'd have to go think about whether running the Get monad can lazily return values or if it always consumes all the input it'll ever need.
Duncan