[Haskell-cafe] efficient combination of foldl' and foldr -> foldl'r

Henning Thielemann lemming at henning-thielemann.de
Fri Dec 5 10:04:22 EST 2008


I want to do a foldl' and a foldr in parallel on a list. I assumed it 
would be no good idea to run foldl' and foldr separately, because then the 
input list must be stored completely between the calls of foldl' and 
foldr. I wanted to be clever and implemented a routine which does foldl' 
and foldr in one go. But surprisingly, at least in GHCi, my clever routine 
is less efficient than the naive one.

Is foldl'rNaive better than I expect, or is foldl'r worse than I hope?


module FoldLR where

import Data.List (foldl', )
import Control.Arrow (first, second, (***), )

foldl'r, foldl'rNaive ::
    (b -> a -> b) -> b -> (c -> d -> d) -> d -> [(a,c)] -> (b,d)

foldl'r f b0 g d0 =
    first ($b0) .
    foldr (\(a,c) ~(k,d) -> (\b -> k $! f b a, g c d)) (id,d0)

foldl'rNaive f b g d xs =
    (foldl' f b *** foldr g d) $ unzip xs

test, testNaive :: (Integer, Char)
test =
    second last $ foldl'r (+) 0 (:) "" $ replicate 1000000 (1,'a')
{-
*FoldLR> test
(1000000,'a')
(2.65 secs, 237509960 bytes)
-}


testNaive =
    second last $ foldl'rNaive (+) 0 (:) "" $ replicate 1000000 (1,'a')
{-
*FoldLR> testNaive
(1000000,'a')
(0.50 secs, 141034352 bytes)
-}



More information about the Haskell-Cafe mailing list