[Haskell-cafe] How to think about this? (profiling)

Bertram Felgenhauer bertram.felgenhauer at googlemail.com
Tue Dec 16 11:36:32 EST 2008


Magnus Therning wrote:
> This behaviour by Haskell seems to go against my intuition, I'm sure I
> just need an update of my intuition ;-)
> 
> I wanted to improve on the following little example code:
> 
>   foo :: Int -> Int
>   foo 0 = 0
>   foo 1 = 1
>   foo 2 = 2
>   foo n = foo (n - 1) + foo (n - 2) + foo (n - 3)

Two more ideas: How about

  -- "loop" keeping the last three elements of the sequence
  -- O(n) per call, constant memory
  foo' :: Int -> Int
  foo' n = go n 0 1 2 where
      go 0 a _ _ = a
      go n a b c = go (n - 1) b c (a + b + c)

or

  -- analogue of the folklore fibonacci definition:
  -- fibs = 0 : 1 : zipWith (+) fibs (tail fibs)
  foos :: [Int]
  foos = 0 : 1 : 2 : zipWith3 (\a b c -> a + b + c)
                              foos (tail foos) (tail (tail foos))

[snip]
> Then I added a convenience function and called it like this:
> 
>   createArray :: Int -> UArray Int Int
>   createArray n = array (0, n) (zip [0..n] (repeat (-1)))
> 
>   main = do
>       (n:_)  <- liftM (map read) getArgs
>       print $ evalState (foo n) (createArray n)
> 
[snip]
> 
>   main = do
>       (n:_)  <- liftM (map read) getArgs
>       print $ evalState (mapM_ foo [0..n] >> foo n) (createArray n)
> 
> Then I started profiling and found out that the latter version both uses
> more memory and makes far more calls to `foo`.  That's not what I
> expected!  (I suspect there's something about laziness I'm missing.)
> 
> Anyway, I ran it with `n=35` and got
> 
>  foo n : 202,048 bytes , foo entries 100
>  mapM_ foo [0..n] >> foo n : 236,312 , foo entries 135 + 1

The number of function calls is to be expected: to evaluate  foo n
for the first time, you need to call  foo (n-1), foo (n-2) and
foo (n-3), making 4 calls per evaluated value. 36*4 = 144 is pretty
close to 135.
(The "missing" 9 calls correspond to foo 0, foo 1 and foo 2)

The difference of 35 can be explained in the same way: the first version
makes 35 fewer explicit calls to 'foo'.

Bertram


More information about the Haskell-Cafe mailing list