
Hi (First question so be gentle)! Just started to look at Haskell and I was wondering about various versions of calculating factorials. If I have facr 0 = 1 facr n = foldr (*) 1 [1..n] facl 0 = 1 facl n = foldl (*) 1 [1..n] Is there any difference in efficiency, I remember reading it is better to count down than to count up but left to right or right to left :-) Cheers Paul Paul Johnston Humanities Development Team Room 2.12 Bridgeford Street Building Manchester University Tel 0161 275 1396 Mail Paul.Johnston@manchester.ac.uk Web http://web-1.humanities.manchester.ac.uk/prjs/mcasspj/ How to shoot yourself in the foot Unix % ls foot.c foot.h foot.o toe.d toe.o %rm* .o rm:.o no such file or directory

Am Donnerstag, 7. August 2008 16:16 schrieb Paul Johnston:
Hi (First question so be gentle)! Just started to look at Haskell and I was wondering about various versions of calculating factorials.
If I have
facr 0 = 1 facr n = foldr (*) 1 [1..n]
facl 0 = 1 facl n = foldl (*) 1 [1..n]
Is there any difference in efficiency, I remember reading it is better to count down than to count up but left to right or right to left :-)
For this task, there will be no big difference unless the compiler's optimiser sees the strictness (which it can, if the type is appropriately determined). facr will build a thunk of the form 1 * (2 * (3 * (4 * (... * (n * 1) ...)))), there is no way the evaluation can start before the end of the list is reached, so the size of the thunk is O(n) and it will blow the stack if n is too large. facl will build a thunk of the form (...(((1 * 1) * 2) * 3) * ...) * n, which will also blow the stack if n is large enough. Since it is built from the inside out, it could be evaluated in each step to prevent the stack overflow, but because of the laziness, that will only happen if the implementation knows that it will be needed, which is for instance the case if you compile with -O (at least if you use GHC) and the type of facl can be deduced or is given as Int -> Int or Integer -> Integer. You can get that behaviour without relying on the optimiser by using the strict left fold foldl' from Data.List, which forces evaluation at each step. As a general rule, if you can get a result (or start producing a result) without traversing the entire list, use foldr. Examples for this are and = foldr (&&) True and or = foldr (||) False and for the case of producing partial results concat = foldr (++) []. If you need to consume the entire list to get a result, use foldl'. I don't know of any case where foldl is a better choice than foldl'.
Cheers Paul
Cheers, Daniel

G'day all.
Quoting Daniel Fischer
facr will build a thunk of the form 1 * (2 * (3 * (4 * (... * (n * 1) ...)))), [...] facl will build a thunk of the form (...(((1 * 1) * 2) * 3) * ...) * n, which will also blow the stack if n is large enough. [...] You can get that behaviour without relying on the optimiser by using the strict left fold
foldl'
from Data.List, which forces evaluation at each step.
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: << {-# SPECIALIZE binaryProduct :: [Integer] -> Integer #-} binaryProduct :: (Num a) => [a] -> a binaryProduct [] = 1 binaryProduct [x] = x binaryProduct xs = binaryProduct (bip' xs) where bip' (x1:x2:xs) = x1*x2 : bip' xs bip' xs = xs fac1 :: Integer -> Integer fac1 n = foldl' (*) 1 [1..n] fac2 :: Integer -> Integer fac2 n = binaryProduct [1..n]
The speed difference for large n is remarkable: << Factorial> fac1 100000 == fac2 100000 True Factorial> :set +s Factorial> fac1 100000 `seq` () () (6.27 secs, 9304407772 bytes) Factorial> fac2 100000 `seq` () () (0.31 secs, 20527124 bytes)
(The `seq` () idiom, by the way, forces computation of the result without incurring the expense of calling "show". The "show" function on Integers is quite slow for very large numbers, and the factorial of 100,000 is a very large number.) As you can probably guess, the speedup is not due to lazy evaluation. A good exercise for bright students who know something about computer arithmetic: Why is the binary tree-style version so much faster? Cheers, Andrew Bromage

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

On Thu, Aug 7, 2008 at 4:16 PM, Paul Johnston
Is there any difference in efficiency, I remember reading it is better to count down than to count up but left to right or right to left :-)
I wrote a small wiki article on the differences beteen the various folds: http://haskell.org/haskellwiki/Foldr_Foldl_Foldl%27 regards, Bas
participants (5)
-
ajb@spamcop.net
-
Bas van Dijk
-
Daniel Fischer
-
Paul Johnston
-
Tillmann Rendel