
Hi all, On the other day I noticed that we could optimize 'sequence' more. I needed it for my monadic parser. Below is my small experiment. Sequence from standard library needs 2.3s to finish (and additional stack space), my version uses only 0.65s and default stack. Is my version better or am I missing something obvious? -- standard sequence1 :: Monad m => [m a] -> m [a] sequence1 ms = foldr k (return []) ms where k m m' = do { x <- m; xs <- m'; return (x:xs) } -- accumulator version sequence2 :: Monad m => [m a] -> m [a] sequence2 ms = sequence' [] ms where sequence' vs [] = return (reverse vs) sequence' vs (m:ms) = m >>= (\v -> sequence' (v:vs) ms) main = do let l = map return [1..1000000] w <- sequence1 l print (sum w) return () gracjan@home:~/some_faster> time ./Some1 +RTS -K100M 500000500000 real 0m2.318s user 0m2.284s sys 0m0.032s gracjan@home:~/some_faster> time ./Some2 500000500000 real 0m0.652s user 0m0.592s sys 0m0.052s -- Gracjan

On Mon, Jul 21, 2008 at 1:54 PM, Gracjan Polak
Hi all,
On the other day I noticed that we could optimize 'sequence' more. I needed it for my monadic parser. Below is my small experiment. Sequence from standard library needs 2.3s to finish (and additional stack space), my version uses only 0.65s and default stack.
Is my version better or am I missing something obvious?
How does your version compare with the library version in the following tests: test1 = do (x:_) <- sequence [return 5, undefined] return x test2 = do (x:_) <- sequence $ return 5 : undefined return x main = do print $ runIdentity test1 print $ runIdentity test2 The function "runIdentity" is found in Control.Monad.Identity in the mtl package. (I haven't tried this code yet, so it may not really be syntactically correct, but hopefully you get the idea.) -Antoine

Antoine Latter
The function "runIdentity" is found in Control.Monad.Identity in the mtl package.
Thanks, I see it now! Laziness is not there! But still... Identity is a bit special monad. What other monads need full laziness in sequence? As far as I know IO is strict. What about lazy/strict state monad? Initially I spotted this possible optimization in context of monadic parser. I am not really sure if I need this property there or not. How do I prove this to myself? Thanks to others who responded. -- Gracjan

Gracjan Polak wrote:
Initially I spotted this possible optimization in context of monadic parser. I am not really sure if I need this property there or not. How do I prove this to myself?
How about some QuickChecking in connection with the "Chasing bottoms" library (http://citeseer.ist.psu.edu/704350.html)? -- Dr. Janis Voigtlaender http://wwwtcs.inf.tu-dresden.de/~voigt/ mailto:voigt@tcs.inf.tu-dresden.de

Janis Voigtlaender wrote:
How about some QuickChecking in connection with the "Chasing bottoms" library (http://citeseer.ist.psu.edu/704350.html)?
Ah, finally a reference to what this curios phrase is actually about...!

On Tue, Jul 22, 2008 at 1:15 AM, Gracjan Polak
Antoine Latter
writes: The function "runIdentity" is found in Control.Monad.Identity in the mtl package.
But still... Identity is a bit special monad. What other monads need full laziness in sequence? As far as I know IO is strict. What about lazy/strict state monad?
A little formal reasoning reveals that sequence1 = sequence2 exactly when (>>=) is strict in its left argument. There are four common monads which are _not_: Identity, Reader, Writer, State (and RWS by extension). Luke

2008/7/22 Luke Palmer
A little formal reasoning reveals that sequence1 = sequence2 exactly when (>>=) is strict in its left argument. There are four common monads which are _not_: Identity, Reader, Writer, State (and RWS by extension).
Still if that makes that much of a difference, maybe we could envision putting a sequence' in the library ? -- Jedaï

Chaddaï Fouché
2008/7/22 Luke Palmer
: A little formal reasoning reveals that sequence1 = sequence2 exactly when (>>=) is strict in its left argument. There are four common monads which are _not_: Identity, Reader, Writer, State (and RWS by extension).
Still if that makes that much of a difference, maybe we could envision putting a sequence' in the library ?
Yes, in my experiments this is to be or not to be. Stack space is limited. Also processing time goes down by 800%, so it is a big deal sometimes. Incomplete list of functions affected: sequence mapM foldM Text.ParserCombinators.Parsec.Combinator(many1,sepBy,endBy,manyTill) Text.ParserCombinators.ReadP(many,many1,count,sepBy,endBy,manyTill) ... As far as I know sequence could be specialized to IO monad and use my transformation. How do I reason if >>= for parsers is lazy in its first argument? -- Gracjan

Gracjan Polak wrote:
How do I reason if >>= for parsers is lazy in its first argument?
Well, to quote from the abstract of the paper I already mentioned (http://citeseer.ist.psu.edu/704350.html): "By testing before proving we avoid wasting time trying to prove statements that are not valid." I think the library described in the paper, available here: http://www.cs.nott.ac.uk/~nad/software/#Chasing%20Bottoms has what you need. For example, you can check for isBottom, combine this with random test case generation, and thus should be able to quickly get an informed hypothesis about whether or not your >>= is lazy. For then proving that hypothesis, the paper (and probably other papers it cites) also provides some techniques that might be of use to you. Ciao, Janis. -- Dr. Janis Voigtlaender http://wwwtcs.inf.tu-dresden.de/~voigt/ mailto:voigt@tcs.inf.tu-dresden.de

gracjanpolak:
Chaddaï Fouché
writes: 2008/7/22 Luke Palmer
: A little formal reasoning reveals that sequence1 = sequence2 exactly when (>>=) is strict in its left argument. There are four common monads which are _not_: Identity, Reader, Writer, State (and RWS by extension).
Still if that makes that much of a difference, maybe we could envision putting a sequence' in the library ?
Yes, in my experiments this is to be or not to be. Stack space is limited. Also processing time goes down by 800%, so it is a big deal sometimes.
Incomplete list of functions affected:
sequence mapM foldM Text.ParserCombinators.Parsec.Combinator(many1,sepBy,endBy,manyTill) Text.ParserCombinators.ReadP(many,many1,count,sepBy,endBy,manyTill) ...
As far as I know sequence could be specialized to IO monad and use my transformation.
How do I reason if >>= for parsers is lazy in its first argument?
How about adding Control.Monad.Strict for the strict package? http://hackage.haskell.org/cgi-bin/hackage-scripts/package/strict

If you can demonstrate the required laziness/strictness properties are identical, looks like a nice idea. gracjanpolak:
Hi all,
On the other day I noticed that we could optimize 'sequence' more. I needed it for my monadic parser. Below is my small experiment. Sequence from standard library needs 2.3s to finish (and additional stack space), my version uses only 0.65s and default stack.
Is my version better or am I missing something obvious?
-- standard sequence1 :: Monad m => [m a] -> m [a] sequence1 ms = foldr k (return []) ms where k m m' = do { x <- m; xs <- m'; return (x:xs) }
-- accumulator version sequence2 :: Monad m => [m a] -> m [a] sequence2 ms = sequence' [] ms where sequence' vs [] = return (reverse vs) sequence' vs (m:ms) = m >>= (\v -> sequence' (v:vs) ms)
main = do let l = map return [1..1000000] w <- sequence1 l print (sum w) return ()
gracjan@home:~/some_faster> time ./Some1 +RTS -K100M 500000500000
real 0m2.318s user 0m2.284s sys 0m0.032s
gracjan@home:~/some_faster> time ./Some2 500000500000
real 0m0.652s user 0m0.592s sys 0m0.052s
-- Gracjan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Don Stewart wrote:
If you can demonstrate the required laziness/strictness properties are identical, looks like a nice idea.
I think they are not identical, as something along Antoine's second example demonstrates. -- Dr. Janis Voigtlaender http://wwwtcs.inf.tu-dresden.de/~voigt/ mailto:voigt@tcs.inf.tu-dresden.de
participants (7)
-
Andrew Coppin
-
Antoine Latter
-
Chaddaï Fouché
-
Don Stewart
-
Gracjan Polak
-
Janis Voigtlaender
-
Luke Palmer