
On 12 Sep 2003 22:08:30 -0000 kuq32tr02@sneakemail.com wrote:
Hello,
I'm starting to use Haskell for writing actual programs using monads and I'm already lost.
I have the following script:
#!/usr/bin/runhugs
module Main where import System(getArgs) main = do putStr "Hello, World\n" strs <- getArgs map putStrLn strs
Which gives the following error:
runhugs: Error occurred Reading file "./mailalias.lhs": Reading file "/usr/lib/hugs/lib/System.hs": Reading file "./mailalias.lhs": Type checking ERROR "./mailalias.lhs":5 - Type error in final generator *** Term : map putStrLn strs *** Type : [IO ()] *** Does not match : IO a
Can someone please explain what I'm doing wrong?
map :: (a -> b) -> [a] -> [b] putStrLn :: String -> IO () therefore map putStrLn :: [String] -> [IO ()] map maps a -pure function- over a list. What you want is to map a -monadic computation- over the list, further you don't care about the result. mapM_ :: Monad m => (a -> m b) -> [a] -> m () mapM_ putStrLn :: [String] -> IO ()