[Haskell-cafe] Shared thunk optimization. Looking to solidify my understanding

wren ng thornton wren at freegeek.org
Wed Sep 22 16:04:54 EDT 2010


On 9/22/10 11:48 AM, Daniel Fischer wrote:
> On Wednesday 22 September 2010 17:10:06, David Sankel wrote:
>> The following code (full code available here[1], example taken from
>> comments here[2]),
>>
>> const' = \a _ ->  a
>>
>> test1 c = let a = const' (nthPrime 100000)
>>            in (a c, a c)
>>
>> test2 c = let a = \_ ->  (nthPrime 100000)
>>            in (a c, a c)
>>
>> test1, although denotationally equivalent to test2 runs about twice as
>> fast. My questions are:
>>
>>     - What is the optimization that test1 is taking advantage of called?
>
> Sharing. test1 computes nthPrime 100000 only once, test2 twice.

Actually, I'd call it partial evaluation.

That is, if we expand the notation for multiple lambdas and inline 
const' then we get

     test1 c =
         let a = (\x -> \_ -> x) (nthPrime 100000)
         in (a c, a c)

     test2 c =
         let a = \_ -> (nthPrime 100000)
         in (a c, a c)

Now, if we follow the evaluation we'll see

     (test1 G) -- for some G
{force test1 to WHNF}
     (\c ->
         let a = (\x -> \_ -> x) (nthPrime 100000)
         in (a c, a c))
     g
{force application to WHNF}
     let c = G in
     let a = (\x -> \_ -> x) (nthPrime 100000) in
     (a c, a c)

And here we're already in WHNF, but lets assume you're going for full NF.

     let c = G in
     let a = (\x -> \_ -> x) (nthPrime 100000) in
     (a c, a c)
{force a to WHNF == force application to WHNF}
     let c = G in
     let a =
         let x = nthPrime 100000 in
         \_ -> x in
     (a c, a c)
{force x to WHNF in the application of a to c}
     let c = G in
     let a =
         let x = X in -- for brevity
         \_ -> x in
     (a c, a c)
{force the application (itself) of a to c}
     let c = G in
     let a =
         let x = X in
         \_ -> x in
     (X, a c)
{force the application of a to c, the second one}
     let c = G in
     let a =
         let x = X in
         \_ -> x in
     (X, X)

Now, notice that because the binding of x was floated out in front of 
the ignored parameter to a, we only end up computing it once and sharing 
that X among all the different calls. This is typically called partial 
evaluation because we can partially evaluate the function a, even 
without knowing its arguments. Partial evaluation is a general 
optimization technique. It is, in fact, the same technique as floating 
invariants out of loops in imperative languages.

When GHC's optimizations are turned on, it realizes that the binding of 
x can be floated out of the lambda because it does not depend on the 
(ignored) parameter. Thus, in optimized code the two will look the same, 
provided the optimizer is smart enough to figure out when things can be 
floated out. But noone wants to be forced to guarantee that the 
optimizer is smart enough, which is why the Haskell specs say nothing 
about the exact evaluation order.

-- 
Live well,
~wren


More information about the Haskell-Cafe mailing list