
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"

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

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

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

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

Hi Emmanuel, On Sun, Jan 27, 2013 at 09:46:30PM +0100, Emmanuel Touzery wrote:
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.
Sometimes it's hard to tell if Haskell is the most beautiful language or the most abstract nonsense. ;) Let's look at the Monad instance for the function (r -> a): instance Monad ((->) r) where -- return :: a -> (r -> a) return a = \_ -> a -- (>>=) :: (r -> a) -> (a -> r -> b) -> (r -> b) left >>= right = \r -> right (left r) r 'return' creates a function ignoring its argument and just returning 'a'. '>>=' creates a function with the argument 'r'. The function 'left' is called with 'r' and the function 'right' is called with the result of 'left' and 'r'. Now let's look at the 'sequence' function: sequence ms = foldr k (return []) ms where k m ms = do x <- m xs <- ms return (x : xs) It's easier to see what happens if we rewrite 'k': k m ms = m >>= (\x -> (ms >>= \xs -> return (x : xs))) We saw that '>>=' creates a function with one argument, that argument is the String containing the file contents, 'x' is the return value of one "sequenced" function which is combined (:) with the previous ones. At the end we have the function (String -> [String]). Greetings, Daniel

Sometimes it's hard to tell if Haskell is the most beautiful language or the most abstract nonsense. ;)
Amen. ;-)
Let's look at the Monad instance for the function (r -> a):
instance Monad ((->) r) where -- return :: a -> (r -> a) return a = \_ -> a
-- (>>=) :: (r -> a) -> (a -> r -> b) -> (r -> b) left >>= right = \r -> right (left r) r
'return' creates a function ignoring its argument and just returning 'a'.
'>>=' creates a function with the argument 'r'. The function 'left' is called with 'r' and the function 'right' is called with the result of 'left' and 'r'.
Now let's look at the 'sequence' function:
sequence ms = foldr k (return []) ms where k m ms = do x <- m xs <- ms return (x : xs)
It's easier to see what happens if we rewrite 'k':
k m ms = m >>= (\x -> (ms >>= \xs -> return (x : xs)))
We saw that '>>=' creates a function with one argument, that argument is the String containing the file contents, 'x' is the return value of one "sequenced" function which is combined (:) with the previous ones.
At the end we have the function (String -> [String]).
I will look at this more in depth this week-end, really thank you for the heads up! This stuff is really a bit crazy, but somehow I still like it ;-) Emmanuel

On Sunday, 27. January 2013 20:43:58 Ertugrul Söylemez wrote:
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.
Thanks, this looks much nicer and is very inspiring. But let me see if I get this correctly: readFile fn returns IO String I cannot see the String itself, but I can map the stats function over it, which gives me anoter IO String. This works, because every Monad is also a functor. Another way of looking at this is that fmap lifts the String->String function "stats" to (IO String) -> (IO String), Again I cannot see the String inside the IO String, but I can pass it to a function String->IO String, using (>>=) and putStrLn is such a function, which also does what I need. I cannot use the same fmap mechanism ("fmap putStrLn"), because putStrLn is already String -> IO String and fmap would lift both sides of "->". I tried to find another way of passing the IO String to putStrLn, but there aren't many options. If I want to use putStrLn, then I need to get the String out of the IO String. AFAICS (>>=) is the only way to do this (other than do notation). In contrast to fmap, (>>=) lifts only the left side. For the hell of it, I tried to replace putStrLn by a String -> Maybe String function. This does not work and it made me realize, that the signature of (>>=) :: m a -> (a-> m b) -> m b demands that the the Monad "m" is the same all the way through, and only its type parameter can change. And the Applicative import is not really needed. Is this about correct? When I have a program, which accesses stdin and stdout and a database, I suppose I will have to do things like this a lot? Sorry for the long post, but I am getting kindof excieted.

On Sun, Jan 27, 2013 at 11:29:18PM +0100, Martin Drautzburg wrote:
On Sunday, 27. January 2013 20:43:58 Ertugrul Söylemez wrote:
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.
Thanks, this looks much nicer and is very inspiring.
But let me see if I get this correctly:
readFile fn returns IO String
I cannot see the String itself, but I can map the stats function over it, which gives me anoter IO String. This works, because every Monad is also a functor. Another way of looking at this is that fmap lifts the String->String function "stats" to (IO String) -> (IO String),
Again I cannot see the String inside the IO String, but I can pass it to a function String->IO String, using (>>=) and putStrLn is such a function, which also does what I need.
I cannot use the same fmap mechanism ("fmap putStrLn"), because putStrLn is already String -> IO String and fmap would lift both sides of "->".
I tried to find another way of passing the IO String to putStrLn, but there aren't many options. If I want to use putStrLn, then I need to get the String out of the IO String. AFAICS (>>=) is the only way to do this (other than do notation). In contrast to fmap, (>>=) lifts only the left side.
For the hell of it, I tried to replace putStrLn by a String -> Maybe String function. This does not work and it made me realize, that the signature of (>>=) :: m a -> (a-> m b) -> m b demands that the the Monad "m" is the same all the way through, and only its type parameter can change.
And the Applicative import is not really needed.
Is this about correct?
That all sounds right to me! -Brent

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.Drautzburg@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

Hello all, here is a Code snipped from a Sound.ALSA.Sequencer example (much has been stripped and this code does not do anything). I just don't seem to get it. Can someone please walk me through it and possibly show ways to avoid the massive nesting. dtz = do SndSeq.withDefault SndSeq.Block $ \h -> do Client.setName (h :: SndSeq.T SndSeq.DuplexMode) "Haskell-Melody" Port.withSimple h "out" (Port.caps [Port.capRead, Port.capSubsRead, Port.capWrite]) (Port.types [Port.typeMidiGeneric, Port.typeApplication]) $ \p -> do Queue.with h $ \q -> do c <- Client.getId h let me = Addr.Cons c p conn <- parseDestArgs h me ["20:0"] Queue.control h q Event.QueueStart Nothing Queue.control h q (Event.QueueTempo (Event.Tempo 10000000)) Nothing return () -- Martin

On Wed, 06 Feb 2013 22:31:05 +0100, Martin Drautzburg
Can someone please walk me through it and possibly show ways to avoid the massive nesting.
dtz = do SndSeq.withDefault SndSeq.Block $ \h -> do Client.setName (h :: SndSeq.T SndSeq.DuplexMode) "Haskell-Melody" Port.withSimple h "out" (Port.caps [Port.capRead, Port.capSubsRead, Port.capWrite]) (Port.types [Port.typeMidiGeneric, Port.typeApplication]) $ \p -> do Queue.with h $ \q -> do c <- Client.getId h let me = Addr.Cons c p conn <- parseDestArgs h me ["20:0"] Queue.control h q Event.QueueStart Nothing Queue.control h q (Event.QueueTempo (Event.Tempo 10000000)) Nothing return ()
I like to divide large functions into several smaller ones: dtz = SndSeq.withDefault SndSeq.Block f1 where f1 h = do Client.setName (h :: SndSeq.T SndSeq.DuplexMode) "Haskell-Melody" Port.withSimple h "out" (Port.caps [Port.capRead, Port.capSubsRead, Port.capWrite]) (Port.types [Port.typeMidiGeneric, Port.typeApplication]) (f2 h) f2 h p = Queue.with h (f3 h p) f3 h p q = do c <- Client.getId h let me = Addr.Cons c p conn <- parseDestArgs h me ["20:0"] Queue.control h q Event.QueueStart Nothing Queue.control h q (Event.QueueTempo (Event.Tempo 10000000)) Nothing return () f1, f2 and f3 might be replaced with more meaningful names. The "return ()" at the end can be removed; such things can be found with hlint[0]. Regards, Henk-Jan van Tuyl [0] http://hackage.haskell.org/package/hlint -- http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming --

On Friday, 8. February 2013 08:26:38 Henk-Jan van Tuyl wrote:
On Wed, 06 Feb 2013 22:31:05 +0100, Martin Drautzburg
wrote: Can someone please walk me through it and possibly show ways to avoid the massive nesting.
dtz = do
SndSeq.withDefault SndSeq.Block $ \h -> do
Client.setName (h :: SndSeq.T SndSeq.DuplexMode) "Haskell-Melody" Port.withSimple h "out"
(Port.caps [Port.capRead, Port.capSubsRead, Port.capWrite]) (Port.types [Port.typeMidiGeneric, Port.typeApplication]) $ \p
-> do
Queue.with h $ \q -> do
c <- Client.getId h let me = Addr.Cons c p conn <- parseDestArgs h me ["20:0"] Queue.control h q Event.QueueStart Nothing Queue.control h q (Event.QueueTempo (Event.Tempo
10000000)) Nothing
return ()
I like to divide large functions into several smaller ones:
dtz = SndSeq.withDefault SndSeq.Block f1 where f1 h = do Client.setName (h :: SndSeq.T SndSeq.DuplexMode) "Haskell-Melody" Port.withSimple h "out" (Port.caps [Port.capRead, Port.capSubsRead, Port.capWrite]) (Port.types [Port.typeMidiGeneric, Port.typeApplication]) (f2 h) f2 h p = Queue.with h (f3 h p) f3 h p q = do c <- Client.getId h let me = Addr.Cons c p conn <- parseDestArgs h me ["20:0"] Queue.control h q Event.QueueStart Nothing Queue.control h q (Event.QueueTempo (Event.Tempo 10000000)) Nothing return ()
I tried to do exactly this and I like it a bit better. But note how those functions get quite a number of parameters. In the nested "do", evertything was in scope. Things get worse, when I try to run something in the innermost "do". When I use individual functions, I need yet another parameter which needs to travel through all these functions. As Brent Yorgey suggested, the nested "do"s can accept another parameter in the topmost function and it will be automatically in scope all the way down. I really wish, someone could elaboreate on this "$ \foo ->do" pattern, - when it is typically used, - what determines the depth of the nesting, - its pros and cons and the possible alternatives. It seems to be some kind of idiom, -- Martin

I really wish, someone could elaborate on this "$ \foo ->do" pattern,
If you are using it in the IO monad consider it as "using a handle" (cf. a file handle or network connection) - as you go outside the IO monad you'll note that a "handle" is really quite a general thing.
participants (8)
-
Brent Yorgey
-
Daniel Trstenjak
-
David McBride
-
Emmanuel Touzery
-
Ertugrul Söylemez
-
Henk-Jan van Tuyl
-
Martin Drautzburg
-
Stephen Tetley