
Hi all, There's a common little situation I keep bumping up against. I don't understand where I'm going wrong, so I've made a little example. It's to do with binding a result to a variable name using "<-". This code works fine: ---------------------------------------------- module Main where import System.Directory (getDirectoryContents) main = do dc <- getDirectoryContents "./foo/" mapM_ putStrLn dc ---------------------------------------------- But if I try to avoid the use of the bind to "dc", I fail: ---------------------------------------------- mapM_ putStrLn (getDirectoryContents "./foo/") ---------------------------------------------- I've tried using map instead of mapM_, and inserted "return"s here and there, but no luck. Can anyone tell me where and why I'm going wrong? The error message is below. Cheers, Paul Couldn't match expected type `[String]' against inferred type `IO [FilePath]' In the second argument of `mapM_', namely `(getDirectoryContents "./foo/")' In the expression: mapM_ putStrLn (getDirectoryContents "./foo/") In the definition of `main': main = mapM_ putStrLn (getDirectoryContents "./foo/")

Hi
You can translate this step by step.
main = do dc <- getDirectoryContents "./foo/"
mapM_ putStrLn dc
Translating out the do notation
(http://www.haskell.org/haskellwiki/Keywords#do):
main = getDirectoryContents >>= \dc ->
mapM_ putStrLn dc
Then we can chop out the dc argument, as its \x -> .... x, and can be
removed (eta reduction):
main = getDirectoryContents >>=
mapM_ putStrLn
And finally we just remove the newline:
main = getDirectoryContents >>= mapM_ putStrLn
Alternatively, we can flip the >>= for =<< and write:
main = mapM_ putStrLn =<< getDirectoryContents
This is now one line, and mirrors how you would write the function if it
was pure using function composition.
Thanks
Neil
This material is sales and trading commentary and does not constitute
investment research. Please follow the attached hyperlink to an
important disclaimer

main = do dc <- getDirectoryContents "./foo/" mapM_ putStrLn dc
Translating out the do notation (http://www.haskell.org/haskellwiki/Keywords#do):
main = getDirectoryContents >>= \dc -> mapM_ putStrLn dc
Woops, I lost "./foo/" here, but it should be fairly easy to insert through the remaining translations. Thanks Neil ============================================================================== Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html ==============================================================================

Hello Neil, Thursday, October 2, 2008, 7:26:23 PM, you wrote: shortly speaking, getDirectoryContents is an action (having "IO a" type) while second mapM_ argument should be a value returned by this action. by using dc variable or >>= operator, you can evaluate action and pass its result to mapM_. of course, after imperative languages experience, it's hard to see difference. take look at http://haskell.org/haskellwiki/IO_inside
Hi
You can translate this step by step.
main = do dc <- getDirectoryContents "./foo/" mapM_ putStrLn dc
Translating out the do notation (http://www.haskell.org/haskellwiki/Keywords#do):
main = getDirectoryContents >>= \dc -> mapM_ putStrLn dc
Then we can chop out the dc argument, as its \x -> .... x, and can be removed (eta reduction):
main = getDirectoryContents >>= mapM_ putStrLn
And finally we just remove the newline:
main = getDirectoryContents >>= mapM_ putStrLn
Alternatively, we can flip the >>= for =<< and write:
main = mapM_ putStrLn =<< getDirectoryContents
This is now one line, and mirrors how you would write the function if it was pure using function composition.
Thanks
Neil
This material is sales and trading commentary and does not constitute investment research. Please follow the attached hyperlink to an important disclaimer
outbind://31/www.credit-suisse.com/emea/legal >
________________________________
From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Paul Keir Sent: 02 October 2008 4:20 pm To: haskell-cafe@haskell.org Subject: [Haskell-cafe] One liner?
Hi all,
There's a common little situation I keep bumping up against. I don't understand where I'm going wrong, so I've made a little example. It's to do with binding a result to a variable name using "<-". This code works fine:
---------------------------------------------- module Main where
import System.Directory (getDirectoryContents)
main = do dc <- getDirectoryContents "./foo/" mapM_ putStrLn dc ----------------------------------------------
But if I try to avoid the use of the bind to "dc", I fail:
---------------------------------------------- mapM_ putStrLn (getDirectoryContents "./foo/") ----------------------------------------------
I've tried using map instead of mapM_, and inserted "return"s here and there, but no luck. Can anyone tell me where and why I'm going wrong? The error message is below.
Cheers, Paul
Couldn't match expected type `[String]' against inferred type `IO [FilePath]' In the second argument of `mapM_', namely `(getDirectoryContents "./foo/")' In the expression: mapM_ putStrLn (getDirectoryContents "./foo/") In the definition of `main': main = mapM_ putStrLn (getDirectoryContents "./foo/")
============================================================================== Please access the attached hyperlink for an important electronic communications disclaimer:
http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html ==============================================================================
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Thanks, and to Ketil too. I did see past the missing "./foo/". That's certainly a solution I'm happy with, and I didn't know the term eta reduction, so thanks for that too.
Paul
-----Original Message-----
From: Mitchell, Neil [mailto:neil.mitchell.2@credit-suisse.com]
Sent: Thu 02/10/2008 16:26
To: Paul Keir; haskell-cafe@haskell.org
Subject: RE: [Haskell-cafe] One liner?
Hi
You can translate this step by step.
main = do dc <- getDirectoryContents "./foo/"
mapM_ putStrLn dc
Translating out the do notation
(http://www.haskell.org/haskellwiki/Keywords#do):
main = getDirectoryContents >>= \dc ->
mapM_ putStrLn dc
Then we can chop out the dc argument, as its \x -> .... x, and can be
removed (eta reduction):
main = getDirectoryContents >>=
mapM_ putStrLn
And finally we just remove the newline:
main = getDirectoryContents >>= mapM_ putStrLn
Alternatively, we can flip the >>= for =<< and write:
main = mapM_ putStrLn =<< getDirectoryContents
This is now one line, and mirrors how you would write the function if it
was pure using function composition.
Thanks
Neil
This material is sales and trading commentary and does not constitute
investment research. Please follow the attached hyperlink to an
important disclaimer

"Paul Keir"
module Main where
import System.Directory (getDirectoryContents)
main = do dc <- getDirectoryContents "./foo/" mapM_ putStrLn dc
mapM_ putStrLn (getDirectoryContents "./foo/")
Couldn't match expected type `[String]'
"mapM_ putStrLn" needs a "[String]" as an argument,
against inferred type `IO [FilePath]'
but you try to give it an "IO [FilePath]" (i.e. IO [String]). As you probably know, do-notation is syntactic sugar for the monad operators, and you can rewrite your function thusly: main = do dc <- getDirectoryContents "./foo/" mapM_ putStrLn dc => main = getDirectoryContents "./foo" >>= \dc -> mapM_ putStrLn dc => main = getDirectoryContents "./foo" >>= mapM_ putStrLn -k -- If I haven't seen further, it is by standing in the footprints of giants
participants (4)
-
Bulat Ziganshin
-
Ketil Malde
-
Mitchell, Neil
-
Paul Keir