[Haskell-cafe] One liner?

Ketil Malde ketil at malde.org
Thu Oct 2 11:35:13 EDT 2008


"Paul Keir" <pkeir at dcs.gla.ac.uk> writes:

> 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


More information about the Haskell-Cafe mailing list