
ajb@spamcop.net wrote:
There's one more possibility you should be aware of, assume you're trying to compute large factorials, and that's to use a binary tree-style recursion pattern. This one is bottom-up, but you could also do top-down:
Here's my top-down binary fold, with growing tree sizes to allow the processing of infinite lists. module Binfold where import System.Environment import Data.List -- fold the first 2 ** n elements tree-shaped binfold :: Int -> (a -> a -> a) -> a -> [a] -> (a, [a]) binfold n f i [] = (i, []) binfold 0 f i (x:xs) = (x, xs) binfold n f i xs = (f y z, xs'') where (y, xs') = binfold (pred n) f i xs (z, xs'') = binfold (pred n) f i xs' -- fold with a growing sequence of binfolds growfold :: Int -> (a -> a -> a) -> a -> [a] -> a growfold n f i [] = i growfold n f i xs = f y (growfold (succ n) f i xs') where (y, xs') = binfold n f i xs main = do [op, n] <- getArgs let fold = case op of "growfold" -> growfold 0 "foldr" -> foldr "foldl" -> foldl "foldl!" -> foldl' print . length . show . fold (*) 1 . enumFromTo 1 . read $ n $ ghc -O2 -main-is Binfold -o Binfold Binfold.hs $ time ./Binfold foldr 100000 456574 real 0m15.094s user 0m0.015s sys 0m0.031s $ time ./Binfold foldl 100000 456574 real 0m18.000s user 0m0.030s sys 0m0.015s $ time ./Binfold foldl! 100000 456574 real 0m4.641s user 0m0.031s sys 0m0.031s $ time ./Binfold growfold 100000 456574 real 0m0.954s user 0m0.015s sys 0m0.015s Tillmann