asymmetric runtimes for symmetric trees

Hi, I'm having a tree data type data Tree a = Leaf a | Fork (Tree a) (Tree a) , a generator for the left-most path of the tree, taking the depth leftPath :: Int -> Tree Int leftPath d | d > 1 = Fork (leftPath (d-1)) (Leaf 1) | d == 1 = (Leaf 1) | otherwise = error "Can't make tree of depth <= 0." and the similar thing for a right-most path rightPath :: Int -> Tree Int rightPath d | d > 1 = Fork (Leaf 1) (rightPath (d-1)) | d == 1 = (Leaf 1) | otherwise = error "Can't make tree of depth <= 0." Now I measured how long it takes to build a huge tree via print $ sumLeafs $ leftPath 1000000 and print $ sumLeafs $ rightPath 1000000 as main functions where sumLeafs (Fork l r) = sumLeafs l + sumLeafs r sumLeafs (Leaf i) = i Compiling without optimisation and running with no extra runtime options, besides -K50M to make available enough stack, yields on my machine (measured via time) that for leftPath the runtime is 3.8s, for rightPath 2.9s. If I optimize with -O2 runtimes decrease to approx. 1s / 0.8s, meaning the difference is still there. Using the -sstderr runtime option shows that (also with the runtime option -H2.5G) garbage collection for the leftPath case takes always slightly longer than for the rightPath case. Can anyone explain why there is that difference? Cheers, Daniel. PS: Here the programs as one block: ---LeftPath.hs module Main where data Tree a = Leaf a | Fork (Tree a) (Tree a) leftPath :: Int -> Tree Int leftPath d | d > 1 = Fork (leftPath (d-1)) (Leaf 1) | d == 1 = (Leaf 1) | otherwise = error "Can't make tree of depth <= 0." sumLeafs (Fork l r) = sumLeafs l + sumLeafs r sumLeafs (Leaf i) = i main = print $ sumLeafs $ leftPath 1000000 ---RightPath.hs module Main where data Tree a = Leaf a | Fork (Tree a) (Tree a) rightPath :: Int -> Tree Int rightPath d | d > 1 = Fork (Leaf 1) (rightPath (d-1)) | d == 1 = (Leaf 1) | otherwise = error "Can't make tree of depth <= 0." sumLeafs (Fork l r) = sumLeafs l + sumLeafs r sumLeafs (Leaf i) = i main = print $ sumLeafs $ rightPath 1000000

Hi, I've got the answer - its the sumLeafs function that behaves different for leftPath / rightPath. If one exchanges it in the leftPath case by sumLeafs (Fork l r) = sumLeafs r + sumLeafs l sumLeafs (Leaf i) = i the difference in runtime is gone. Cheers, Daniel. Am Dienstag, den 21.09.2010, 19:14 +0200 schrieb Daniel Seidel:
Hi,
I'm having a tree data type
data Tree a = Leaf a | Fork (Tree a) (Tree a)
, a generator for the left-most path of the tree, taking the depth
leftPath :: Int -> Tree Int leftPath d | d > 1 = Fork (leftPath (d-1)) (Leaf 1) | d == 1 = (Leaf 1) | otherwise = error "Can't make tree of depth <= 0."
and the similar thing for a right-most path
rightPath :: Int -> Tree Int rightPath d | d > 1 = Fork (Leaf 1) (rightPath (d-1)) | d == 1 = (Leaf 1) | otherwise = error "Can't make tree of depth <= 0."
Now I measured how long it takes to build a huge tree via
print $ sumLeafs $ leftPath 1000000
and
print $ sumLeafs $ rightPath 1000000
as main functions where
sumLeafs (Fork l r) = sumLeafs l + sumLeafs r sumLeafs (Leaf i) = i
Compiling without optimisation and running with no extra runtime options, besides -K50M to make available enough stack, yields on my machine (measured via time) that for leftPath the runtime is 3.8s, for rightPath 2.9s. If I optimize with -O2 runtimes decrease to approx. 1s / 0.8s, meaning the difference is still there.
Using the -sstderr runtime option shows that (also with the runtime option -H2.5G) garbage collection for the leftPath case takes always slightly longer than for the rightPath case.
Can anyone explain why there is that difference?
Cheers,
Daniel.
PS: Here the programs as one block:
---LeftPath.hs
module Main where
data Tree a = Leaf a | Fork (Tree a) (Tree a)
leftPath :: Int -> Tree Int leftPath d | d > 1 = Fork (leftPath (d-1)) (Leaf 1) | d == 1 = (Leaf 1) | otherwise = error "Can't make tree of depth <= 0."
sumLeafs (Fork l r) = sumLeafs l + sumLeafs r sumLeafs (Leaf i) = i
main = print $ sumLeafs $ leftPath 1000000
---RightPath.hs
module Main where
data Tree a = Leaf a | Fork (Tree a) (Tree a)
rightPath :: Int -> Tree Int rightPath d | d > 1 = Fork (Leaf 1) (rightPath (d-1)) | d == 1 = (Leaf 1) | otherwise = error "Can't make tree of depth <= 0."
sumLeafs (Fork l r) = sumLeafs l + sumLeafs r sumLeafs (Leaf i) = i
main = print $ sumLeafs $ rightPath 1000000
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tuesday 21 September 2010 19:45:50, Daniel Seidel wrote:
Hi,
I've got the answer - its the sumLeafs function that behaves different for leftPath / rightPath. If one exchanges it in the leftPath case by
sumLeafs (Fork l r) = sumLeafs r + sumLeafs l sumLeafs (Leaf i) = i
the difference in runtime is gone.
Yes. The matter is that with the original sumLeafs (btw., that ought to be sumLeaves), the left path builds a call-tree for sumLeafs isomorphic to the tree first. Once that's complete, the evaluation proceeds from leaves to root. The right path, on the other hand, always has the call to sumLeafs for the left subtree returning without recursion, so it builds a tree of calls to (+) which is isomorphic to the original tree, 1 + (1 + (1 + (1 + ...(1 + 1)...))). Since (+) is a simpler function than sumLeafs, that call tree is apparently cheaper. For trees like these, a much better implementation of sumLeafs uses an accumulating parameter and detects leaves on the right while going down the tree: sumLeafs = smlvs 0 smlvs !acc (Leaf i) = acc+i smlvs acc (Fork l (Leaf j)) = smlvs (acc+j) l smlvs acc (Fork l r) = smlvs (smlvs acc l) r (Note there's no need to detect leaves on the left.) That sums the left and right paths in 0.02s with -O2. It'll be faster (and allocate much less) for all trees containing many very skewed subtrees (so lots of leaves with the other branch going much deeper), but for well balanced trees, it makes practically no difference.
Cheers,
Daniel.
Hey, that's *my* line!
participants (2)
-
Daniel Fischer
-
Daniel Seidel