[Haskell-cafe] asymmetric runtimes for symmetric trees

Daniel Seidel ds at informatik.uni-bonn.de
Tue Sep 21 13:14:22 EDT 2010


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



More information about the Haskell-Cafe mailing list