
[This message is literate Haskell] Hi -cafe, I was trying to use Monad.foldM in the State monad recently and ran into some performance issues. They were eventually fixed with seq, but along the way I made some discoveries, which I thought I would share. The Report defines foldM as foldM :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a foldM f z [] = return z foldM f z (x:xs) = f z x >>= \z' -> foldM f z' xs It turns out that foldM is essentially a right fold. Define f' = \h t -> flip f h >=> t. The operator (>=>) is (reverse) Kleisli composition, defined in Control.Monad as f >=> g = \x -> f x >>= g. Now foldM f z xs = foldr f' return xs z. Proof. On the empty list, foldM f z [] = return z [definition of foldM] = foldr f' return [] z [definition of foldr] Now fix a list xs and inductively assume that foldM f z xs = foldr f' return xs z for all z. Then for any z and x, foldM f z (x:xs) = f z x >>= \z' -> foldM f z' xs [definition of foldM] = f z x >>= \z' -> foldr f' return xs z' [inductive hypothesis] = f z x >>= foldr f' return xs [eta-conversion(*)] = flip f x z >>= foldr f' return xs [definition of flip] = (\z' -> flip f x z' >>= foldr f' return xs) z [beta-reduction] = (flip f x >=> foldr f' return xs) z [definition of >=>] = (f' x (foldr f' return xs)) z [definition of f'] = foldr f' return (x:xs) z [definition of foldr] (*) The eta-conversion preserves strictness as long as return /= _|_, since f >=> g is in WHNF. Interestingly, foldM can also be written as a left fold. To see this, note that it is a theorem that foldr f z xs = foldl f z xs as long as f is associative and z is a unit for f. Since (>=>) is associative with unit return, we have foldr (\h t -> flip f h >=> t) return = foldr (>=>) return . map (flip f) [foldr/map fusion] = foldl (>=>) return . map (flip f) [by the theorem] = foldl (\t h -> t >=> flip f h) return [foldl/map fusion] Therefore foldM f z xs = foldr f' return xs z = foldl f'' return xs z, where f'' = \t h -> t >=> flip f h. But this doesn't mean these all have the same performance characteristics. Exercise for the reader: find examples where the foldr version performs better than the foldl version and vice-versa. I've noticed this distinction between State and [] in particular. They both may require use of seq in the function f to prevent stack overflow. Here is a module implementing these versions of foldM. It seems reasonable to have versions with <=< and with f unflipped as well, but those could be derived from the functions below.
module FoldM (foldrM, foldr1M, foldlM, foldl1M) where import Control.Monad((>=>))
-- foldrM nests to the right: -- foldrM f z [x1, ..., xn] = (flip f x1 >=> (... >=> (flip f xn)...)) $ z foldrM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a foldrM f z xs = foldr (\h t -> flip f h >=> t) return xs z
Surprisingly, this may or may not be faster than the equivalent foldrM f z = return z >>= foldr (\h t -> flip f h >=> t) return xs depending on the monad. But they're both slower than foldM.
foldr1M f (x:xs) = foldrM f x xs
-- foldlM nests to the left: -- foldlM f z [x1, ..., xn] = (...(flip f x1) >=> ...) >=> flip f xn) $ z foldlM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a foldlM f z xs = foldl (\t h -> t >=> flip f h) return xs z
Again, this is apparently faster or slower than either of foldlM f z xs = return z >>= foldl (\t h -> t >=> flip f h) return xs foldlM f = foldl (\t h -> t >>= flip f h) . return depending on the monad.
foldl1M f (x:xs) = foldlM f x xs
--
Jason McCarty

On Wednesday 19 August 2009 12:14:24 am Jason McCarty wrote:
Interestingly, foldM can also be written as a left fold. To see this, note that it is a theorem that foldr f z xs = foldl f z xs as long as f is associative and z is a unit for f.
It must also be the case that xs is finite in length, because if it is infinite, then 'foldl f z xs' is bottom, while 'foldr f z xs' needn't be. This difference holds over into foldM implemented with each, where you can write something like: foldM (\f e -> if even e then Left (show e) else Right f) "no evens" [1..] and get an answer of 'Left "2"' with a foldr implementation, but bottom with a foldl implementation. This potentially translates into its own performance concerns, because in such monads, the computation can short-circuit upon finding a 'throw' when using the foldr implementation, but with the foldl implementation, you have to do at least a little shuffling of thunks for the entire list. -- Dan

2009/8/19 Dan Doel
On Wednesday 19 August 2009 12:14:24 am Jason McCarty wrote:
Interestingly, foldM can also be written as a left fold. To see this, note that it is a theorem that foldr f z xs = foldl f z xs as long as f is associative and z is a unit for f.
This is not true: f has to be commutative, not associative. Consider matrix multiplication.
It must also be the case that xs is finite in length, because if it is infinite, then 'foldl f z xs' is bottom, while 'foldr f z xs' needn't be. This difference holds over into foldM implemented with each, where you can write something like:
foldM (\f e -> if even e then Left (show e) else Right f) "no evens" [1..]
and get an answer of 'Left "2"' with a foldr implementation, but bottom with a foldl implementation.
This potentially translates into its own performance concerns, because in such monads, the computation can short-circuit upon finding a 'throw' when using the foldr implementation, but with the foldl implementation, you have to do at least a little shuffling of thunks for the entire list.
-- Dan _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Eugene Kirpichov Web IR developer, market.yandex.ru

Am Mittwoch 19 August 2009 16:32:57 schrieb Eugene Kirpichov:
2009/8/19 Dan Doel
: On Wednesday 19 August 2009 12:14:24 am Jason McCarty wrote:
Interestingly, foldM can also be written as a left fold. To see this, note that it is a theorem that foldr f z xs = foldl f z xs as long as f is associative and z is a unit for f.
This is not true: f has to be commutative, not associative.
Consider matrix multiplication.
It is true: foldr: A1*(A2*(... *AN*E)) foldl: (...((E*A1)*A2)*...*AN) Commutativity doesn't help, consider data Foo = Z | A | B (~) :: Foo -> Foo -> Foo Z ~ x = x x ~ Z = x B ~ B = A _ ~ _ = B (~) is commutative, but not associative, Z is a unit for (~). foldr (~) Z [A,A,B] = B foldl (~) Z [A,A,B] = A

You're right. My bad, indeed.
2009/8/19 Daniel Fischer
Am Mittwoch 19 August 2009 16:32:57 schrieb Eugene Kirpichov:
2009/8/19 Dan Doel
: On Wednesday 19 August 2009 12:14:24 am Jason McCarty wrote:
Interestingly, foldM can also be written as a left fold. To see this, note that it is a theorem that foldr f z xs = foldl f z xs as long as f is associative and z is a unit for f.
This is not true: f has to be commutative, not associative.
Consider matrix multiplication.
It is true: foldr: A1*(A2*(... *AN*E)) foldl: (...((E*A1)*A2)*...*AN)
Commutativity doesn't help, consider
data Foo = Z | A | B
(~) :: Foo -> Foo -> Foo Z ~ x = x x ~ Z = x B ~ B = A _ ~ _ = B
(~) is commutative, but not associative, Z is a unit for (~).
foldr (~) Z [A,A,B] = B foldl (~) Z [A,A,B] = A
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Eugene Kirpichov Web IR developer, market.yandex.ru

It is associativity that is required, not commutativity (in addition to the
fact that the list is finite).
This is why Data.Foldable provides operations for monoids over containers.
Monoids just provide you with associativity and a unit, which lets you
reparenthesize the fold however you want.
See the monoids library or my slides from hac-phi for lots of (ab)uses of a
monoid's associativity.
http://comonad.com/reader/2009/hac-phi-slides/
-Edward Kmett
On Wed, Aug 19, 2009 at 10:32 AM, Eugene Kirpichov
2009/8/19 Dan Doel
: On Wednesday 19 August 2009 12:14:24 am Jason McCarty wrote:
Interestingly, foldM can also be written as a left fold. To see this, note that it is a theorem that foldr f z xs = foldl f z xs as long as f is associative and z is a unit for f.
This is not true: f has to be commutative, not associative.
Consider matrix multiplication.
It must also be the case that xs is finite in length, because if it is infinite, then 'foldl f z xs' is bottom, while 'foldr f z xs' needn't be. This difference holds over into foldM implemented with each, where you can write something like:
foldM (\f e -> if even e then Left (show e) else Right f) "no evens" [1..]
and get an answer of 'Left "2"' with a foldr implementation, but bottom with a foldl implementation.
This potentially translates into its own performance concerns, because in such monads, the computation can short-circuit upon finding a 'throw' when using the foldr implementation, but with the foldl implementation, you have to do at least a little shuffling of thunks for the entire list.
-- Dan _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Eugene Kirpichov Web IR developer, market.yandex.ru _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (5)
-
Dan Doel
-
Daniel Fischer
-
Edward Kmett
-
Eugene Kirpichov
-
Jason McCarty