[Haskell-cafe] Re: Troubles understanding memoization in SOE

ChrisK haskell at list.mightyreason.com
Wed Sep 26 17:03:31 EDT 2007


Peter Verswyvelen wrote:
>  Paul L wrote:
> 
>> We recently wrote a paper about the leak problem. The draft is at
>> http://www.cs.yale.edu/~hl293/download/leak.pdf. Comments are welcome!
> I'm trying to understand the following in this paper:
> 
> (A) repeat x = x : repeat x
> or, in lambdas:
> (B) repeat = λx → x : repeat x
> This requires O(n) space. But we can achieve O(1) space by writing instead:
> (C) repeat = λx → let xs = x : xs in xs
> 
> Let me see if I understand this correctly. Since I'm an imperative
> programmer, I'll try a bit of C++ here.
> 
> struct Cell : Value
> {
> Value* head;
> Value* tail;
> };
> 
> So in (A) and (B), a Cell c1 is allocated, and c1->head would be a
> pointer to x, and c1->tail would be a pointer to a newly allocated Cell
> c2, etc etc, hence O(n) space complexity
> In (C) however, a Cell xs is allocated, and xs->head is also a pointer
> to x, but xs->tail is a pointer the cell xs again, creating one circular
> data structure, hence O(1) space complexity.
> 
> Is this more or less correct?

Yes.  Also I believe (A) and (B) are the same as

repeat = fix (\ f -> (\ x -> x : f x ) )

While (C) is

repeat = \x -> fix (\ me -> x : me )
or
repeat x = fix (\me -> x : me )

> 
> I'm also trying to figure out how the "fixed point combinator" works, so
> the fix f = f (fix f), and it's effect on space/time complexity. Any
> good tutorials on that one? Or is this the one
> http://haskell.org/haskellwiki/Recursive_function_theory. Looks a bit
> scary at first sight ;-)
> 
> Thanks again,
> Peter

A good way to think about 'fix' is that it lets us write a definition that talks
about the thing that we are defining.  This is very common in Haskell, since
every recursive definition or mutually recursive set of definitions talks about
itself.  (Every Haskell let is a bit like Scheme's letrec).

This is also common in C++ and Java when an object "talks about" itself while it
is being constructed.

Warning: It is easy for a programming mistake to create a dependency loop (or
"black hole") when using 'fix' improperly.  This is similar to a C++/Java object
calling itself during construction when it is in only a partially constructed
state and causing an error.

Now take the definition from GHC's base package, currently in
http://darcs.haskell.org/packages/base/Data/Function.hs

> -- | @'fix' f@ is the least fixed point of the function @f@,
> -- i.e. the least defined @x@ such that @f x = x at .
> fix :: (a -> a) -> a
> fix f = let x = f x in x

Consider the type of fix, namely (a->a)->a.
Note that is not the same as a->a->a which is actually a->(a->a).

For (A) and (B) the type 'a' is the type of 'f' which is a function.
If repeat :: q -> [q] then 'a' is 'q->[q]' and the fix is of type
( (q->[q]) -> (q->[q]) ) -> (q->[q])

For (C) the type 'a' is the type of 'me' which is a list, and the fix is of type
( [q] -> [q] ) -> [q]


Expand (C) step by step:

-- Rename x to be q to avoid name collisions
repeat = \q -> fix (\me -> q : me )
-- Now substitute the definition of fix using f = (\me -> q : me)
repeat = \q -> let x = (\me -> q : me) x in x
-- Apply the function with me replaced by x
repeat = \q -> let x = q : x in x
Optionally convert to pointful notation
repeat q = let x = q : x in x

And these are your definition (C)

Expand (A) or (B) step by step:

Rename x to q to avoid name collision later
repeat = fix (\ f -> (\ q -> q : f q ) )
Expand definition of fix replacing f with (\ f -> (\ q -> q : f q ) )
repeat = let x = (\ f -> (\ q -> q : f q ) ) x in x
Apply the function replacing f with x
repeat = let x = (\ q -> q : x q ) ) in x
Simplify by noting that 'x' and 'repeat' name the same thing
repeat = (\q -> q : repeat q)
Optionally convert to pointful notation
repeat q = q : repeat q

-- 
Chris



More information about the Haskell-Cafe mailing list