Monads and Functions sequence and sequence_

Hi, Can somebody please explain exactly how the monad functions "sequence" and "sequence_" are meant to work? I have almost every Haskell textbook, but there's surprisingly little information in them about the two functions. From what I can gather, "sequence" and "sequence_" behave differently depending on the types of the Monads that they are processing. Is this correct? Some concrete examples would be really helpful. Even references to some research papers that explain the rationale behind these (and all the other..?) monad functions would be great. Thanks in advance, Mark Spezzano

On 2010-10-30 07:07, Mark Spezzano wrote:
Hi,
Can somebody please explain exactly how the monad functions "sequence" and "sequence_" are meant to work?
I have almost every Haskell textbook, but there's surprisingly little information in them about the two functions.
From what I can gather, "sequence" and "sequence_" behave differently depending on the types of the Monads that they are processing. Is this correct? Some concrete examples would be really helpful.
sequence [m1,m2,m3,m4,...] = do x1 <- m1 x2 <- m2 x3 <- m3 x4 <- m4 ... return [x1,x2,x3,x4,...] sequence_ [m1,m2,m3,m4,...] = do m1 m2 m3 m4 ... return () Cheers,

Not exactly. If you use the type with Maybe Int like so: sequence [Just 1, Nothing, Just 2] then the result is Nothing. Whereas sequence [Just 1, Just 2, Just 3] gives Just [1, 2, 3] Why? I assume there's special implementations of sequence and sequence_ depending on the type of monad used. If it's a sequence_ [putStrLn "hello", putStrLn "goodbye"] then this prints out hello and goodbye on separate lines. It seems to work differently for different types. Mark On 30/10/2010, at 3:42 PM, Bardur Arantsson wrote:
On 2010-10-30 07:07, Mark Spezzano wrote:
Hi,
Can somebody please explain exactly how the monad functions "sequence" and "sequence_" are meant to work?
I have almost every Haskell textbook, but there's surprisingly little information in them about the two functions.
From what I can gather, "sequence" and "sequence_" behave differently depending on the types of the Monads that they are processing. Is this correct? Some concrete examples would be really helpful.
sequence [m1,m2,m3,m4,...] = do x1 <- m1 x2 <- m2 x3 <- m3 x4 <- m4 ... return [x1,x2,x3,x4,...]
sequence_ [m1,m2,m3,m4,...] = do m1 m2 m3 m4 ... return ()
Cheers,
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 30 October 2010 16:30, Mark Spezzano
Not exactly. If you use the type with Maybe Int like so:
sequence [Just 1, Nothing, Just 2]
then the result is Nothing.
Whereas sequence [Just 1, Just 2, Just 3] gives
Just [1, 2, 3]
Why?
I assume there's special implementations of sequence and sequence_ depending on the type of monad used. If it's a sequence_ [putStrLn "hello", putStrLn "goodbye"] then this prints out hello and goodbye on separate lines.
It seems to work differently for different types.
The definition of the monad. In the Maybe monad, as soon as you get a Nothing the entire thing returns Nothing. sequence [ma,mb,mc] = do { a <- ma; b <- mb; c <- mc; return [a,b,c] } = ma >>= \ a -> mb >>= \ b -> mc >>= \ c -> return [a,b,c] However, for Maybe: instance Monad Maybe where ... Nothing >>= f = Nothing Just x >>= f = f x ... So yes, the behaviour of the Monad is dependent upon the Monad. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

That is a result of the implementation of the specific Monad instance, and
that does depend on the type, as you say (but it isn't determined for
sequence(_) specifically).
Nothing >>= f = Nothing
Just x >>= f = f x
is why a Nothing "pollutes" the sequenced lists of Maybes. If Maybe is a
Monad representing computations that can fail (to produce a result), then if
you sequence a bunch of such computations together, if any one computation
fails, your entire computation fails. This reflects the natural behavior of
the Maybe monad, where if you use "x <- maybe computation", the only way to
produce that x is if the computation returned Just.
In other monads, sequence will behave in the "right way" for that monad.
On Sat, Oct 30, 2010 at 1:30 AM, Mark Spezzano wrote: Not exactly. If you use the type with Maybe Int like so: sequence [Just 1, Nothing, Just 2] then the result is Nothing. Whereas sequence [Just 1, Just 2, Just 3] gives Just [1, 2, 3] Why? I assume there's special implementations of sequence and sequence_
depending on the type of monad used. If it's a sequence_ [putStrLn "hello",
putStrLn "goodbye"] then this prints out hello and goodbye on separate
lines. It seems to work differently for different types. Mark On 30/10/2010, at 3:42 PM, Bardur Arantsson wrote: On 2010-10-30 07:07, Mark Spezzano wrote: Hi, Can somebody please explain exactly how the monad functions "sequence"
and "sequence_" are meant to work? I have almost every Haskell textbook, but there's surprisingly little
information in them about the two functions. From what I can gather, "sequence" and "sequence_" behave differently
depending on the types of the Monads that they are processing. Is this
correct? Some concrete examples would be really helpful. sequence [m1,m2,m3,m4,...] = do
x1 <- m1
x2 <- m2
x3 <- m3
x4 <- m4
...
return [x1,x2,x3,x4,...] sequence_ [m1,m2,m3,m4,...] = do
m1
m2
m3
m4
...
return () Cheers, _______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe _______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

On Oct 30, 2010, at 2:30 PM, Mark Spezzano wrote:
If you use the type with Maybe Int like so:
sequence [Just 1, Nothing, Just 2]
then the result is Nothing.
Whereas sequence [Just 1, Just 2, Just 3] gives
Just [1, 2, 3]
Try do x <- Just 1 y <- Nothing z <- Just 2 return [x,y,z] and do x <- Just 1 y <- Just 2 z <- Just 3 return [x,y,z] The results are the same as with your calls of `sequence`. It is >>= which makes the difference, not `sequence`. Sebastian

The actual, entire, complete definitions of sequence and sequence_ are (or at least, could be):
sequence [] = return [] sequence (m:ms) = do x <- m xs <- sequence ms return (x:xs)
-- or, equivalently: sequence' = foldr (liftM2 (:)) (return [])
sequence_ [] = return () sequence_ (x:xs) = do x sequence_ xs
-- or: sequence'_ = foldr (>>) (return ())
They're defined once for all monads, not once for each monad, so in some sense they behave the 'same' in that they use the Monad instance in the same way. It's just like, say, sort :: Ord a => [a] -> [a] might do different computations to compare elements depending on what 'a' is, but always produces a sorted list regardless of that detail.

The expression sequence [a,b,c,...] is roughly equivalent to do r_a <- a r_b <- b r_c <- c ... return [r_a,r_b,r_c,...] The expression sequence_ [a,b,c,...] is roughly equivalent to do a b c ... return () Does that help? Cheers, Greg On 10/29/10 10:07 PM, Mark Spezzano wrote:
Hi,
Can somebody please explain exactly how the monad functions "sequence" and "sequence_" are meant to work?
I have almost every Haskell textbook, but there's surprisingly little information in them about the two functions.
From what I can gather, "sequence" and "sequence_" behave differently depending on the types of the Monads that they are processing. Is this correct? Some concrete examples would be really helpful.
Even references to some research papers that explain the rationale behind these (and all the other..?) monad functions would be great.
Thanks in advance,
Mark Spezzano _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

* Mark Spezzano
Can somebody please explain exactly how the monad functions "sequence" and "sequence_" are meant to work?
The others in this thread have already explained how these functions work, so I'll just give an example how they are used. Consider the following task: to read 30 lines from standard input. For one line you would use an action getLine :: IO String How to execute this 30 times? Haskell has a function replicate :: Int -> a -> [a] which takes a number and produces a list with that number of identical elements. So this is close to what we need: replicate 30 getLine :: [IO String] This is a list containing 30 'getLine' actions. But the list of actions _is not_ an action itself. This is what sequence does -- it transforms a list of actions into a single action which gathers the results into one list. As its name suggests, it does sequencing of actions. sequence $ replicate 30 getLine :: IO [String] Exactly what we need, an action producing a list of lines read. Now, let's consider this code: sequence [ putStrLn $ show i ++ " green bottles standing on the wall" | i <- reverse [1..10] ] :: IO [()] This action prints 10 lines and also returns us gathered results, i.e. 10 '()', one from each putStrLn (recall that putStrLn has type "String -> IO ()". Most probably we don't care about those '()', but they still occupy memory and introduce a space leak as explained here[1]. That's why a version of sequence is introduced which ignores the results of actions and simply returns (). It is called "sequence_". sequence_ :: (Monad m) => [m a] -> m () As a side note, we can rewrite our last example without using list comprehension in the following way: let p i = putStrLn $ show i ++ " green bottles standing on the wall" in sequence_ $ map p $ reverse [1..10] The combinations of sequence and sequence_ with map are so common that they have special names: mapM = \f -> sequence . map f :: (Monad m) => (a -> m b) -> [a] -> m [b] mapM_ = \f -> sequence_ . map f :: (Monad m) => (a -> m b) -> [a] -> m () [1] http://neilmitchell.blogspot.com/2008/12/mapm-mapm-and-monadic-statements.ht... -- Roman I. Cheplyaka :: http://ro-che.info/ "Don't let school get in the way of your education." - Mark Twain
participants (8)
-
Bardur Arantsson
-
Ben Millwood
-
Daniel Peebles
-
Gregory Crosswhite
-
Ivan Lazar Miljenovic
-
Mark Spezzano
-
Roman Cheplyaka
-
Sebastian Fischer