[Haskell-cafe] Sharing Subexpressions: Memoization of Fibonacci sequence

Daniel Fischer daniel.is.fischer at web.de
Wed Oct 14 19:41:10 EDT 2009


Am Mittwoch 14 Oktober 2009 23:30:05 schrieb SimonK77:
> Hallo Daniel,
>
> can you explain the difference between a "pattern binding" and a "function
> binding"? I haven't heard about these two terms so far.

The formal specification is at http://haskell.org/onlinereport/decls.html#sect4.4.3

A function binding is a binding where the function name and at least one parameter 
(pattern) appear to the left of '=', while in a pattern binding only bound patterns appear 
on the left.

-- function bindings
fun x = expression           -- binds fun
x \/ y = expr'               -- binds (\/)

-- pattern bindings
func = \x -> expression      -- binds func
var = expr                   -- binds var
(v1,v2) = express            -- binds v1 and v2
(a0:a1:tl)                   -- binds a0, a1 and tl
    | even v1   = exp1
    | otherwise = exp2

The first three are *simple* pattern bindings.

> And furthermore:
> Why does the memoization only happen with pattern binding?

I don't know all the details either, but the point is that names bound by a (simple) 
pattern binding are "constant applicative forms" (http://www.haskell.org/haskellwiki/CAF) 
which can be shared by all uses (if they have a monomorphic type, cf. also 
http://www.haskell.org/haskellwiki/Monomorphism_Restriction and 
http://haskell.org/onlinereport/decls.html#sect4.5.5), while names bound by a function 
binding aren't shared across computations (I think it is generally undecidable how much 
could be shared and anyway it would be too complicated for the compiler to investigate 
that - too little gain for too much effort).

So with function-bound

fbfib :: Int -> Integer
fbfib k =
    let fib 0 = 0
        fib 1 = 1
        fib n = fbfib (n-2) + fbfib (n-1)
    in (map fib [0 ..] !! k)

fb2fib :: Int -> Integer
fb2fib k =
    let fib 0 = 0
        fib 1 = 1
        fib n = fb2fib (n-2) + fb2fib (n-1)
        flst = map fib [0 .. ]
    in (flst !! k)

nothing is shared, each (recursive) call to fb(2)fib creates a new list of Fibonacci 
values (in principle, different arguments could require very different code-paths, so we 
don't even bother to let the compiler look for the few cases where it could determine 
sharing would be beneficial).

With pattern-bound functions, it's harder to know when sharing will happen. It depends on 
the form of the RHS and where things that might be shared are bound.

In

memoized_fib :: Int -> Integer
memoized_fib =
    let fib 0 = 0
        fib 1 = 1
        fib n = memoized_fib (n-2) + memoized_fib (n-1)
    in (map fib [0 ..] !!)

the list of Fibonacci numbers is shared, even though it hasn't been given a name (In 
general, give entities you want to be shared a name of their own to increase the chance of 
them being really shared).

If you define the function with a simple pattern binding which has a lambda-expression on 
the right hand side, it depends on whether things are bound within the lambda-scope or 
outside. In

plfib :: Int -> Integer
plfib = \k ->
    let fib 0 = 0
        fib 1 = 1
        fib n = plfib (n-2) + plfib (n-1)
    in (map fib [0 ..] !! k)

the things which could be shared are bound inside the lambda-expression, therefore they 
aren't shared (they could potentially depend on the lambda-bound variable[s], here k). 

Lifting the binding of fib outside the lambda

pblfib :: Int -> Integer
pblfib =
    let fib 0 = 0
        fib 1 = 1
        fib n = pblfib (n-2) + pblfib (n-1)
    in \k -> (map fib [0 ..] !! k)

doesn't help - of course, the list in which we index is still inside the lambda. Give it a 
name and hoist it outside the lambda:

peblfib :: Int -> Integer
peblfib =
    let fib 0 = 0
        fib 1 = 1
        fib n = peblfib (n-2) + peblfib (n-1)
        flst = map fib [0 .. ]
    in \k -> (flst !! k)

Now flst is a CAF which can be shared, and indeed it is:
*MFib> peblfib 40
102334155
(0.00 secs, 0 bytes)

>
> Best regards,
>
> Simon

Hope this gets you started,

Daniel



More information about the Haskell-Cafe mailing list