Always check optimizations to make sure they are not pessimizations!

Actually, traversing the list twice is very cheap compared to space leakage, and accumulating pairs requires tuple boxing and unboxing which I don't know how to get GHC not to do.

Your avg3 (along with several attempts of mine to fix the problem) gave stack overflows on a large list.

Only avg4 below (traversing the list twice with strict accumulation) didn't blow up on large lists, even though avg5 and avg6 were intended to be strict.

Prelude Control.Arrow Data.List>
 let avg4 = uncurry (/) . (foldl' (+) 0 &&& foldl' (\x y -> x + 1) 0)
  in avg4 [1..10000000]
5000000.5
-- This took 13 sec on my machine

Prelude Control.Arrow Data.List> let avg3 = uncurry (/) . foldr (\x (s,n) -> (s + x,n + 1)) (0,0) in avg3 [1..10000000]
*** Exception: stack overflow
-- This fails in 1 sec

Prelude Control.Arrow Data.List>
 let avg5 = uncurry (/) . foldl' (\(s,n) x -> (s + x,n + 1)) (0,0)
  in avg5 [1..10000000]
*** Exception: stack overflow
-- This fails in 100 sec

Prelude Control.Arrow Data.List>
 let avg6 = uncurry (/) . foldl' (\sn x -> (fst sn+x,snd sn+1)) (0,0)
  in avg6 [1..10000000]
*** Exception: stack overflow
-- This fails in 30 sec

Prelude Control.Arrow Data.List>
 let avg3 = uncurry (/) . foldr (\n -> (+n) *** (+1)) (0, 0)
  in avg3 [1..10000000]
*** Exception: stack overflow
-- This fails in 2 sec

Tim Newsham wrote:
Just goofing around with arrows and foldr while reading Hutton's
excellent paper on folds (http://www.cs.nott.ac.uk/~gmh/fold.pdf).

Wondering if this can be done automatically and more generally?

module Main where
import Control.Arrow
import Data.List

-- sum and length expressed as foldr.
fsum = foldr (\n -> (+n)) 0
flen = foldr (\n -> (+1)) 0

-- compute average using arrows..
-- compute the sum of a list, compute the length, and do a divide.
-- this traverses the list twice using two foldrs.
avg1 = uncurry (/) . (fsum &&& flen)
avg2 = uncurry (/) . (foldr (\n -> (+n)) 0 &&& foldr (\n -> (+1)) 0)

-- But the two foldr's can be fused together
-- here we're mixing the two foldr constants 0 and 0 to (0,0)
-- and we're mixing the two functions (\n -> (+n)) and
-- (\n -> (+1)) to (\n -> (+n) *** (+1)).
avg3 = uncurry (/) . foldr (\n -> (+n) *** (+1)) (0, 0)

main = do
    print $ avg1 [1,2,3,4]
    print $ avg2 [1,2,3,4]
    print $ avg3 [1,2,3,4]

Tim Newsham
http://www.thenewsh.com/~newsham/
_______________________________________________
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

Reply via email to