[Haskell-cafe] memorize function with number parameterized types in GHC

Bin Jin bjin1990 at gmail.com
Mon Nov 7 02:29:29 CET 2011


Hi
This method is what I'm looking for. it's a nice general solution, but it
doesn't solve my problem here.
I'm using ghc 7.0.3, I tried to cache p2num and montgKeys in the way you
showed. It seems that ghc doesn't memorize p2num and reject to compile new
montgKeys.
I think caching values with dynamic types is complicated in ghc's runtime
environment. Anyone knows the details?
On Nov 7, 2011 7:07 AM, "wren ng thornton" <wren at freegeek.org> wrote:

> On 11/6/11 10:51 AM, Bin Jin wrote:
>
>> Yes, but I think it's not a funtion since the function didn't use the
>> parameter. So maybe there is a way to make memorizing possible.
>>
>
> In general, if the argument is not used then
>
>    \x -> E
>
> is equal to
>
>    let e = E in \x -> e
>
> Which we can make strict by adding a bang-pattern or a seq
>
>    let !e = E in \x -> e
>  ==
>    let e = E in e `seq` \x -> e
>
> The strictness isn't always necessary, but it helps to ensure that GHC
> doesn't get rid of the let-binding which would take us back to the original
> (\x -> E). Now, if we use this as the definition of the function, it'll
> ensure that the computation of E is done as a CAF and hence is memoized
> (since laziness is call-by-name + memoization).
>
>
> This trick can be generalized to any function of which parts of it are
> constant in some subset of parameters. That is, if we have
>
>    \x y z -> E (F (G H x) y) z
>
> then this can be converted into
>
>    let !h = H in
>    \x ->
>    let !g = G h x in
>    \y ->
>    let !f = F g y in
>    \z ->
>    E f z
>
> Now, whenever we want to use this function we pass in as many arguments as
> we are holding fixed, and force the resulting function in order to memoize
> the initial computations. For example, if the above function is called foo,
> then we could use it like:
>
>    forM xs $ \x -> do
>        let !foo_x = foo x
>        forM ys $ \y -> do
>            let !foo_x_y = foo_x y
>            forM zs $ \z -> do
>                let !foo_x_y_z = foo_x_y z
>                ...
>
> In this example we're performing loop invariant code motion, but doing so
> dynamically in order to maintain a separation between the definition of foo
> and its use.
>
> --
> Live well,
> ~wren
>
> ______________________________**_________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/**mailman/listinfo/haskell-cafe<http://www.haskell.org/mailman/listinfo/haskell-cafe>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20111107/15174eb1/attachment.htm>


More information about the Haskell-Cafe mailing list