Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  How to unnest "do" (Martin Drautzburg)
   2. Re:  How to unnest "do" (Ertugrul S?ylemez)
   3. Re:  How to unnest "do" (David McBride)
   4. Re:  How to unnest "do" (Emmanuel Touzery)
   5. Re:  How to unnest "do" (Brent Yorgey)
   6. Re:  How to unnest "do" (Emmanuel Touzery)


----------------------------------------------------------------------

Message: 1
Date: Sun, 27 Jan 2013 18:27:48 +0100
From: Martin Drautzburg <martin.drautzb...@web.de>
Subject: [Haskell-beginners] How to unnest "do"
To: beginners@haskell.org
Message-ID: <201301271827.48843.martin.drautzb...@web.de>
Content-Type: text/plain;  charset="us-ascii"

Hello all,

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"






------------------------------

Message: 2
Date: Sun, 27 Jan 2013 20:43:58 +0100
From: Ertugrul S?ylemez <e...@ertes.de>
Subject: Re: [Haskell-beginners] How to unnest "do"
To: beginners@haskell.org
Message-ID: <20130127204358.4d65d...@tritium.streitmacht.eu>
Content-Type: text/plain; charset="us-ascii"

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.drautzb...@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-0001.pgp>

------------------------------

Message: 3
Date: Sun, 27 Jan 2013 15:06:47 -0500
From: David McBride <toa...@gmail.com>
Subject: Re: [Haskell-beginners] How to unnest "do"
To: beginners@haskell.org
Message-ID:
        <CAN+Tr40r+Y=rqa-phqnorbs0mzrh__rswbkyjbjfh_tovnu...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Here's what I would do.  There's a MaybeT monad in the transormers library
that is pretty good for this sort of stuff.  I might restructure it like
this:

module Main where

import Control.Monad.Trans.Maybe (runMaybeT, MaybeT)
import Control.Monad.Trans (liftIO)
import System.Environment (getArgs)
import Control.Applicative ((<|>))

margs :: MaybeT IO ()
margs = do
  [fname] <- liftIO $ getArgs
  fstr <- liftIO $ readFile fname
  let nWords = length . words $ fstr
      nLines = length . lines $ fstr
      nChars = length fstr
  liftIO . putStrLn . unwords $ [ show nLines, show nWords, show nChars]

mnoargs :: MaybeT IO ()
mnoargs = liftIO $ print "No args"

main = runMaybeT (margs <|> mnoargs)

This exploits the alternative instance of MaybeT.  If the pattern match for
arguments fails, then the whole function returns nothing.  That causes the
alternative to be run instead.  Also since MaybeT has an instance for
MonadIO, you can do any IO you need by using liftIO.

There is also an EitherT type in the errors package that can return *why*
something failed, but I haven't messed with it a ton, so I can't really
give a tutorial.

On Sun, Jan 27, 2013 at 12:27 PM, Martin Drautzburg <
martin.drautzb...@web.de> wrote:

> Hello all,
>
> 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"
>
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20130127/8f9386f9/attachment-0001.htm>

------------------------------

Message: 4
Date: Sun, 27 Jan 2013 21:29:27 +0100
From: Emmanuel Touzery <etouz...@gmail.com>
Subject: Re: [Haskell-beginners] How to unnest "do"
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Message-ID:
        <cac42renujn_m3eeltobbg0t38c2ytrbop9brkvqsrokbkzv...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

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


> 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]
>


I'm sorry, may I ask on which monad here is "sequence" operating?

I can see that sequence here turns [a->a] into a->[a], I'm just not sure
which is the monad at play here... I just need a little bit more
explanation about this code before I get it.

Thank you!

Emmanuel
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20130127/b50928dd/attachment-0001.htm>

------------------------------

Message: 5
Date: Sun, 27 Jan 2013 15:34:05 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] How to unnest "do"
To: beginners@haskell.org
Message-ID: <20130127203405.ga28...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Sun, Jan 27, 2013 at 09:29:27PM +0100, Emmanuel Touzery wrote:
> >     stats :: String -> String
> >     stats =
> >         unwords .
> >         sequence [show . length . words,
> >                   show . length . lines,
> >                   show . length]
> >
> >
> [..]
> 
> 
> > 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]
> >
> 
> 
> I'm sorry, may I ask on which monad here is "sequence" operating?
> 
> I can see that sequence here turns [a->a] into a->[a], I'm just not sure
> which is the monad at play here... I just need a little bit more
> explanation about this code before I get it.

It is the ((->) a)  monad, also known as the reader monad.

-Brent



------------------------------

Message: 6
Date: Sun, 27 Jan 2013 21:46:30 +0100
From: Emmanuel Touzery <etouz...@gmail.com>
Subject: Re: [Haskell-beginners] How to unnest "do"
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Message-ID:
        <CAC42Rem0m+H_U-sc_PjmtJLp0+hk=f8mUk=zuodekxdbbt5...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Thank you. I thought it might be, but it isn't exactly intuitive for me at
this point. I'll read some more about that monad.
On 27 Jan 2013 21:35, "Brent Yorgey" <byor...@seas.upenn.edu> wrote:

> On Sun, Jan 27, 2013 at 09:29:27PM +0100, Emmanuel Touzery wrote:
> > >     stats :: String -> String
> > >     stats =
> > >         unwords .
> > >         sequence [show . length . words,
> > >                   show . length . lines,
> > >                   show . length]
> > >
> > >
> > [..]
> >
> >
> > > 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]
> > >
> >
> >
> > I'm sorry, may I ask on which monad here is "sequence" operating?
> >
> > I can see that sequence here turns [a->a] into a->[a], I'm just not sure
> > which is the monad at play here... I just need a little bit more
> > explanation about this code before I get it.
>
> It is the ((->) a)  monad, also known as the reader monad.
>
> -Brent
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20130127/52823779/attachment.htm>

------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 55, Issue 30
*****************************************

Reply via email to