
Sequence isn't necessarily strict. Sequence, rather necessarily,
depends on the semantics of (>>=) in that monad.
Prelude Control.Monad.Identity> runIdentity $ take 10 `liftM` sequence
(map return $ repeat 5)
[5,5,5,5,5,5,5,5,5,5]
What matters is if (>>=) is strict in its first argument. The
Identity Monad provided by mtl and transformers is not strict in the
first argument of (>>=). Hence sequence isn't strict in that Identity
Monad.
Compare to IO, where (>>=) is strict in its first argument:
Prelude Control.Monad.Identity> take 10 `liftM` sequence (map return $
repeat 5) :: IO [Int]
^CInterrupted.
After a while, I got bored and interrupted it.
Anyway. There's no documentation on the (non-)strictness of sequence,
because it isn't actually defined. It depends on the choice of m.
Carl Howells
On Sun, Dec 19, 2010 at 1:58 PM, Daniel Fischer
On Sunday 19 December 2010 22:18:59, Jacek Generowicz wrote:
The reason this doesn't stop where you expect it to is that sequence is effectively strict
That would explain it. Thank you.
Where is this fact documented? I mostly rely on Hoogle, which gets me to
http://hackage.haskell.org/packages/archive/base/latest/doc/html/Prelude .html#v
:sequence
which says nothing about strictness.
How could I have known this without having to bother anyone else?
Well, you can deduce it from sequence's type. That's of course not something you immediately see, but in hindsight, it's pretty easy to understand.
sequence :: Monad m => [m a] -> m [a]
So, basically all sequence can do is use (>>=) and return. Reasonably,
sequence [] = return []
is the only thing that's possible. For nonempty lists,
sequence (x:xs) = ?
Well, what can sequence do? It has to do something with x and something with xs, the only reasonable thing is to call sequence on the tail and run x, combining x's result and the result of sequence xs.
One can choose the order, but
sequence (x:xs) = do a <- x as <- sequence xs return (a:as)
is the most sensible thing.
Now, that means before sequence can deliver anything, it has to run all actions (because if any action fails, sequence fails and that can't be known before all actions have been run).
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe