[Haskell-cafe] Fusing foldr's

Tim Newsham newsham at lava.net
Thu Oct 11 04:08:35 EDT 2007


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/


More information about the Haskell-Cafe mailing list