Lazy streams and unsafeInterleaveIO
Remi Turk
remi.turk@wanadoo.nl
Tue, 24 Dec 2002 19:09:53 +0100
On Mon, Dec 23, 2002 at 09:05:00AM +0000, Glynn Clements wrote:
> Jyrinx wrote:
> > So is this lazy-stream-via-unsafeInterleaveIO not so nasty, then, so
> > long as a few precautions (not reading too far into the stream,
> > accounting for buffering, etc.) are taken? I like the idiom Hudak uses
> > (passing a stream of I/O results to the purely functional part of the
> > program), so if it's kosher enough I'd like to get hacking elsewhere ...
>
> It depends upon the amount and the complexity of the program's I/O,
> and the degree of control which you require. For a simple stream
> filter (read stdin, write stdout), lazy I/O is fine; for a program
> which has more complex I/O behaviour, lazy I/O may become a nuisance
> as the program grows more complex or as you need finer control.
Hi,
just for fun I wrote a slightly-enhanced version of my previous one-liner ;o)
It needs to be compiled with GHC's "-package util" as it uses GNU Readline.
I guess it demonstrates why lazy io may not always be a good idea when doing
more complex things with IO.
Happy hacking,
Remi
P.S. Have fun with forward-references as program-input ;-D
P.P.S. GNU Readline implements history-functions itself of
course. Who talked about reinventing the wheel? :D
module Main where
import Monad (liftM, zipWithM_)
import Maybe (catMaybes, isJust)
import Readline (readline)
import System.IO.Unsafe (unsafeInterleaveIO)
-- Like the prelude-function sequence, but lazy
lazySequenceIO :: [IO a] -> IO [a]
lazySequenceIO [] = return []
lazySequenceIO (p:ps) = do
x <- unsafeInterleaveIO p
unsafeInterleaveIO $ liftM (x:) (lazySequenceIO ps)
{- Given a list of prompts, read lines with GNU Readline until
either we've had all prompts or the users presses ^D -}
readLines :: [String] -> IO [String]
readLines = liftM (catMaybes . takeWhile isJust)
. lazySequenceIO . map (unsafeInterleaveIO . readline)
main = do
putStrLn "N Add the number N"
putStrLn "<enter> Again"
putStrLn "!N Repeat input N"
putStrLn "?N Enter result N as input"
input <- readLines $ map (\n -> show n ++ "> ") [0..]
let output = scanl1 (+) $ zipWith (parse input output)
[0..] input
zipWithM_ printRes [0..] output
where
printResult :: Integer -> Integer -> IO ()
printResult nr res = putStrLn $ show nr ++ ": " ++ show res
parse :: [String] -> [Integer] -> Int -> String -> Integer
parse input output nr s
= let p nr s
-- last number again
| null s = p (nr-1) (input !! nr)
-- repeat input N
| head s == '!' = let index = read (tail s)
in p index (input !! index)
-- enter result N
| head s == '?' = let index = read (tail s)
in output !! index
-- just a number
| otherwise = read s
in p nr s
--
Diese Augen haben es gesehen
Doch diese Augen schliessen sich
Und ungehindert fliesst das Blut
Und das Schweigen wird unerträglich laut