
On Tue, Sep 15, 2009 at 9:29 PM, Daniel Fischer
Am Dienstag 15 September 2009 21:13:02 schrieb Daniel Fischer:
Still, the body should be read lazily. I'm not sure, but the tracing message may be output because of its position.
With
where readBody = withFile fn ReadMode $ \h -> do b <- hGetContents h seq b $ return (trace ("Read body from: " ++ fn) b)
there's no tracing output.
Yes, tested with -rw-r--r-- 1 me users 243M 15. Sep 21:17 file1.txt -rw-r--r-- 1 me users 243M 15. Sep 21:18 file2.txt
Ok, Daniel, I got the point: the IO action gets performed but there's no need to use unsafePerformIO as hGetContents is already lazy and the IO action is "ineffective" anyway when the result is not needed. Yet, I'm still confused as "seq b" should force the complete execution of hGetContents. So I decided to run a different test: I'm using this code: --- module Main where import System.IO import System.IO.Unsafe import Control.Applicative import Data.List import Data.Ord import Debug.Trace data Bit = Bit { index :: Integer, body :: String } readBit fn = withFile fn ReadMode $ \h -> Bit <$> (hGetLine h >>= return . read) <*> readBody where readBody = trace "In readBody" $ withFile fn ReadMode $ \h -> do b <- hGetContents h seq b $ return $ trace ("Read body from: " ++ fn) b main = do bl <- mapM readBit ["file1.txt","file2.txt"] mapM_ (putStrLn . show . index) $ sortBy (comparing index) bl putStrLn $ body $ head bl ---- (Hope this looks better than before). I ran this on a 115KB-long file1.txt file and traced with dtruss (OSX strace equivalent). You know what? Only the first 1024 bytes of file1.txt are read and actually displayed. So, it seems that "seq b" is completely ineffective and program is not correct. Cristiano