On 6/20/06, Taro Ikai <[EMAIL PROTECTED]> wrote:
Here's a code fragment I have from working with Hal Daume's "Yet Another
Haskell Tutorial". I cannot figure out how to iterate over the result
from askForNumbers that returns "IO [Integer]", and print them.

The "<-" operator seems to take IO off of the results from actions like
getContents, which returns type "IO String", but I cannot seem to use it
to take IO off of lists with it. What am I supposed to do?

Also, as a side question, what should I be returning from the do function?

>>>code>>>>

module Main
    where

import IO

main = do
  hSetBuffering stdin LineBuffering
  s <- askForNumbers   {-- This compiles --}
  map show s           {-- But this doesn't. Why? --}

s is a list of numbers, "map show s" is a list of Strings. It is not
an IO [Strings] so you can't use it like an action.
Think about what you're trying to do here, you map "show" on a list of
ints, but what do you do with the result? Nothing. Why would you
*want* the above to compile? It would just convert a bunch of numbers
into strings and then forget about them!
So what you want is probably something like:

let xs = map show s

The rule of thumb is, "use 'let' for regular values, and (<-) for actions".

If you want to print all of them you could do something like:

printList [] = return ()
printList (x:xs) = do putStrLn x
                            printList xs

On the other hand, this operation seems generally useful, so why not
generalise it a bit?

mapAction [] = return ()
mapAction a (x:xs) = do a x
                                   mapAction a xs


And in fact, this function already exists! It's called mapM_ (the M is
for Monad).
You could use this by passing in "putStrLn" as the action to this function.

/S
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to