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
[EMAIL PROTECTED]
-- 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: [EMAIL PROTECTED]

_______________________________________________
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Reply via email to