
As an experiment for a bigger project, I cooked up a simple program: It asks for integers interactively, and after each input, it spits out the running total. The wrinkle is that the function for calculating the total should be a non-monadic stream function (that is, type [Integer] -> [Integer] so that runningTotals [1,2,3,4,5] == [1,3,6,10,15]). The task is then to write a function to return a stream of integers, grabbing them from IO-land lazily (a la getContents). My first attempts had it not displaying a running total until all input (terminated by an input of 0) had finished, at which point it spit out all the totals (i.e. it wasn't an interactive program anymore). I poked around in the docs and on the Web for a while, and found out about unsafeInterleaveIO, which solved the problem neatly (after I modified runningTotals to be less eager, as it was reading ahead by an extra integer each time). I ended up with the attached code (for GHC 5.04.2). My question is this: Is there a more elegant (i.e. non-"unsafe") way to do this? I vaguely recall from the Hudak book (which I unfortunately don't have convenient at the moment) that he used a channel for something like this (the interactive graphics stuff), but IIRC his system would be overkill for my application (including the bigger project). It doesn't seem like it should need any black magic, and concurrency (which channels need, right?) doesn't appear worth the hassle. Really, my desire comes down to a simple, safe, single-threaded way to write a function to generate a lazy stream. Is there such? Luke Maurer jyrinx_list@mindspring.com -- running-total -- Haskell program that takes integers as input, outputting a running total -- after each input -- Demonstrates use of lazy streams module Main where import IO import System.IO.Unsafe import Monad runningTotals :: [Integer] -> [Integer] runningTotals [] = [] runningTotals (x:xs) = rt' 0 (x:xs) where rt' tot (x:xs) = (tot+x) `seq` (tot+x):(rt' (tot+x) xs) rt' _ [] = [] -- Note that runningTotals does what appears to be a stateful calculation when -- numbers are read one at a time; however, lazy streams allow this to be a -- pure function. Haskell is cool. inputNumbers :: IO [Integer] inputNumbers = do x <- putStr "? " >> readLn if x == 0 then return [] else do xs <- (unsafeInterleaveIO inputNumbers) return (x:xs) main = do numbers <- inputNumbers mapM_ (putStrLn . (flip shows) "") (runningTotals numbers)

On Sun, Dec 22, 2002 at 04:00:45AM -0800, Jyrinx wrote:
As an experiment for a bigger project, I cooked up a simple program: It asks for integers interactively, and after each input, it spits out the running total. The wrinkle is that the function for calculating the total should be a non-monadic stream function (that is, type [Integer] -> [Integer] so that runningTotals [1,2,3,4,5] == [1,3,6,10,15]). The task is then to write a function to return a stream of integers, grabbing them from IO-land lazily (a la getContents).
Hi, what about module Main where main = getContents >>= mapM_ print . scanl1 (+) . map read . lines Happy hacking, Remi -- Diese Augen haben es gesehen Doch diese Augen schliessen sich Und ungehindert fliesst das Blut Und das Schweigen wird unertr�glich laut

Remi Turk wrote:
On Sun, Dec 22, 2002 at 04:00:45AM -0800, Jyrinx wrote:
As an experiment for a bigger project, I cooked up a simple program: It asks for integers interactively, and after each input, it spits out the running total. The wrinkle is that the function for calculating the total should be a non-monadic stream function (that is, type [Integer] -> [Integer] so that runningTotals [1,2,3,4,5] == [1,3,6,10,15]). The task is then to write a function to return a stream of integers, grabbing them from IO-land lazily (a la getContents).
Hi, what about
module Main where
main = getContents >>= mapM_ print . scanl1 (+) . map read . lines
Ooh, neat! :-) (I love these one-liners - Haskell is absurdly concise :-D ) Hrm ... wasn't aware of the scanl1 thingie; looks like I reinvented the wheel a little ... (Come to think of it, is there any sort of handy quick-reference card for all these combinators? Seems like I and other novices could stand to save some typing ...) One sticking point, though (and this is relevant to the bigger project): I'd like to print a prompt somehow before each input, which I'm not sure is possible if I just slurp up everything from getContents ... I've thought of using interact somehow, but I'm not sure where I'd start with that one ... (Out of curiosity: How is the compiler deciding on a type for the input? (That is, how does it know we want integers? Is it just a default?) Looks to me like all it can infer is that it's of classes Read, Show, and Num ... that doesn't much narrow things down ...) BTW, I already found a major problem with the code I attached earlier, using unsafeInterleaveIO: Run in GHCi (as I had done), it works fine; but compiled by GHC and run as an executable, it waits for input and *then* displays the prompt after the user hits Enter ... not very helpful. I didn't think it would do that, since (putStr "? " >> readLn) seemed pretty explicit as to order of evaluation, but I guess that's what I get for breaking referential transparency ... Luke Maurer jyrinx_list@mindspring.com

BTW, I already found a major problem with the code I attached earlier, using unsafeInterleaveIO: Run in GHCi (as I had done), it works fine; but compiled by GHC and run as an executable, it waits for input and *then* displays the prompt after the user hits Enter ... not very helpful. I didn't think it would do that, since (putStr "? " >> readLn) seemed pretty explicit as to order of evaluation, but I guess that's what I get for breaking referential transparency ...
You probably want to set the buffering otherwise. GHCi automatically sets the buffering to nobuffering when it starts, so this probably explains why you don't experience the problem in GHCi. Import IO and do something like: hSetBuffering stdout NoBuffering -- or LineBuffering hSetBuffering stdin NoBuffering ...something like that... HTH - Hal

Hal Daume III wrote:
BTW, I already found a major problem with the code I attached earlier, using unsafeInterleaveIO: Run in GHCi (as I had done), it works fine; but compiled by GHC and run as an executable, it waits for input and *then* displays the prompt after the user hits Enter ... not very helpful. I didn't think it would do that, since (putStr "? " >> readLn) seemed pretty explicit as to order of evaluation, but I guess that's what I get for breaking referential transparency ...
You probably want to set the buffering otherwise. [...]
Ah, you're right ... I changed (putStr "? " >> readLn) to (putStr "? "
hFlush stdout >> readLn) and it worked.
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 ... Luke Maurer jyrinx_list@mindspring.com

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.
If you just wanted a getContents replacement with a prompt, the
obvious solution would be to use unsafeInterleaveIO just to implement
that specific function.
The main problems with lazy I/O are the lack of control over ordering
(e.g. you can't delete the file until a stream has been closed, but
you may not be able to control how long the stream remains open), and
the inability to handle exceptions (the actual exception won't occur
until after e.g. getContents has returned).
--
Glynn Clements

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.
If you just wanted a getContents replacement with a prompt, the obvious solution would be to use unsafeInterleaveIO just to implement that specific function.
Well, yeah - but I don't want to get into the habit of using the unsafe*IO stuff when it just seems convenient. This way, I know specifically why I need it, and can encapsulate its use in a small library with predictable results (i.e. I can separate concerns).
The main problems with lazy I/O are the lack of control over ordering (e.g. you can't delete the file until a stream has been closed, but you may not be able to control how long the stream remains open) [...]
Wait ... but the Library Report (11.2.1) says that, after a call to hGetContents (which I assume getContents is based on), the file is "semi-closed," and a call to hClose will indeed then close it ...
[...] and the inability to handle exceptions (the actual exception won't occur until after e.g. getContents has returned).
But how does this differ from strict I/O? I mean, say there's a disk error in the middle of some big file I want to crunch. Under traditional I/O, I open the file and proceed to read each piece of data, process it, and continue to the next one, reading the raw data only as I need it. When I hit the error, an exception will be thrown in the middle of the operation. In lazy I/O, I might use getContents to get all the characters lazily; the getContents call will read each piece of data as it's needed in the operation - in other words, the data is read as the program uses it, just like with traditional I/O. And when the error occurs, the operation will be unceremoniously interrupted, again the same as by strict I/O. In mean, if an exception is thrown because of a file error, I can't hope to catch it in the data-crunching part of the program anyway ... Luke Maurer jyrinx_list@mindspring.com

Jyrinx wrote:
[...] and the inability to handle exceptions (the actual exception won't occur until after e.g. getContents has returned).
But how does this differ from strict I/O? I mean, say there's a disk error in the middle of some big file I want to crunch. Under traditional I/O, I open the file and proceed to read each piece of data, process it, and continue to the next one, reading the raw data only as I need it. When I hit the error, an exception will be thrown in the middle of the operation. In lazy I/O, I might use getContents to get all the characters lazily; the getContents call will read each piece of data as it's needed in the operation - in other words, the data is read as the program uses it, just like with traditional I/O. And when the error occurs, the operation will be unceremoniously interrupted, again the same as by strict I/O. In mean, if an exception is thrown because of a file error, I can't hope to catch it in the data-crunching part of the program anyway ...
No, but with strict I/O, you are bound to be "within" the IO monad
when the exception is thrown, so you *can* catch it.
If you are just going to allow all exceptions to be fatal, and don't
need any control over I/O ordering, you may as well just use lazy I/O.
However, if you are writing real software as opposed to just toy
programs, you have to handle exceptions; e.g. a web browser which died
every time that a server refused a connection wouldn't be of much use.
--
Glynn Clements

Glynn Clements wrote:
Jyrinx wrote:
[...] and the inability to handle exceptions (the actual exception won't occur until after e.g. getContents has returned).
But how does this differ from strict I/O? I mean, say there's a disk error in the middle of some big file I want to crunch. Under traditional I/O, I open the file and proceed to read each piece of data, process it, and continue to the next one, reading the raw data only as I need it. When I hit the error, an exception will be thrown in the middle of the operation. In lazy I/O, I might use getContents to get all the characters lazily; the getContents call will read each piece of data as it's needed in the operation - in other words, the data is read as the program uses it, just like with traditional I/O. And when the error occurs, the operation will be unceremoniously interrupted, again the same as by strict I/O. In mean, if an exception is thrown because of a file error, I can't hope to catch it in the data-crunching part of the program anyway ...
No, but with strict I/O, you are bound to be "within" the IO monad when the exception is thrown, so you *can* catch it.
If you are just going to allow all exceptions to be fatal, and don't need any control over I/O ordering, you may as well just use lazy I/O. However, if you are writing real software as opposed to just toy programs, you have to handle exceptions; e.g. a web browser which died every time that a server refused a connection wouldn't be of much use.
Sure - and that's why I don't do *everything* in purely-functional-land. I suppose what I'm going for is separation of concerns: Anything with any business catching exceptions should be in the IO monad; calculations, transformations, etc., which depend on such a continuous stream of data couldn't deal with the exception if I wanted them to, but the IO code that invokes them can. In the Web browser example, I imagine (and this is off the top of my head) that a major functional part of the program would be a function that takes a bunch of HTML (presumably passed as a lazy stream from a server, achieved in the IO monad), processes it, and renders a bunch of graphical data for the screen (of which IO code could control the display). If a connection is refused, IO code catches the error before it can pass the stream to the rendering function; if a connection is cut off or something, the rendering code can't deal with that, and the exception gets caught back in I/O-land. Luke Maurer jyrinx_list@mindspring.com

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

On Mon, Dec 23, 2002 at 09:05:00AM +0000, Glynn Clements wrote:
The main problems with lazy I/O are the lack of control over ordering (e.g. you can't delete the file until a stream has been closed, but you may not be able to control how long the stream remains open), and the inability to handle exceptions (the actual exception won't occur until after e.g. getContents has returned).
For my purposes it suffices to have a notion of when I'm done generating output from the input stream and I close the handle then. I basically just pass around the input file handles in perpetuity and either don't close them until the last minute, as it's important to clean up so I can reuse the action later, or until I'm done generating output from a complete scan of the thing. This forces the evaluation of the data structures created from the input, which may linger around longer than the input stream itself. Basically, I don't have these issues. Actually, you -should- be able to delete the file before the stream has been closed; this is a common idiom for dealing with temporary files. Bill

On Sunday, December 22, 2002, at 04:00 AM, Jyrinx wrote:
As an experiment for a bigger project, I cooked up a simple program: It asks for integers interactively, and after each input, it spits out the running total. The wrinkle is that the function for calculating the total should be a non-monadic stream function (that is, type [Integer] -> [Integer] so that runningTotals [1,2,3,4,5] == [1,3,6,10,15]). The task is then to write a function to return a stream of integers, grabbing them from IO-land lazily (a la getContents).
My first attempts had it not displaying a running total until all input (terminated by an input of 0) had finished, at which point it spit out all the totals (i.e. it wasn't an interactive program anymore). I poked around in the docs and on the Web for a while, and found out about unsafeInterleaveIO, which solved the problem neatly (after I modified runningTotals to be less eager, as it was reading ahead by an extra integer each time). I ended up with the attached code (for GHC 5.04.2).
My question is this: Is there a more elegant (i.e. non-"unsafe") way to do this? I vaguely recall from the Hudak book (which I unfortunately don't have convenient at the moment) that he used a channel for something like this (the interactive graphics stuff), but IIRC his system would be overkill for my application (including the bigger project). It doesn't seem like it should need any black magic, and concurrency (which channels need, right?) doesn't appear worth the hassle. Really, my desire comes down to a simple, safe, single-threaded way to write a function to generate a lazy stream. Is there such?
Luke Maurer jyrinx_list@mindspring.com -- running-total -- Haskell program that takes integers as input, outputting a running total -- after each input -- Demonstrates use of lazy streams
module Main where
import IO import System.IO.Unsafe import Monad
runningTotals :: [Integer] -> [Integer] runningTotals [] = [] runningTotals (x:xs) = rt' 0 (x:xs) where rt' tot (x:xs) = (tot+x) `seq` (tot+x):(rt' (tot+x) xs) rt' _ [] = []
-- Note that runningTotals does what appears to be a stateful calculation when -- numbers are read one at a time; however, lazy streams allow this to be a -- pure function. Haskell is cool.
inputNumbers :: IO [Integer] inputNumbers = do x <- putStr "? " >> readLn if x == 0 then return [] else do xs <- (unsafeInterleaveIO inputNumbers) return (x:xs)
main = do numbers <- inputNumbers mapM_ (putStrLn . (flip shows) "") (runningTotals numbers)
Below, is another solution to the problem you described (sorry for the rather late reply). If you are curious how I 'invented' the solution (program), please let me know. Many people dazzle us by providing the final program, but say little about the process they used to arrive at that particular program/solution. With this problem, I used a particular formal method to arrive at the program. The method also helps to ensure program correctness. I tested the program using ghc and ghci. With the following source code contained in file "runningTotal.hs", I compiled and tested using ghc, by entering on the shell command line (the prompt on my computer is "richard%"): richard% ghc --make runningTotal.hs -o runningTotal richard% ./runningTotal With ghci, I performed the following two steps: richard% ghci runningTotal.hs Prelude Main> main Note: Although the program shown below borrows from Simon Thompson's book, "Haskell: The Craft of Functional Programming", Second Edition (see page 394), one can still methodically 'derive' the program, which I did. That is, one can still ask the question, "How did Prof. Thompson arrive at his solution for a similar problem he describes (page 394)?" ----------runningTotal.hs begins here---------- module Main where import IO getInt :: IO Int getInt = do putStr "Enter an integer: " line <- getLine return (read line :: Int) sumInts :: Int -> IO Int sumInts t = do n <- getInt if n==0 then return t else do putStr "? " print (n+t) sumInts (n+t) main :: IO () main = do hSetBuffering stdout NoBuffering -- or LineBuffering hSetBuffering stdin NoBuffering putStrLn "Enter integers one per line (entering zero terminates the program)" putStrLn "After entering an integer, the running total will be displayed preceded by a '? '." putStrLn "" sum <- sumInts 0 -- start out with the total initialized to zero putStr "The final total was " print sum ----------runningTotal.hs ends here---------- Sincerely, Richard E. Adams Email: radams@iglide.net
participants (6)
-
Glynn Clements
-
Hal Daume III
-
Jyrinx
-
Remi Turk
-
Richard E.Adams
-
William Lee Irwin III