[Newbie] Streams and IO

Christian Hofer christian.hofer@gmx.de
Sun, 10 Aug 2003 19:08:59 +0200


Hello,

I am completely new to functional programming, am just reading through 
SOE (great book so far!) and try to understand streams in 
client-server-interactions. Therefore I wrote the following program 
(which has nothing to do with the book exercises), which is intended to 
read integers from stdin and to write the sum of the inputs so far to 
stdout.

When I start it (in Hugs), I can enter numbers, but don't get back the 
sum, but every second time a zero, every forth time the value I just 
entered and every forth time the sum of the two values I entered the latest.

Could s.o. explain me, what is going wrong? I can't figure out, what is 
happening here. (I know that there are easier solutions to the problem 
than using streams, but the latter was my intention for learning.)

Thanks,
Christian

module Main where

main = sequence reqs
	
type Request = IO Int
type Response = IO Int

reqs :: [Request]
reqs = client resps
resps :: [Response]
resps = server reqs

client :: [Response] -> [Request]
client (y:ys) = (do toPrint <- y
                     putStr ("So far: " ++ show toPrint ++ "\nEnter 
number: ")
                     line <- getLine
                     return (parseToInt line)) : client ys

server :: [Request] -> [Response]
server = scanl helper (return 0)
         where helper :: IO Int -> IO Int -> IO Int
	      helper sofar x = do a <- x
	                          sf <- sofar
	                          return (a + sf)

parseToInt :: String -> Int
parseToInt str = foldl nextDigit 0 (intList str)
    where intList :: String -> [Int]
	 -- only for positive numbers so far	
	 intList = map (\x -> fromEnum x - 48)
	 nextDigit :: Int -> Int -> Int
	 nextDigit a b = a * 10 + b