[Haskell-cafe] Lazier I/O?
Dimitry Golubovsky
dimitry at golubovsky.org
Mon Nov 28 07:27:44 EST 2005
This may be a stupud question, but how to make I/O in Haskell really lazy?
Here is a simple program:
====
module Main where
import System.IO
import Foreign
import Data.Word
import Data.Char
s2c :: String -> [Word8]
s2c s = map (fromIntegral . ord) s
sendstr :: Handle -> String -> IO Int
sendstr h s = do
let c = s2c s
ln = length c
allocaBytes ln $ \buf -> do
pokeArray buf c
hPutBuf h buf ln
return ln
main = do
hSetBuffering stdout NoBuffering
l1 <- sendstr stdout "abcde\n"
l2 <- sendstr stdout "defghij\n"
putStrLn $ "sent " ++ (show l2) ++ " bytes"
putStrLn $ "sent " ++ (show l1) ++ " bytes"
====
It prints:
abcde
defghij
sent 8 bytes
sent 6 bytes
i. e. the first string is output first although the result from that
output (how many bytes sent) is needed second.
What is desired is to have the IO actions perform as their results are
needed. I am assuming some knowledge that those actions have only
limited scope of side effects (e. g. order of outputs within a window is
significant, but order of appearance of those windows on the screen may
not be). I see some way to do this by writing regular non-monadic
Haskell stuff, representing each side effects scope (i. e. where
ordering of actions is necessary) with its own instance of an I/O like
monad (but runnable from an outside non-monadic code), and then using
unsafePerformIO as needed. But there may be some framework already
developed (albeit with unsafePerformIO, but hiding it from application
developers).
Any ideas, pointers?
Thanks
Dimitry
More information about the Haskell-Cafe
mailing list