[Haskell-beginners] How to unnest "do"

Ertugrul Söylemez es at ertes.de
Sun Jan 27 20:43:58 CET 2013


Hi there Martin,

since the nested 'do' makes sense, there is little you can do about it.
However, you can make the code more beautiful and restructure it a bit.
This is how I would have written it:

    import Control.Applicative
    import System.Environment
    import System.IO

    stats :: String -> String
    stats =
        unwords .
        sequence [show . length . words,
                  show . length . lines,
                  show . length]

    main :: IO ()
    main = do
        args <- getArgs
        case args of
          [fn] -> fmap stats (readFile fn) >>= putStrLn
          _    -> hPutStrLn stderr "Usage: wc FNAME"

This improves the statistics code slightly, but uses some monadic
machinery you may not be familiar with.  Another way to read the 'stats'
function is this:

    stats :: String -> String
    stats str =
        unwords [show . length . words $ str,
                 show . length . lines $ str,
                 show . length $ str]

Finally you can improve the command line argument processing itself
simply by being more sensible about what makes a valid command line:

    main =
        getArgs >>=
        mapM_ (fmap stats . readFile >=> putStrLn)

Instead of expecting exactly one command line argument you print the
counts for every argument.  That means, if there are no arguments, you
print no counts.  This makes more sense than the highhanded "I want
exactly one argument, otherwise I won't work" syntax, because now your
whole program forms a homomorphism (shell syntax):

    `prog x` `prog y` = `prog x y`

This allows reasoning and optimization.


Greets,
Ertugrul


Martin Drautzburg <Martin.Drautzburg at web.de> wrote:

> in the code snippet below, is there a way to factor out the second
> "do"?
>
> import System (getArgs)
> main :: IO ()
> main = do
>         args <- getArgs
>         case args of
>                 [fname] ->  do fstr <- readFile fname
>                                let nWords = length . words $ fstr
>                                    nLines = length . lines $ fstr
>                                    nChars = length fstr
>                                putStrLn . unwords $ [ show nLines
>                                              , show nWords
>                                              , show nChars
>                                              , fname]
>                 _ ->putStrLn "usage: wc fname"

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 836 bytes
Desc: not available
URL: <http://www.haskell.org/pipermail/beginners/attachments/20130127/f7505ede/attachment.pgp>


More information about the Beginners mailing list