Re: [Haskell-cafe] memoization

2013-07-24 Thread Andreas Abel

Sorry I screwed up.  The following is indeed memoizing:

fib5 :: Int - Integer
fib5 = \ x - fibs !! x
   where fibs = map fib [0 ..]
 fib 0 = 0
 fib 1 = 1
 fib n = fib5 (n-2) + fib5 (n-1)

Here, the eta-expansion does not matter.  But as you say, memoized_fib 
below is not memoizing, since x is in scope in the where clauses, even 
though they do not mention it.  Thus, for each x we get new 
definitions of fibs and fib.  Yet, this is only true for -O0.


For -O1 and greater, ghc seems to see that x is not mentioned in the 
where clauses and apparently lifts them out.  Thus, for -O1.. 
memoized_fib is also memoizing.  (I ran it, this time ;-) !)


Cheers,
Andreas

On 22.07.13 11:43 PM, Tom Ellis wrote:

On Mon, Jul 22, 2013 at 04:16:19PM +0200, Andreas Abel wrote:

In general, I would not trust such compiler magic, but just let-bind
anything I want memoized myself:

memoized_fib :: Int - Integer
memoized_fib x = fibs !! x
 where fibs  = map fib [0..]   -- lazily computed infinite list
   fib 0 = 0
   fib 1 = 1
   fib n = memoized_fib (n-2) + memoized_fib (n-1)

The eta-expansions do not matter.


I meant to write

  Then, eta-expansions do not matter.

(In general, they do matter.)


But this is *not* memoized (run it and see!).  The eta-expansions do
indeed matter (although I don't think they are truly eta-expasions because
of the desugaring of the where to a let).

What matters is not the let binding, but where the let binding occurs in
relation to the lambda.  There's no compiler magic here, just operational
semantics.

Tom

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2013-07-24 Thread Tom Ellis
On Wed, Jul 24, 2013 at 10:06:59AM +0200, Andreas Abel wrote:
 For -O1 and greater, ghc seems to see that x is not mentioned in the
 where clauses and apparently lifts them out.  Thus, for -O1..
 memoized_fib is also memoizing.  (I ran it, this time ;-) !)

Right, I believe this is the full laziness transformation I mentioned
before

http://foldoc.org/full+laziness 
 

 
http://www.haskell.org/pipermail/haskell-cafe/2013-February/105201.html

Tom

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2013-07-23 Thread Tom Ellis
On Mon, Jul 22, 2013 at 04:04:33PM -0700, wren ng thornton wrote:
 Consider rather,
 
 f1 = let y = blah blah in \x - x + y
 
 f2  x = let y = blah blah in x + y
 
 The former will memoize y and share it across all invocations of f1;
 whereas f2 will recompute y for each invocation.

Indeed.

 In principle, we could translate between these two forms (the f2 == f1
 direction requires detecting that y does not depend on x). However, in
 practice, the compiler has no way to decide which one is better since it
 involves a space/time tradeoff which: (a) requires the language to keep
 track of space and time costs, (b) would require whole-program analysis to
 determine the total space/time costs, and (c) requires the user's
 objective function to know how to weight the tradeoff ratio.

This is called the full laziness transformation

http://foldoc.org/full+laziness

and indeed with optimization on GHC (sometimes) does it, even when not 
appropriate

http://www.haskell.org/pipermail/haskell-cafe/2013-February/105201.html

Tom

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2013-07-23 Thread wren ng thornton
On 7/22/13 7:41 PM, David Thomas wrote:
 On Mon, Jul 22, 2013 at 4:04 PM, wren ng thornton w...@freegeek.org
wrote:
 In principle, we could translate between these two forms (the f2 == f1
 direction requires detecting that y does not depend on x). However, in
 practice, the compiler has no way to decide which one is better since it
 involves a space/time tradeoff which: (a) requires the language to keep
 track of space and time costs, (b) would require whole-program analysis to
 determine the total space/time costs, and (c) requires the user's
 objective function to know how to weight the tradeoff ratio.

 I, for one, would love to have a compiler do (a) based on (b), my
 specification of (c), and the ability to pin particular things...

Oh, so would I! But, having worked on this problem in a different
language, I'm well aware of how difficult it is to actually implement (a)
and (b).

-- 
Live well,
~wren


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2013-07-22 Thread KC
Have you tried the compiler?


On Sun, Jul 21, 2013 at 11:59 PM, Christopher Howard 
christopher.how...@frigidcode.com wrote:

  When I previously asked about memoization, I got the impression that
 memoization is not something that just happens magically in Haskell. Yet,
 on a Haskell wiki page about 
 Memoizationhttp://www.haskell.org/haskellwiki/Memoization#Memoization_with_recursion,
 an example given is

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


 I guess this works because, for example, I tried memoized_fib 1 and
 the interpreter took three or four seconds to calculate. But every
 subsequent call to memoized_fib 1 returns instantaneously (as does
 memoized_fib 10001).

 Could someone explain the technical details of why this works? Why is map
 fib [0 ..] not recalculated every time I call memoized_fib?

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
--
Regards,
KC
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2013-07-22 Thread Christopher Howard
On 07/21/2013 11:19 PM, KC wrote:
 Have you tried the compiler?

No. Would that work differently some how?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2013-07-22 Thread Chris Wong
 memoized_fib :: Int - Integer
 memoized_fib = (map fib [0 ..] !!)
where fib 0 = 0
  fib 1 = 1
  fib n = memoized_fib (n-2) + memoized_fib (n-1)


[.. snipped ..]

 Could someone explain the technical details of why this works? Why is map
 fib [0 ..] not recalculated every time I call memoized_fib?

A binding is memoized if, ignoring everything after the equals sign,
it looks like a constant.

In other words, these are memoized:

x = 2

Just x = blah

(x, y) = blah

f = \x - x + 1
-- f = ...

and these are not:

f x = x + 1

f (Just x, y) = x + y

If you remove the right-hand side of memoized_fib, you get:

memoized_fib = ...

This looks like a constant. So the value (map fib [0..] !!) is memoized.

If you change that line to

memoized_fib x = map fib [0..] !! x

GHC no longer memoizes it, and it runs much more slowly.

--
Chris Wong, fixpoint conjurer
  e: lambda.fa...@gmail.com
  w: http://lfairy.github.io/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2013-07-22 Thread Christopher Howard
On 07/21/2013 11:52 PM, Chris Wong wrote:
 [.. snipped ..]

 A binding is memoized if, ignoring everything after the equals sign,
 it looks like a constant.

 In other words, these are memoized:

 x = 2

 Just x = blah

 (x, y) = blah

 f = \x - x + 1
 -- f = ...

 and these are not:

 f x = x + 1

 f (Just x, y) = x + y

 If you remove the right-hand side of memoized_fib, you get:

 memoized_fib = ...

 This looks like a constant. So the value (map fib [0..] !!) is memoized.

 If you change that line to

 memoized_fib x = map fib [0..] !! x

 GHC no longer memoizes it, and it runs much more slowly.

 --
 Chris Wong, fixpoint conjurer
   e: lambda.fa...@gmail.com
   w: http://lfairy.github.io/

Thanks. That's very helpful to know. Yet, it seems rather strange and
arbitrary that f x = ... and f = \x - ... would be treated in such
a dramatically different manner.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2013-07-22 Thread Tom Ellis
On Mon, Jul 22, 2013 at 12:02:54AM -0800, Christopher Howard wrote:
  A binding is memoized if, ignoring everything after the equals sign,
  it looks like a constant.
[...]
 Thanks. That's very helpful to know. Yet, it seems rather strange and
 arbitrary that f x = ... and f = \x - ... would be treated in such
 a dramatically different manner.

This is actually rather subtle, and it's to do with desugaring of pattern
matching and where.

f x = expression s x where s = subexpression

desugars to

f = \x - (let s = subexpression in expression s x)

This is not the same as

f = expression s where s = subexpression

which desugars to

f = let s = subexpression in (expression s)

which I think is the same as

f = let s = subexpression in (\x - expression s x)

In the first case a new thunk for s is created each time an argument is
applied to f.  In the second case the same thunk for s exists for all
invocations of f.

This is nothing to do with explicit memoization by the compiler, but is
simply the operational semantics of lazy evaluation in terms of thunks.

(I think I got this all right, and if not I hope someone will chime in with
a correction.  I spent some time trying to grasp this a few months ago, but
as I said it's subtle, at least to someone like me who hasn't studied lambda
calculus in depth!)

Tom

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2013-07-22 Thread Tom Ellis
On Mon, Jul 22, 2013 at 07:52:06PM +1200, Chris Wong wrote:
 A binding is memoized if, ignoring everything after the equals sign,
 it looks like a constant.
 
 In other words, these are memoized:
[...]
 f = \x - x + 1
[...]
 and these are not:
 
 f x = x + 1

In what sense is the former memoised?  I'm not aware of any difference
between these two definitions.

Tom

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2013-07-22 Thread 14875
in this case, neither of them is memoized. because they don't have any data
in expressions.
memoized is for constants who have data structure in its expression


2013/7/22 Tom Ellis tom-lists-haskell-cafe-2...@jaguarpaw.co.uk

 On Mon, Jul 22, 2013 at 07:52:06PM +1200, Chris Wong wrote:
  A binding is memoized if, ignoring everything after the equals sign,
  it looks like a constant.
 
  In other words, these are memoized:
 [...]
  f = \x - x + 1
 [...]
  and these are not:
 
  f x = x + 1

 In what sense is the former memoised?  I'm not aware of any difference
 between these two definitions.

 Tom

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2013-07-22 Thread Andreas Abel

On 22.07.2013 09:52, Chris Wong wrote:

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



[.. snipped ..]


Could someone explain the technical details of why this works? Why is map
fib [0 ..] not recalculated every time I call memoized_fib?


A binding is memoized if, ignoring everything after the equals sign,
it looks like a constant.

In other words, these are memoized:

 x = 2

 Just x = blah

 (x, y) = blah

 f = \x - x + 1
 -- f = ...

and these are not:

 f x = x + 1

 f (Just x, y) = x + y

If you remove the right-hand side of memoized_fib, you get:

 memoized_fib = ...

This looks like a constant. So the value (map fib [0..] !!) is memoized.

If you change that line to

 memoized_fib x = map fib [0..] !! x

GHC no longer memoizes it, and it runs much more slowly.


True, but the essential thing to be memoized is not memoized_fib, which 
is a function, but the subexpression


  map fib [0..]

which is an infinite list, i.e., a value.

The rule must be like in

  let x = e

if e is purely applicative, then its subexpressions are memoized.
For instance, the following is also not memoizing:

fib3 :: Int - Integer
fib3 = \ x - map fib [0 ..] !! x
   where fib 0 = 0
 fib 1 = 1
 fib n = fib3 (n-2) + fib3 (n-1)

In general, I would not trust such compiler magic, but just let-bind 
anything I want memoized myself:


memoized_fib :: Int - Integer
memoized_fib x = fibs !! x
where fibs  = map fib [0..]   -- lazily computed infinite list
  fib 0 = 0
  fib 1 = 1
  fib n = memoized_fib (n-2) + memoized_fib (n-1)

The eta-expansions do not matter.

Cheers,
Andreas

--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2013-07-22 Thread Christopher Howard
On 07/22/2013 06:16 AM, Andreas Abel wrote:
 On 22.07.2013 09:52, Chris Wong wrote:

 True, but the essential thing to be memoized is not memoized_fib,
 which is a function, but the subexpression

   map fib [0..]

 which is an infinite list, i.e., a value.

 The rule must be like in

   let x = e

 if e is purely applicative, then its subexpressions are memoized.
 For instance, the following is also not memoizing:

 fib3 :: Int - Integer
 fib3 = \ x - map fib [0 ..] !! x
where fib 0 = 0
  fib 1 = 1
  fib n = fib3 (n-2) + fib3 (n-1)

 In general, I would not trust such compiler magic, but just let-bind
 anything I want memoized myself:

 memoized_fib :: Int - Integer
 memoized_fib x = fibs !! x
 where fibs  = map fib [0..]   -- lazily computed infinite list
   fib 0 = 0
   fib 1 = 1
   fib n = memoized_fib (n-2) + memoized_fib (n-1)

 The eta-expansions do not matter.

 Cheers,
 Andreas


Is this behavior codified somewhere? (I can't seem to find it in the GHC
user guide.)

The memoize package from hackage, interestingly enough, states that
[Our memoization technique] relies on implementation assumptions that,
while not guaranteed by the semantics of Haskell, appear to be true.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2013-07-22 Thread Tom Ellis
On Mon, Jul 22, 2013 at 04:16:19PM +0200, Andreas Abel wrote:
 In general, I would not trust such compiler magic, but just let-bind
 anything I want memoized myself:
 
 memoized_fib :: Int - Integer
 memoized_fib x = fibs !! x
 where fibs  = map fib [0..]   -- lazily computed infinite list
   fib 0 = 0
   fib 1 = 1
   fib n = memoized_fib (n-2) + memoized_fib (n-1)
 
 The eta-expansions do not matter.

But this is *not* memoized (run it and see!).  The eta-expansions do
indeed matter (although I don't think they are truly eta-expasions because
of the desugaring of the where to a let).

What matters is not the let binding, but where the let binding occurs in
relation to the lambda.  There's no compiler magic here, just operational
semantics.

Tom

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2013-07-22 Thread wren ng thornton
On 7/22/13 9:06 AM, Tom Ellis wrote:
 On Mon, Jul 22, 2013 at 07:52:06PM +1200, Chris Wong wrote:
 A binding is memoized if, ignoring everything after the equals sign,
 it looks like a constant.

 In other words, these are memoized:
 [...]
  f = \x - x + 1
 [...]
 and these are not:

  f x = x + 1

 In what sense is the former memoised?  I'm not aware of any difference
 between these two definitions.

Consider rather,

f1 = let y = blah blah in \x - x + y

f2  x = let y = blah blah in x + y

The former will memoize y and share it across all invocations of f1;
whereas f2 will recompute y for each invocation.

In principle, we could translate between these two forms (the f2 == f1
direction requires detecting that y does not depend on x). However, in
practice, the compiler has no way to decide which one is better since it
involves a space/time tradeoff which: (a) requires the language to keep
track of space and time costs, (b) would require whole-program analysis to
determine the total space/time costs, and (c) requires the user's
objective function to know how to weight the tradeoff ratio.

-- 
Live well,
~wren


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2013-07-22 Thread David Thomas
I, for one, would love to have a compiler do (a) based on (b), my
specification of (c), and the ability to pin particular things...


On Mon, Jul 22, 2013 at 4:04 PM, wren ng thornton w...@freegeek.org wrote:

 On 7/22/13 9:06 AM, Tom Ellis wrote:
  On Mon, Jul 22, 2013 at 07:52:06PM +1200, Chris Wong wrote:
  A binding is memoized if, ignoring everything after the equals sign,
  it looks like a constant.
 
  In other words, these are memoized:
  [...]
   f = \x - x + 1
  [...]
  and these are not:
 
   f x = x + 1
 
  In what sense is the former memoised?  I'm not aware of any difference
  between these two definitions.

 Consider rather,

 f1 = let y = blah blah in \x - x + y

 f2  x = let y = blah blah in x + y

 The former will memoize y and share it across all invocations of f1;
 whereas f2 will recompute y for each invocation.

 In principle, we could translate between these two forms (the f2 == f1
 direction requires detecting that y does not depend on x). However, in
 practice, the compiler has no way to decide which one is better since it
 involves a space/time tradeoff which: (a) requires the language to keep
 track of space and time costs, (b) would require whole-program analysis to
 determine the total space/time costs, and (c) requires the user's
 objective function to know how to weight the tradeoff ratio.

 --
 Live well,
 ~wren


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2013-07-22 Thread Christopher Howard
On 07/22/2013 03:41 PM, David Thomas wrote:
 I, for one, would love to have a compiler do (a) based on (b), my
 specification of (c), and the ability to pin particular things...



The reason it is a big deal to me is it sometimes the more
natural-looking (read, declarative) way of writing a function is only
reasonably efficient if certain parts are memoized. Otherwise I end up
having to pass around extra arguments or data structures representing
the data I don't want to be recalculated.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization of functions

2011-09-06 Thread briand
On Tue, 06 Sep 2011 15:16:09 -0400
Michael Orlitzky mich...@orlitzky.com wrote:

 I'm working on a program where I need to compute a gajillion (171442176)
 polynomials and evaluate them more than once. This is the definition of
 the polynomial, and it is expensive to compute:
 
  polynomial :: Tetrahedron - (RealFunction Point)
  polynomial t =
  sum [ (c t i j k l) `cmult` (beta t i j k l) | i - [0..3],
 j - [0..3],
 k - [0..3],
 l - [0..3],
 i + j + k + l == 3]
 
 Currently, I'm storing the polynomials in an array, which is quickly
 devoured by the OOM killer. This makes me wonder: how much memory can I
 expect to use storing a function in an array? Is it possible to save
 some space through strictness? Does that question even make sense?
 

it's not clear what the relation to your final result is, e.g. can you can 
computer partial values and then store them ?  or are you having to calculate 
all 171442176 values and then do further computation with those values ?

if you need to store the results of the polynomials and then use them for 
further computation, well then it would seem that you're out of luck.

unboxing is likely to be your best friend.

in the event that unboxed arrays would help, I highly recommend repa.

Brian


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization/call-by-need

2010-09-20 Thread Henning Thielemann
Alex Rozenshteyn schrieb:
 I feel that there is something that I don't understand completely:  I
 have been told that Haskell does not memoize function call, e.g.
 slowFib 50
 will run just as slowly each time it is called.  However, I have read
 that Haskell has call-by-need semantics, which were described as lazy
 evaluation with memoization

http://www.haskell.org/haskellwiki/Memoization

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization/call-by-need

2010-09-16 Thread Ketil Malde
Alex Rozenshteyn rpglove...@gmail.com writes:

 I understand that

 fib50 = slowFib 50

 will take a while to run the first time but be instant each subsequent call;
 does this count as memoization?

I didn't see anybody else answering this in so many words, but I'd say
no, since you only name one particular value.  Memoization of slowFib
would mean to provide a replacement for the *function* that remembers
previous answers.

Try e.g. these in GHCi (import (i.e. :m +) Data.Array for memoFib):

  slowFib 0 = 1; slowFib 1 = 1; slowFib x = slowFib (x-1) + slowFib (x-2)
  memoFib x = a!x where a = listArray (0,n) (1:1:[ a!(x-1)+a!(x-2) | 
x-[2..99]])

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization/call-by-need

2010-09-16 Thread Román González
Alex,

Maybe this pdf can enlighten you a little bit about memoization and lazy
evaluation in Haskell =
http://www.cs.uu.nl/wiki/pub/USCS2010/CourseMaterials/A5-memo-slides-english.pdf

Cheers.

Roman.-


I feel that there is something that I don't understand completely:  I have
 been told that Haskell does not memoize function call, e.g.

 slowFib 50

will run just as slowly each time it is called.  However, I have read that
 Haskell has call-by-need semantics, which were described as lazy evaluation
 with memoization


 I understand that

 fib50 = slowFib 50

will take a while to run the first time but be instant each subsequent call;
 does this count as memoization?


 (I'm trying to understand Purely Functional Data Structures, hence this
question)


-- 

  Alex R
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization/call-by-need

2010-09-15 Thread Tim Chevalier
On 9/15/10, Alex Rozenshteyn rpglove...@gmail.com wrote:
 I feel that there is something that I don't understand completely:  I have
 been told that Haskell does not memoize function call, e.g.
  slowFib 50
 will run just as slowly each time it is called.  However, I have read that
 Haskell has call-by-need semantics, which were described as lazy evaluation
 with memoization

 I understand that
  fib50 = slowFib 50
 will take a while to run the first time but be instant each subsequent call;
 does this count as memoization?


Hi, Alex --

Haskell's informal semantics dictate that if we evaluate the expression:

let fib50 = slowFib 50 in
  fib50 + fib50

then the expression (slowFib 50) will be evaluated only once, not
twice, because it has a name. On the other hand, if you wrote:

let fib50 = slowFib 50 in
  fib50 + (slowFib 50)

then (slowFib 50) would be evaluated twice, because there's no
principle requiring the compiler to notice that (slowFib 50) is the
same expression as the one bound to fib50.

An optimization called full laziness can accomplish the kind of
stronger memoization you were suggesting in some cases, but GHC
doesn't do it consistently, as it can make performance worse.

Cheers,
Tim

-- 
Tim Chevalier * http://cs.pdx.edu/~tjc * Often in error, never in doubt
Both of them are to world religions what JavaScript is to programming
languages. -- Juli Mallett, on Satanism and Wicca
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization/call-by-need

2010-09-15 Thread Daniel Fischer
On Wednesday 15 September 2010 22:38:48, Tim Chevalier wrote:
 On the other hand, if you wrote:

 let fib50 = slowFib 50 in
   fib50 + (slowFib 50)

 then (slowFib 50) would be evaluated twice, because there's no
 principle requiring the compiler to notice that (slowFib 50) is the
 same expression as the one bound to fib50.

If you compile your module with ghc -O[2], ghc does notice, whether you 
give it a name once or not - without optimisations, it doesn't, however.
And if the two expressions appear far enough apart, it will probably not 
notice with optimisations either.
The upshot is, if you don't name an expression, the compiler *might* notice 
repeated use and share it, but you'd better not rely on it. If you want an 
expression to be shared, name it - then a decent implementation will share 
it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization/call-by-need

2010-09-15 Thread Conal Elliott
Hi Alex,

In Haskell, data structures cache, while functions do not.

Memoization is conversion of functions into data structures (and then
trivially re-wrapping as functions) so as to exploit the caching property of
data structures to get caching functions.

  - Conal

On Wed, Sep 15, 2010 at 11:03 AM, Alex Rozenshteyn rpglove...@gmail.comwrote:

 I feel that there is something that I don't understand completely:  I have
 been told that Haskell does not memoize function call, e.g.
  slowFib 50
 will run just as slowly each time it is called.  However, I have read that
 Haskell has call-by-need semantics, which were described as lazy evaluation
 with memoization

 I understand that
  fib50 = slowFib 50
 will take a while to run the first time but be instant each subsequent
 call; does this count as memoization?

 (I'm trying to understand Purely Functional Data Structures, hence this
 question)

 --
   Alex R


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization/call-by-need

2010-09-15 Thread wren ng thornton

On 9/15/10 10:39 PM, Conal Elliott wrote:

Hi Alex,

In Haskell, data structures cache, while functions do not.


Exactly. What this means is that when you call (slowFib 50) Haskell does 
not alter slowFib in any way to track that it maps 50 to $whatever; 
however, it does track that that particular expression instance 
evaluates to $whatever. This is why, when you define fib50=(slowFib 50) 
it only needs to compute $whatever the first time the value of fib50 is 
required. After the first evaluation it's the same as if we had defined 
fib50=$whatever.


So, the function being memoized is the evaluation function of Haskell 
itself, not any of the functions _in_ the language. There are various 
libraries for memoizing functions in Haskell, they're just not part of 
the language definition.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-09 Thread Edward Kmett
On Thu, Jul 8, 2010 at 5:30 PM, Angel de Vicente ang...@iac.es wrote:

 Hi,

 I'm going through the first chapters of the Real World Haskell book,
 so I'm still a complete newbie, but today I was hoping I could solve
 the following function in Haskell, for large numbers (n  108)

 f(n) = max(n,f(n/2)+f(n/3)+f(n/4))

 I've seen examples of memoization in Haskell to solve fibonacci
 numbers, which involved computing (lazily) all the fibonacci numbers
 up to the required n. But in this case, for a given n, we only need to
 compute very few intermediate results.

 How could one go about solving this efficiently with Haskell?

 We can do this very efficiently by making a structure that we can index in
sub-linear time.

But first,

{-# LANGUAGE BangPatterns #-}

import Data.Function (fix)

Lets define f, but make it use 'open recursion' rather than call itself
directly.

f :: (Int - Int) - Int - Int
f mf 0 = 0
f mf n = max n $ mf (div n 2) +
 mf (div n 3) +
 mf (div n 4)

You can get an unmemoized f by using `fix f`

This will let you test that f does what you mean for small values of f by
calling, for example: `fix f 123` = 144

We could memoize this by defining:

f_list :: [Int]
f_list = map (f faster_f) [0..]

faster_f :: Int - Int
faster_f n = f_list !! n

That performs passably well, and replaces what was going to take O(n^3) time
with something that memoizes the intermediate results.

But it still takes linear time just to index to find the memoized answer for
`mf`. This means that results like:

*Main Data.List faster_f 123801
248604

are tolerable, but the result doesn't scale much better than that. We can do
better!

First lets define an infinite tree:

data Tree a = Tree (Tree a) a (Tree a)
instance Functor Tree where
fmap f (Tree l m r) = Tree (fmap f l) (f m) (fmap f r)

And then we'll define a way to index into it, so we can find a node with
index n in O(log n) time instead:

index :: Tree a - Int - a
index (Tree _ m _) 0 = m
index (Tree l _ r) n = case (n - 1) `divMod` 2 of
(q,0) - index l q
(q,1) - index r q

... and we may find a tree full of natural numbers to be convenient so we
don't have to fiddle around with those indices:

nats :: Tree Int
nats = go 0 1
where
go !n !s = Tree (go l s') n (go r s')
where
l = n + s
r = l + s
s' = s * 2

Since we can index, you can just convert a tree into a list:

toList :: Tree a - [a]
toList as = map (index as) [0..]

You can check the work so far by verifying that `toList nats` gives you
[0..]

Now,

f_tree :: Tree Int
f_tree = fmap (f fastest_f) nats

fastest_f :: Int - Int
fastest_f = index f_tree

works just like with list above, but instead of taking linear time to find
each node, can chase it down in logarithmic time.

The result is considerably faster:

*Main fastest_f 12380192300
67652175206

*Main fastest_f 12793129379123
120695231674999

In fact it is so much faster that you can go through and replace Int with
Integer above and get ridiculously large answers almost instantaneously

*Main fastest_f' 1230891823091823018203123
93721573993600178112200489

*Main fastest_f' 12308918230918230182031231231293810923
11097012733777002208302545289166620866358

-Edward Kmett
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-09 Thread Angel de Vicente

Hi,

thanks for all the replies. I'm off now to try all the suggestions...

Cheers,
Ángel de Vicente
--
http://www.iac.es/galeria/angelv/

High Performance Computing Support PostDoc
Instituto de Astrofísica de Canarias
-
ADVERTENCIA: Sobre la privacidad y cumplimiento de la Ley de Protección de 
Datos, acceda a http://www.iac.es/disclaimer.php
WARNING: For more information on privacy and fulfilment of the Law concerning 
the Protection of Data, consult http://www.iac.es/disclaimer.php?lang=en

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-09 Thread Daniel Fischer
On Friday 09 July 2010 01:03:48, Luke Palmer wrote:
 On Thu, Jul 8, 2010 at 4:23 PM, Daniel Fischer daniel.is.fisc...@web.de 
wrote:
  On Friday 09 July 2010 00:10:24, Daniel Fischer wrote:
  You can also use a library (e.g.
  http://hackage.haskell.org/package/data- memocombinators) to do the
  memoisation for you.
 
  Well, actualy, I think http://hackage.haskell.org/package/MemoTrie
  would be the better choice for the moment, data-memocombinators
  doesn't seem to offer the functionality we need out of the box.

 I'm interested to hear what functionality MemoTrie has that
 data-memocombinators does not.  I wrote the latter in hopes that it
 would be strictly more powerful*.

It's probably my night-blindness, but I didn't see an immediate way to 
memoise a simple function on a short look at the docs, like

memo :: (ConstraintOn a) = (a - b) - a - b

, which Data.MemoTrie provides (together with memo2 and memo3, which data-
memocombinators provide too).

Taking a closer look at the docs in daylight, I see data-mc provides that 
out of the box too, the stuff is just differently named (bool, char, 
integral, ...) - which I didn't expect.

So you could take it as an indication that I'm visually impaired, or as an 
indication that the docs aren't as obvious as they could be.

Cheers,
Daniel

 Luke

 * Actually MemoTrie wasn't around when I wrote that, but I meant the
 combinatory technique should be strictly more powerful than a
 typeclass technique.  And data-memocombinators has many primitives, so
 I'm still curious.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-09 Thread Mike Dillon
begin Edward Kmett quotation:
 The result is considerably faster:
 
 *Main fastest_f 12380192300
 67652175206
 
 *Main fastest_f 12793129379123
 120695231674999

I just thought I'd point out that running with these particular values
on a machine with a 32 bit Int will cause your machine to go deep into
swap... Anything constant greater that maxBound is being wrapped back to
the negative side, causing havoc to ensue. I changed the open version of
f to look like this to exclude negative values:

f :: (Int - Int) - Int - Int
f mf 0 = 0
f mf n | n  0 = error $ Invalid n value:  ++ show n
f mf n | otherwise = max n $ mf (div n 2) +
 mf (div n 3) +
 mf (div n 4)

-md
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-09 Thread Edward Kmett
Very true. I was executing the large Int-based examples on a 64 bit machine.


You can of course flip over to Integer on either 32 or 64 bit machines and
alleviate the problem with undetected overflow. Of course that doesn't help
with negative initial inputs
;)

I do agree It is still probably a good idea to either filter the negative
case like you do here, or, since it is well defined, extend the scope of the
memo table to the full Int range by explicitly memoizing negative vales as
well.

-Edward Kmett

On Fri, Jul 9, 2010 at 11:51 AM, Mike Dillon m...@embody.org wrote:

 begin Edward Kmett quotation:
  The result is considerably faster:
 
  *Main fastest_f 12380192300
  67652175206
 
  *Main fastest_f 12793129379123
  120695231674999

 I just thought I'd point out that running with these particular values
 on a machine with a 32 bit Int will cause your machine to go deep into
 swap... Anything constant greater that maxBound is being wrapped back to
 the negative side, causing havoc to ensue. I changed the open version of
 f to look like this to exclude negative values:

f :: (Int - Int) - Int - Int
f mf 0 = 0
 f mf n | n  0 = error $ Invalid n value:  ++ show n
f mf n | otherwise = max n $ mf (div n 2) +
  mf (div n
 3) +
 mf (div n
 4)

 -md

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-08 Thread Daniel Fischer
On Thursday 08 July 2010 23:30:05, Angel de Vicente wrote:
 Hi,

 I'm going through the first chapters of the Real World Haskell book,
 so I'm still a complete newbie, but today I was hoping I could solve
 the following function in Haskell, for large numbers (n  108)

 f(n) = max(n,f(n/2)+f(n/3)+f(n/4))

You need some base case or you'll have infinite recursion.


 I've seen examples of memoization in Haskell to solve fibonacci
 numbers, which involved computing (lazily) all the fibonacci numbers
 up to the required n. But in this case, for a given n, we only need to
 compute very few intermediate results.

 How could one go about solving this efficiently with Haskell?

If f has the appropriate type and the base case is f 0 = 0,

module Memo where

import Data.Array

f :: (Integral a, Ord a, Ix a) = a - a
f n = memo ! n
  where
memo = array (0,n) $ (0,0) : 
   [(i, max i (memo!(i `quot` 2) + memo!(i `quot` 3) 
 + memo!(i `quot` 4))) | i - [1 .. n]]

is wasteful regarding space, but it calculates only the needed values and 
very simple.
(to verify:
module Memo where

import Data.Array
import Debug.Trace

f :: (Integral a, Ord a, Ix a) = a - a
f n = memo ! n
  where
memo = array (0,n) $ (0,0) : 
[(i, max (trace (calc  ++ show i) i) (memo!(i `quot` 2) 
 + memo!(i `quot` 3) + memo!(i `quot` 4))) | i - [1 .. n]]

)

You can also use a library (e.g. http://hackage.haskell.org/package/data-
memocombinators) to do the memoisation for you.

Another fairly simple method to memoise is using a Map and State,

import qualified Data.Map as Map
import Control.Monad.State

f :: (Integral a) = a - a
f n = evalState (memof n) (Map.singleton 0 0)
  where
memof k = do
  mb - gets (Map.lookup k)
  case mb of
Just r - return r
Nothing - do
  vls - mapM memof [k `quot` 2, k `quot` 3, k `quot` 4]
  let vl = max k (sum vls)
  modify (Map.insert k vl)
  return vl


 Thanks in advance,
 Ángel de Vicente

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-08 Thread Daniel Fischer
On Friday 09 July 2010 00:10:24, Daniel Fischer wrote:
 You can also use a library (e.g.
 http://hackage.haskell.org/package/data- memocombinators) to do the
 memoisation for you.

Well, actualy, I think http://hackage.haskell.org/package/MemoTrie would be 
the better choice for the moment, data-memocombinators doesn't seem to 
offer the functionality we need out of the box.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-08 Thread Luke Palmer
On Thu, Jul 8, 2010 at 4:23 PM, Daniel Fischer daniel.is.fisc...@web.de wrote:
 On Friday 09 July 2010 00:10:24, Daniel Fischer wrote:
 You can also use a library (e.g.
 http://hackage.haskell.org/package/data- memocombinators) to do the
 memoisation for you.

 Well, actualy, I think http://hackage.haskell.org/package/MemoTrie would be
 the better choice for the moment, data-memocombinators doesn't seem to
 offer the functionality we need out of the box.

I'm interested to hear what functionality MemoTrie has that
data-memocombinators does not.  I wrote the latter in hopes that it
would be strictly more powerful*.

Luke

* Actually MemoTrie wasn't around when I wrote that, but I meant the
combinatory technique should be strictly more powerful than a
typeclass technique.  And data-memocombinators has many primitives, so
I'm still curious.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-08 Thread Michael Mossey



Daniel Fischer wrote:


If f has the appropriate type and the base case is f 0 = 0,

module Memo where

import Data.Array

f :: (Integral a, Ord a, Ix a) = a - a
f n = memo ! n
  where
memo = array (0,n) $ (0,0) : 
   [(i, max i (memo!(i `quot` 2) + memo!(i `quot` 3) 
 + memo!(i `quot` 4))) | i - [1 .. n]]


is wasteful regarding space, but it calculates only the needed values and 
very simple.


Can someone explain to a beginner like me why this calculates only the 
needed values? The list comprehension draws from 1..n so I don't 
understand why all those values wouldn't be computed.


Thanks
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-08 Thread Gregory Crosswhite

 On 7/8/10 9:17 PM, Michael Mossey wrote:



Daniel Fischer wrote:


If f has the appropriate type and the base case is f 0 = 0,

module Memo where

import Data.Array

f :: (Integral a, Ord a, Ix a) = a - a
f n = memo ! n
  where
memo = array (0,n) $ (0,0) :[(i, max i (memo!(i 
`quot` 2) + memo!(i `quot` 3)  + memo!(i `quot` 
4))) | i - [1 .. n]]


is wasteful regarding space, but it calculates only the needed values 
and very simple.


Can someone explain to a beginner like me why this calculates only the 
needed values? The list comprehension draws from 1..n so I don't 
understand why all those values wouldn't be computed.




The second pair of each element of the list will remain unevaluated 
until demanded --- it's the beauty of being a lazy language.  :-)  Put 
another way, although it might look like the list contains values (and 
technically it does due to referential transparency), at a lower level 
what it actually contains are pairs such that the second element is 
represented not by number but rather by a function that can be called to 
obtain its value.


Cheers,
Greg

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-08 Thread Michael Mossey
Thanks, okay the next question is: how does the memoization work? Each 
call to memo seems to construct a new array, if the same f(n) is 
encountered several times in the recursive branching, it would be 
computed several times. Am I wrong?

Thanks,
Mike

Gregory Crosswhite wrote:

 On 7/8/10 9:17 PM, Michael Mossey wrote:



Daniel Fischer wrote:


If f has the appropriate type and the base case is f 0 = 0,

module Memo where

import Data.Array

f :: (Integral a, Ord a, Ix a) = a - a
f n = memo ! n
  where
memo = array (0,n) $ (0,0) :[(i, max i (memo!(i 
`quot` 2) + memo!(i `quot` 3)  + memo!(i `quot` 
4))) | i - [1 .. n]]


is wasteful regarding space, but it calculates only the needed values 
and very simple.


Can someone explain to a beginner like me why this calculates only the 
needed values? The list comprehension draws from 1..n so I don't 
understand why all those values wouldn't be computed.




The second pair of each element of the list will remain unevaluated 
until demanded --- it's the beauty of being a lazy language.  :-)  Put 
another way, although it might look like the list contains values (and 
technically it does due to referential transparency), at a lower level 
what it actually contains are pairs such that the second element is 
represented not by number but rather by a function that can be called to 
obtain its value.


Cheers,
Greg

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization in Haskell?

2010-07-08 Thread Gregory Crosswhite
 You're correct in pointing out that f uses memoization inside of 
itself to cache the intermediate values that it commutes, but those 
values don't get shared between invocations of f;  thus, if you call f 
with the same value of n several times then the memo table might get 
reconstructed redundantly.  (However, there are other strategies for 
memoization that are persistent across calls.)


Cheers,
Greg

On 7/8/10 9:59 PM, Michael Mossey wrote:
Thanks, okay the next question is: how does the memoization work? Each 
call to memo seems to construct a new array, if the same f(n) is 
encountered several times in the recursive branching, it would be 
computed several times. Am I wrong?

Thanks,
Mike

Gregory Crosswhite wrote:

 On 7/8/10 9:17 PM, Michael Mossey wrote:



Daniel Fischer wrote:


If f has the appropriate type and the base case is f 0 = 0,

module Memo where

import Data.Array

f :: (Integral a, Ord a, Ix a) = a - a
f n = memo ! n
  where
memo = array (0,n) $ (0,0) :[(i, max i (memo!(i 
`quot` 2) + memo!(i `quot` 3)  + memo!(i `quot` 
4))) | i - [1 .. n]]


is wasteful regarding space, but it calculates only the needed 
values and very simple.


Can someone explain to a beginner like me why this calculates only 
the needed values? The list comprehension draws from 1..n so I don't 
understand why all those values wouldn't be computed.




The second pair of each element of the list will remain unevaluated 
until demanded --- it's the beauty of being a lazy language.  :-)  
Put another way, although it might look like the list contains values 
(and technically it does due to referential transparency), at a lower 
level what it actually contains are pairs such that the second 
element is represented not by number but rather by a function that 
can be called to obtain its value.


Cheers,
Greg

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2009-09-11 Thread staafmeister


Hi,

Investigating memoization inspired by replies from this thread. I
encountered something strange in the behavior of ghci. Small chance it's a
bug, it probably is a feature, but I certainly don't understand it :)

The interpreter session went as follows

GHCi, version 6.10.4: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
Prelude :load test_bug.hs
[1 of 1] Compiling Main ( test_bug.hs, interpreted )
Ok, modules loaded: Main.
*Main let s1 = memo2 solve2
Loading package syb ... linking ... done.
Loading package array-0.2.0.0 ... linking ... done.
Loading package containers-0.2.0.1 ... linking ... done.
Loading package filepath-1.1.0.2 ... linking ... done.
Loading package old-locale-1.0.0.1 ... linking ... done.
Loading package old-time-1.0.0.2 ... linking ... done.
Loading package unix-2.3.2.0 ... linking ... done.
Loading package directory-1.0.0.3 ... linking ... done.
Loading package process-1.0.1.1 ... linking ... done.
Loading package random-1.0.0.1 ... linking ... done.
Loading package haskell98 ... linking ... done.
*Main :type s1
s1 :: [()] - [()] - ModP
*Main let s2 a b = memo2 solve2 a b
*Main :type s2
s2 :: (Eq t) = [t] - [t] - ModP

Here memo2 is a function that works like a combinator to obtain a memoized
recursive function. However the type of the function depends on how I define
it. In point-free style it gets the wrong
type, however if I define (s2) with explicit arguments the type is correct?
Do you know what happens here? I would expect the types to be the same.

Another question is: I use now makeStableName for equality but using this
function memoization does not work and it still takes a long (exponential?)
time to go through the codejam testcases. The memoization using data.map
works flawless.

Greetings,
Gerben

ps.

The content of test_bug.hs is

import Data.IORef
import System.IO.Unsafe
import Control.Exception
import qualified Data.Map as M
import Text.Printf
import qualified Data.HashTable as H
import System.Mem.StableName
import Data.Ratio
import Array

memo f = unsafePerformIO $ do
  cache - H.new (==) (H.hashInt . hashStableName)
  let cacheFunc = \x - unsafePerformIO $ do stable - makeStableName x
 lup - H.lookup cache stable
 case lup of
   Just y - return y
   Nothing - do let res = f
cacheFunc x
 H.insert cache
stable res
 return res
  return cacheFunc

memo2 f = curry $ memo (\g (x,y) - f (curry g) x y)

newtype ModP = ModP Integer deriving Eq

p=10007

instance Show ModP where
  show (ModP x) = printf %d x

instance Num ModP where
  ModP x + ModP y = ModP ((x + y) `mod` p)
  fromInteger x = ModP (x `mod` p)
  ModP x * ModP y = ModP ((x * y) `mod` p)
  abs = undefined
  signum = undefined

solve2 f _ [] = 1::ModP
solve2 f [] _ = 0::ModP
solve2 f (hs:ts) t@(ht:tt) | hs==ht = f ts tt + f ts t
   | otherwise = f ts t

go (run, line) = Case #++show run++: ++show ((memo2 solve2) line
welcome to code jam)

main = interact $ unlines . map go . zip [1..] . tail . lines

-- 
View this message in context: 
http://www.nabble.com/memoization-tp25306687p25400506.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2009-09-10 Thread staafmeister

Thanks to reactions!

What do you think about such a function? This function is
still a bit dangerous (I think). I don't know how to make
sure the compiler does not lift cache to something global.

But on the other hand this use of unsafePerformIO is legit
because it doesn't alter the referential transparency of 
the function. The same as in DiffArray.

Greetings
Gerben

memo f =
  let cache = unsafePerformIO $ newIORef M.empty
  cachedFunc x = unsafePerformIO (do
   m - readIORef cache
   case M.lookup x m of
 Just y - return y
 Nothing - do let res = f x
   writeIORef cache $ M.insert x res m
   return res)
  in cachedFunc

memo2 f = curry $ memo $ uncurry f

-- 
View this message in context: 
http://www.nabble.com/memoization-tp25306687p25381881.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2009-09-05 Thread Daniel Fischer
Am Samstag 05 September 2009 11:52:50 schrieb staafmeister:
 Hi,

 I participating in de google code jam this year and I want to try to use
 haskell. The following
 simple  http://code.google.com/codejam/contest/dashboard?c=90101#s=p2
 problem
 would have the beautiful haskell solution.

 import Data.MemoTrie
 import Data.Char
 import Data.Word
 import Text.Printf

 newtype ModP = ModP Integer deriving Eq

 p=1

 instance Show ModP where
   show (ModP x) = printf %04d x

 instance Num ModP where
   ModP x + ModP y = ModP ((x + y) `mod` p)
   fromInteger x = ModP (x `mod` p)
   ModP x * ModP y = ModP ((x * y) `mod` p)
   abs = undefined
   signum = undefined

 solve _ [] = 1::ModP
 solve [] _ = 0::ModP
 solve (hs:ts) t@(ht:tt) | hs==ht = solve ts tt + solve ts t

 | otherwise = solve ts t

 go (run, line) = Case #++show run++: ++show (solve line welcome to
 code jam)

 main = interact $ unlines . map go . zip [1..] . tail . lines


 Which is unfortunately exponential.

 Now in earlier thread I argued for a compiler directive in the lines of {-#
 Memoize function -#},
 but this is not possible (it seems to be trivial to implement though).

Not really. Though a heck of a lot easier than automatic memoisation.

 Now I used memotrie which
 runs hopelessly out of memory. I looked at some other haskell solutions,
 which were all ugly and
 more clumsy compared to simple and concise C code. So it seems to me that
 haskell is very nice
 and beautiful until your are solving real algorithmic problems when you
 want to go back to some
 imperative language.

 How would experienced haskellers solve this problem?

 Thanks

completely unoptimised:

--
module Main (main) where

import Text.Printf
import Data.List

out :: Integer - String
out n = printf %04d (n `mod` 1)

update :: [(String,Integer)] - Char - [(String,Integer)]
update ((p@((h:_),n)):tl) c
= case update tl c of
((x,m):more)
| c == h- p:(x,m+n):more
other - p:other
update xs _ = xs

solve pattern = snd . last . foldl' update (zip (tails pattern) (1:repeat 0))

solveLine :: String - (Integer,String) - String
solveLine pattern (i,str) = Case#  ++ show i ++ :  ++ out (solve pattern 
str)

main :: IO ()
main = interact $ unlines . map (solveLine welcome to code jam)
. zip [1 .. ] . tail . lines
--

./codeJam +RTS -sstderr -RTS  C-large-practice.in
snip
Case# 98: 4048  
   
Case# 99: 8125  
   
Case# 100: 0807 
   
  15,022,840 bytes allocated in the heap
   
 789,028 bytes copied during GC 
   
 130,212 bytes maximum residency (1 sample(s))  
   
  31,972 bytes maximum slop 
   
   1 MB total memory in use (0 MB lost due to fragmentation)
   

  Generation 0:28 collections, 0 parallel,  0.00s,  0.00s elapsed
  Generation 1: 1 collections, 0 parallel,  0.00s,  0.00s elapsed

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time0.04s  (  0.03s elapsed)
  GCtime0.00s  (  0.01s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time0.04s  (  0.04s elapsed)

  %GC time   0.0%  (13.8% elapsed)

  Alloc rate417,277,929 bytes per MUT second

  Productivity 100.0% of total user, 98.6% of total elapsed


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2009-09-05 Thread Reid Barton
On Sat, Sep 05, 2009 at 02:52:50AM -0700, staafmeister wrote:
 How would experienced haskellers solve this problem?

You could just memoize using an array, like in C.

import Data.Array

occurrences :: Num a = String - String - a
occurrences key buf = grid ! (0, 0)  -- grid ! (i, j) = occurrences (drop i 
key) (drop j buf)
  where grid = listArray ((0, 0), (nk, nb)) [
  if i == nk then 1
  else if j == nb then 0
   else (if key !! i == buf !! j then grid ! (i+1, j+1) else 0) + 
grid ! (i, j+1)
  | i - [0..nk], j - [0..nb]
  ]
nk = length key
nb = length buf

Regards,
Reid
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization local to a function

2009-02-26 Thread Dusan Kolar
Thanks for all the hints and code provided, nevertheless, it implied 
another questions:


1) Am I right that MemoCombinators can be hardly ever used with hugs? If 
not, which guidelines to be used for installation...
2) Is there any paper/tutorial/wiki that describes, which local 
definitions/expressions are discarded/not shared after/to the next 
computation, that means separated closure is built for them?


Dusan

Henning Thielemann wrote:


On Wed, 25 Feb 2009, Luke Palmer wrote:

On Wed, Feb 25, 2009 at 10:38 AM, Dusan Kolar ko...@fit.vutbr.cz 
wrote:
   I have a function a computation of which is quite expensive, 
it is recursively
  dependent on itself with respect to some other function values 
- we can roughly
  model its behaviour with fib function (returns n-th number of 
Fibonacci's
  sequence). Unfortunately, it is not fib, it is far more 
complicated.
  Nevertheless, for demonstration of my question/problem I will 
use fib, it's quite

  good.


I suggest using data-memocombinators for this rather than rolling 
your own.  It accomplishes
the same thing, but makes the choice of memo structure independent of 
the code that uses it

(and Memo.integral has asymptotically better performance than a list).


Nice to know that there is a package for this purpose. See also
  http://haskell.org/haskellwiki/Memoization



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization local to a function

2009-02-26 Thread Dušan Kolář
Thanks for all the hints and code provided, nevertheless, it implied 
another questions:


1) Am I right that MemoCombinators can be hardly ever used with hugs? If 
not, which guidelines to be used for installation...
2) Is there any paper/tutorial/wiki that describes, which local 
definitions/expressions are discarded/not shared after/to the next 
computation, that means separated closure is built for them?


Dusan

Henning Thielemann wrote:


On Wed, 25 Feb 2009, Luke Palmer wrote:

On Wed, Feb 25, 2009 at 10:38 AM, Dusan Kolar ko...@fit.vutbr.cz 
wrote:
   I have a function a computation of which is quite expensive, 
it is recursively
  dependent on itself with respect to some other function values 
- we can roughly
  model its behaviour with fib function (returns n-th number of 
Fibonacci's
  sequence). Unfortunately, it is not fib, it is far more 
complicated.
  Nevertheless, for demonstration of my question/problem I will 
use fib, it's quite

  good.


I suggest using data-memocombinators for this rather than rolling 
your own.  It accomplishes
the same thing, but makes the choice of memo structure independent of 
the code that uses it

(and Memo.integral has asymptotically better performance than a list).


Nice to know that there is a package for this purpose. See also
  http://haskell.org/haskellwiki/Memoization


--

 Dusan Kolartel: +420 54 114 1238
 UIFS FIT VUT Brno  fax: +420 54 114 1270
 Bozetechova 2   e-mail: ko...@fit.vutbr.cz
 Brno 612 66
 Czech Republic

--

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Memoization local to a function

2009-02-25 Thread Sittampalam, Ganesh
Dusan Kolar wrote:
 Nevertheless, local version does not
 work.  

Restructure your code like this:

 fibL m =
   let
 allfib = 0:1:[allfib!!n + allfib!!(n+1) | n - [0..]]
   in allfib !! m

fibL = let allfib = 0:1:[allfib!!n + allfib!!(n+1) | n - [0..]]
 in \m - allfib !! m

i.e. move the definition of the memo table outside the scope of
the specific parameter you want to memoise over.

Cheers,

Ganesh

=== 
 Please access the attached hyperlink for an important electronic 
communications disclaimer: 
 http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html 
 
=== 
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization local to a function

2009-02-25 Thread Luke Palmer
On Wed, Feb 25, 2009 at 10:38 AM, Dusan Kolar ko...@fit.vutbr.cz wrote:

  I have a function a computation of which is quite expensive, it is
 recursively dependent on itself with respect to some other function values -
 we can roughly model its behaviour with fib function (returns n-th number of
 Fibonacci's sequence). Unfortunately, it is not fib, it is far more
 complicated. Nevertheless, for demonstration of my question/problem I will
 use fib, it's quite good.


I suggest using
data-memocombinatorshttp://hackage.haskell.org/cgi-bin/hackage-scripts/package/data-memocombinatorsfor
this rather than rolling your own.  It accomplishes the same thing,
but
makes the choice of memo structure independent of the code that uses it (and
Memo.integral has asymptotically better performance than a list).

Luke




  I want to store results in a list (array, with its strong size limit that
 I do not know prior to computation, is not suitable) and then pick them up
 using (!!) operator. Well, if the list is global function/constant then it
 works quite well. Unfortunately, this is not, what I would like to have.
 Nevertheless, local version does not work.

  Could someone point me to some text that explains it? Memoization text on
 wiki does not seem to be helpful. Time/operation consumption is deduced from
 number of reductions reported by hugs and winhugs (tested both on Linux and
 Windows).

  Thank you for hints,

  Dusan


 P.S.
 Code I used for testing.

 module Testmemo
   (  fibW
   ,  fibL
   ,  fibM
   )  where


 fibW m = allfib !! m
  where
   allfib = 0:1:[allfib!!n + allfib!!(n+1) | n - [0..]]


 fibL m =
  let
   allfib = 0:1:[allfib!!n + allfib!!(n+1) | n - [0..]]
  in allfib !! m


 fibM n = myallfib !! n
 myallfib = 0:1:[myallfib!!n + myallfib!!(n+1) | n - [0..]]

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization local to a function

2009-02-25 Thread Henning Thielemann


On Wed, 25 Feb 2009, Luke Palmer wrote:


On Wed, Feb 25, 2009 at 10:38 AM, Dusan Kolar ko...@fit.vutbr.cz wrote:
   I have a function a computation of which is quite expensive, it is 
recursively
  dependent on itself with respect to some other function values - we can 
roughly
  model its behaviour with fib function (returns n-th number of Fibonacci's
  sequence). Unfortunately, it is not fib, it is far more complicated.
  Nevertheless, for demonstration of my question/problem I will use fib, 
it's quite
  good.


I suggest using data-memocombinators for this rather than rolling your own.  It 
accomplishes
the same thing, but makes the choice of memo structure independent of the code 
that uses it
(and Memo.integral has asymptotically better performance than a list).


Nice to know that there is a package for this purpose. See also
  http://haskell.org/haskellwiki/Memoization___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization-question

2008-12-16 Thread Mattias Bengtsson
On Fri, 2008-12-12 at 15:47 +0100, Bertram Felgenhauer wrote:
 GHC does opportunistic CSE, when optimizations are enabled. [...]

I see. Thank you!

Mattias

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization-question

2008-12-12 Thread Bertram Felgenhauer
Mattias Bengtsson wrote:
 The program below computes (f 27) almost instantly but if i replace the
 definition of (f n) below with (f n = f (n - 1) * f (n -1)) then it
 takes around 12s to terminate. I realize this is because the original
 version caches results and only has to calculate, for example, (f 25)
 once instead of (i guess) four times.
 There is probably a good reason why this isn't caught by the compiler.
 But I'm interested in why. Anyone care to explain?

GHC does opportunistic CSE, when optimizations are enabled. See

http://www.haskell.org/haskellwiki/GHC:FAQ#Does_GHC_do_common_subexpression_elimination.3F
(http://tinyurl.com/33q93a)

I've found it very hard to predict whether this will happen or not, from
a given source code, because the optimizer will transform the program a
lot and the opportunistic CSE rule may apply to one of the transformed
versions.

It's best to make sharing explicit when you need it, as you did below.

  main = print (f 27)
  
  f 0 = 1
  f n = let f' = f (n-1)
in f' * f'

Bertram
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization-question

2008-12-11 Thread Donnie Jones
Hello Mattias,

I think you will find this thread from the haskell-cafe mailing list quite
helpful.
  Re: [Haskell-cafe] Memoization
  http://www.mail-archive.com/haskell-cafe@haskell.org/msg09924.html

Also, the Haskell wiki contains comments about techniques for memoization
along with references at the bottom.
  Haskell wiki Memoization:
  http://www.haskell.org/haskellwiki/Memoization

Hope that helps.
__
Donnie Jones

On Thu, Dec 11, 2008 at 10:18 AM, Mattias Bengtsson 
moonl...@dtek.chalmers.se wrote:

 The program below computes (f 27) almost instantly but if i replace the
 definition of (f n) below with (f n = f (n - 1) * f (n -1)) then it
 takes around 12s to terminate. I realize this is because the original
 version caches results and only has to calculate, for example, (f 25)
 once instead of (i guess) four times.
 There is probably a good reason why this isn't caught by the compiler.
 But I'm interested in why. Anyone care to explain?

  main = print (f 27)
 
  f 0 = 1
  f n = let f' = f (n-1)
in f' * f'

 (compiled with ghc --make -O2)

 Mattias

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization-question

2008-12-11 Thread Daniel Fischer
Am Donnerstag, 11. Dezember 2008 16:18 schrieb Mattias Bengtsson:
 The program below computes (f 27) almost instantly but if i replace the
 definition of (f n) below with (f n = f (n - 1) * f (n -1)) then it
 takes around 12s to terminate. I realize this is because the original
 version caches results and only has to calculate, for example, (f 25)
 once instead of (i guess) four times.
 There is probably a good reason why this isn't caught by the compiler.
 But I'm interested in why. Anyone care to explain?

  main = print (f 27)
 
  f 0 = 1
  f n = let f' = f (n-1)
in f' * f'

 (compiled with ghc --make -O2)

 Mattias


Not an expert, so I may be wrong.
The way you wrote your function, you made it clear to the compiler that you 
want sharing, so it shares.
With

g 0 = 1
g n = g (n-1)*g (n-1)

it doesn't, because the type of g is Num t = t - t, and you might call it 
with whatever weird Num type, for which sharing might be a bad idea (okay, 
for this specific function I don't see how I would define a Num type where 
sharing would be bad).
If you give g a signature like
g :: Int - Int,
the compiler knows that sharing is a good idea and does it (cool thing aside:
with
module Main where

f 0 = 1
f n = let a = f (n-1) in a*a

main = do
print (f 27)
print (g 30)

g 0 = 1
g n = g (n-1)*g (n-1)

main still runs instantaneously, but g n takes exponential time at the ghci 
prompt. That's because in main the argument of g is defaulted to Integer, so 
it's shared.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization-question

2008-12-11 Thread Daniel Fischer
Am Donnerstag, 11. Dezember 2008 21:11 schrieb Bulat Ziganshin:
 Hello Daniel,

 Thursday, December 11, 2008, 11:09:46 PM, you wrote:

 you is almost right. but ghc don't share results of function calls
 despite their type. it just assumes that value of any type may use a
 lot of memory even if this type is trivial :)

I may misunderstand you here. But if you give a type signature specifying a 
nice known type, I'm pretty sure ghc _does_ sharing (tried with Int - Int 
and Integer - Integer, g 200 instantaneous), at least with -O2. Without 
sharing, it would require 2^(n+1) - 1 calls to evaluate g n, that wouldn't be 
nearly as fast. Without the type signature, it must assume the worst, so it 
doesn't share.


 example when automatic sharing is very bad idea is:

 main = print (sum[1..10^10] + sum[1..10^10])

Depends on what is shared. Sharing the list would be a very bad idea, sharing
sum [1 .. 10^10] would probably be a good idea.


  Am Donnerstag, 11. Dezember 2008 16:18 schrieb Mattias Bengtsson:
  The program below computes (f 27) almost instantly but if i replace the
  definition of (f n) below with (f n = f (n - 1) * f (n -1)) then it
  takes around 12s to terminate. I realize this is because the original
  version caches results and only has to calculate, for example, (f 25)
  once instead of (i guess) four times.
  There is probably a good reason why this isn't caught by the compiler.
  But I'm interested in why. Anyone care to explain?
 
   main = print (f 27)
  
   f 0 = 1
   f n = let f' = f (n-1)
 in f' * f'
 
  (compiled with ghc --make -O2)
 
  Mattias
 
  Not an expert, so I may be wrong.
  The way you wrote your function, you made it clear to the compiler that
  you want sharing, so it shares.
  With
 
  g 0 = 1
  g n = g (n-1)*g (n-1)
 
  it doesn't, because the type of g is Num t = t - t, and you might call
  it with whatever weird Num type, for which sharing might be a bad idea
  (okay, for this specific function I don't see how I would define a Num
  type where sharing would be bad).
  If you give g a signature like

 g :: Int - Int,

  the compiler knows that sharing is a good idea and does it (cool thing
  aside: with
  module Main where
 
  f 0 = 1
  f n = let a = f (n-1) in a*a
 
  main = do
  print (f 27)
  print (g 30)
 
  g 0 = 1
  g n = g (n-1)*g (n-1)
 
  main still runs instantaneously, but g n takes exponential time at the
  ghci prompt. That's because in main the argument of g is defaulted to
  Integer, so it's shared.)
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization-question

2008-12-11 Thread Daniel Fischer
Am Donnerstag, 11. Dezember 2008 21:56 schrieb Bulat Ziganshin:
 Hello Daniel,

 Thursday, December 11, 2008, 11:49:40 PM, you wrote:

 sorry for noise, it seems that i know ghc worse than you

If only that were true.
I just know that GHC's optimiser can do some rather impressive stuff when 
given appropriate types, so I tried.
Meanwhile, I've confirmed that it does share (for Int and Integer) with -O1 
and -O2, but not with -O0, by looking at the generated core.

Cheers,
Daniel
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2008-07-13 Thread Derek Elkins
On Sun, 2008-07-13 at 20:24 +0200, Logesh Pillay wrote:
 I know we can perform memoization in Haskell.  The well known recursive 
 Fibonacci example works v. well.  f(1) returns a virtually instant 
 answer which would not be possible otherwise.
 
 My (probably naive) function to give the number of partitions of a number :-
 p = ((map p' [0 .. ]) !!)
   where
   p' 0 = 1
   p' 1 = 1
   p' n = sum [(((-1) ^ (k+1)) * ( p' (n-((k*(3*k-1)) `div` 2))  +  p' 
 (n-((k*(3*k+1)) `div` 2 | k  - [1 .. n]]
 
 It is an attempt to apply the Euler recurrence formula (no 11 in 
 http://mathworld.wolfram.com/PartitionFunctionP.html )
 
 It works but it is shockingly slow.  It is orders of magnitude slower 
 than the Python memoized version which runs very fast.
 parts = {0:1, 1:1}
 def P(n):
   if not n in parts:
 parts[n] = sum ([( ((-1) ** (k+1)) * ( P(n-((k*(3*k-1))//2)) +  
 P(n-((k*(3*k+1))//2)) ) ) for k in xrange (1, n+1)])
   return parts[n]
 
 Why?  Its as if memoization is being ignored in the haskell version.  

That's because you aren't using it.

 How to fix?

Use your memoized function.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2008-07-13 Thread Ketil Malde
Logesh Pillay [EMAIL PROTECTED] writes:

 Why?  Its as if memoization is being ignored in the haskell version.
 How to fix?

Shouldn't the definition of p' call (the memoized) p somewhere?  In
other words, I can't see any memoization, you seem to just map a
normal, expensive, recursive function p' over a list.

(Another difference is that Python's associative arrays are likely to
be faster than Haskell's linear-time indexed lists.)

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] memoization

2008-07-13 Thread Henning Thielemann


On Sun, 13 Jul 2008, Logesh Pillay wrote:

I know we can perform memoization in Haskell.  The well known recursive 
Fibonacci example works v. well.  f(1) returns a virtually instant answer 
which would not be possible otherwise.


My (probably naive) function to give the number of partitions of a number :-
p = ((map p' [0 .. ]) !!)
where
p' 0 = 1
p' 1 = 1
p' n = sum [(((-1) ^ (k+1)) * ( p' (n-((k*(3*k-1)) `div` 2))  +  p' 
(n-((k*(3*k+1)) `div` 2 | k  - [1 .. n]]


You don't use memoization here - so why do you expect it would take place?

I have a fast implementation:
  http://darcs.haskell.org/htam/src/Combinatorics/Partitions.hs

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2007-05-30 Thread Creighton Hogg

On 5/26/07, Mark Engelberg [EMAIL PROTECTED] wrote:


I'd like to write a memoization utility.  Ideally, it would look
something like this:

memoize :: (a-b) - (a-b)

memoize f gives you back a function that maintains a cache of
previously computed values, so that subsequent calls with the same
input will be faster.

I've searched the web for memoization examples in Haskell, and all the
examples use the trick of storing cached values in a lazy list.  This
only works for certain types of functions, and I'm looking for a more
general solution.

In other languages, one would maintain the cache in some sort of
mutable map.  Even better, in many languages you can rebind the name
of the function to the memoized version, so recursive functions can be
memoized without altering the body of the function.

I don't see any elegant way to do this in Haskell, and I'm doubting
its possible.  Can someone prove me wrong?



Now maybe I'm being dense here, but would you really *want* a way in Haskell
to do something like
memo :: (a-b) - a-b
since it changes the semantics of the function?
It seems like a better abstraction would be to have
memo :: (a-b)- M a b
where M is an instance of Arrow so that you can keep a proper notion of
composition between memoized functions.
Is there something wrong with my thinking?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2007-05-30 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Creighton Hogg wrote:
 Now maybe I'm being dense here, but would you really *want* a way in
 Haskell
 to do something like
 memo :: (a-b) - a-b
 since it changes the semantics of the function?
 It seems like a better abstraction would be to have
 memo :: (a-b)- M a b
 where M is an instance of Arrow so that you can keep a proper notion of
 composition between memoized functions.
 Is there something wrong with my thinking?

memoize f gives you back a function that maintains a cache of
previously computed values, so that subsequent calls with the same
input will be faster.

Speed isn't part of Haskell function semantics (luckily, or we wouldn't
be able to have an optimizer in the first place).

memoize does not change the semantics of the function (I think)

Your better abstraction is, anyway, better in terms of being
implementable in existing Haskell - you might need an (Eq a) context or
something. However it interferes with code structure for a
non-semantical change (strong effects on memory use and speed which you
might _want_ to manage more explicitly, but that's not theoretically
affecting purity)


Isaac
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGXZPDHgcxvIWYTTURAi9fAJ44oIE85tZd+OtUOKswZnleBdt7eACeJuET
65AkQ2zI15CH6pnMHFmQddE=
=n5OS
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2007-05-30 Thread Creighton Hogg

On 5/30/07, Isaac Dupree [EMAIL PROTECTED] wrote:


-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

Creighton Hogg wrote:
 Now maybe I'm being dense here, but would you really *want* a way in
 Haskell
 to do something like
 memo :: (a-b) - a-b
 since it changes the semantics of the function?
 It seems like a better abstraction would be to have
 memo :: (a-b)- M a b
 where M is an instance of Arrow so that you can keep a proper notion of
 composition between memoized functions.
 Is there something wrong with my thinking?

memoize f gives you back a function that maintains a cache of
previously computed values, so that subsequent calls with the same
input will be faster.

Speed isn't part of Haskell function semantics (luckily, or we wouldn't
be able to have an optimizer in the first place).

memoize does not change the semantics of the function (I think)

Your better abstraction is, anyway, better in terms of being
implementable in existing Haskell - you might need an (Eq a) context or
something. However it interferes with code structure for a
non-semantical change (strong effects on memory use and speed which you
might _want_ to manage more explicitly, but that's not theoretically
affecting purity)



Eh, I guess I was just being fascist.  I suppose that even if there are side
effects involved in the memoization, it doesn't break referential
transparency which is the real measure of purity.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2007-05-27 Thread Rodrigo Queiro

sorear pointed me to this paper a while ago:
http://citeseer.ist.psu.edu/peytonjones99stretching.html

I never tried any of the code in the end, but it will probably be useful?

On 27/05/07, Mark Engelberg [EMAIL PROTECTED] wrote:


I'd like to write a memoization utility.  Ideally, it would look
something like this:

memoize :: (a-b) - (a-b)

memoize f gives you back a function that maintains a cache of
previously computed values, so that subsequent calls with the same
input will be faster.

I've searched the web for memoization examples in Haskell, and all the
examples use the trick of storing cached values in a lazy list.  This
only works for certain types of functions, and I'm looking for a more
general solution.

In other languages, one would maintain the cache in some sort of
mutable map.  Even better, in many languages you can rebind the name
of the function to the memoized version, so recursive functions can be
memoized without altering the body of the function.

I don't see any elegant way to do this in Haskell, and I'm doubting
its possible.  Can someone prove me wrong?

--Mark
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2007-05-27 Thread Marc A. Ziegert
you may want to use a container like Array or Map.
most times i use an Array myself to speed things up like this.
with Map it will either be a bit tricky or you'll need to use an unsafeIO hack.
here are some functions that may help you. my favorites are Array and MapMealey.
- marc


memoizeArrayUnsafe :: (Ix i) = (i,i) - (i-e) - (i-e)
memoizeArrayUnsafe r f = (Data.Array.!) $ Data.Array.listArray r $ fmap f $ 
Data.Ix.range r
memoizeArray :: (Ix i) = (i,i) - (i-e) - (i-e)
memoizeArray r f i = if Data.Ix.inRange r i then memoizeArrayUnsafe r f i else 
f i


data Mealey i o = Mealey { runMealey :: i - (o,Mealey i o) }
memoizeMapMealey :: (Ord k) = (k-a) - (Mealey k a)
memoizeMapMealey f = Mealey (fm Data.Map.empty) where 
fm m k = case Data.Map.lookup m k of
(Just a) - (a,Mealey . fm $ m)
Nothing - let a = f k in (a,Mealey . fm $ Data.Map.insert k a 
$ m)

memoizeMapST :: (Ord k) = (k-ST s a) - ST s (k-ST s a)
memoizeMapST f = do
r - newSTRef (Data.Map.empty)
return $ \k - do
m - readSTRef r
case Data.Map.lookup m k of
(Just a) - return a
Nothing - do
a - f k
writeSTRef r $ Data.Map.insert k a m
return a


or with inelegant unsafe hacks you get more elegant interfaces:


memoizeMapUnsafeIO :: (Ord k) = (k-IO a) - (k-a)
memoizeMapUnsafeIO f = unsafePerformIO $ do
r - newIORef (Data.Map.empty)
return $ \k - unsafePerformIO $ do
m - readIORef r
case Data.Map.lookup m k of
(Just a) - return a
Nothing - do
a - f k
writeIORef r $ Data.Map.insert k a m
return a

memoizeMap :: (Ord k) = (k-a) - (k-a)
memoizeMap f = memoizeMapUnsafeIO (return . f)
memoizeMap f = runST $ do
f' - memoizeMapST (return . f)
return $ runST . unsafeIOToST . unsafeSTToIO . f'


Am Sonntag, 27. Mai 2007 04:34 schrieb Mark Engelberg:
 I'd like to write a memoization utility.  Ideally, it would look
 something like this:
 
 memoize :: (a-b) - (a-b)
 
 memoize f gives you back a function that maintains a cache of
 previously computed values, so that subsequent calls with the same
 input will be faster.
 
 I've searched the web for memoization examples in Haskell, and all the
 examples use the trick of storing cached values in a lazy list.  This
 only works for certain types of functions, and I'm looking for a more
 general solution.
 
 In other languages, one would maintain the cache in some sort of
 mutable map.  Even better, in many languages you can rebind the name
 of the function to the memoized version, so recursive functions can be
 memoized without altering the body of the function.
 
 I don't see any elegant way to do this in Haskell, and I'm doubting
 its possible.  Can someone prove me wrong?
 
 --Mark
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 


pgpmBt6Z94b21.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2007-05-26 Thread Felipe Almeida Lessa

On 5/26/07, Mark Engelberg [EMAIL PROTECTED] wrote:

I don't see any elegant way to do this in Haskell, and I'm doubting
its possible.  Can someone prove me wrong?


Provided some sort of memoize :: (a-b) - (a-b), I'd do something like

f = memoize g where
 g =  recursive call to f, not g ...

But probably there's something better I've missed =).

--
Felipe.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2007-05-26 Thread Stefan O'Rear
On Sat, May 26, 2007 at 11:41:28PM -0300, Felipe Almeida Lessa wrote:
 On 5/26/07, Mark Engelberg [EMAIL PROTECTED] wrote:
 I don't see any elegant way to do this in Haskell, and I'm doubting
 its possible.  Can someone prove me wrong?
 
 Provided some sort of memoize :: (a-b) - (a-b), I'd do something like
 
 f = memoize g where
  g =  recursive call to f, not g ...
 
 But probably there's something better I've missed =).

memofix :: ((a - b) - (a - b)) - a - b
memofix ff = let g = memoize (ff g) in g

fib = memofix $ \fib k - case k of
0 - 0
1 - 1
n - fib (n-1) + fib (n-2)

Stefan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2007-05-26 Thread Erik de Castro Lopo
Stefan O'Rear wrote:

 
 memofix :: ((a - b) - (a - b)) - a - b
 memofix ff = let g = memoize (ff g) in g
 
 fib = memofix $ \fib k - case k of
 0 - 0
 1 - 1
 n - fib (n-1) + fib (n-2)

Stefan, these is something missing here. Where is memoize
defined?

Erik
-- 
-
Erik de Castro Lopo
-
I hack, therefore I am.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2007-05-26 Thread Felipe Almeida Lessa

On 5/27/07, Stefan O'Rear [EMAIL PROTECTED] wrote:

memofix :: ((a - b) - (a - b)) - a - b
memofix ff = let g = memoize (ff g) in g

fib = memofix $ \fib k - case k of
0 - 0
1 - 1
n - fib (n-1) + fib (n-2)


But this way you miss pattern matching and guards? How would you write
something like:

ack = curry (memoize a) where
 a (0,n)  = n + 1
 a (m,0)  = ack (m-1) 1
 a (m,n) | m  0 || n  0 = error ack of negative integer
 | otherwise  = let inner = ack m (n-1)
in  ack (m-1) inner


--
Felipe.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2005-10-08 Thread Jon Fairbairn
On 2005-10-07 at 22:42- Gerd M wrote:
 As (memory) is a function, it
 cannot be memoized (the function can be, but not its result, which is
 what you're after).
 How can a funcion be memoized but not it's result (what does this mean)!? 
 Since there are no side effects in Haskell why is it important that the 
 array is a CAF? Or let's say it that way, why can't the results of a (pure) 
 function be memoized since it always returns the same result for the same 
 parameters?

I'm a bit rusty on this, but here's an attempt at an
explanation.

This is an implementation issue; a matter of choice for the
implementor. In a function like this:

 f x = factorial 100 + x

factorial 100 doesn't depend on x -- is a CAF -- so it can
be lifted out and computed only once. Note that since the
value of f doesn't depend on whether this is done, there's
no /requirement/ that the compiler do it.

In this:

 g a = \ x - factorial a + x

g 100 is equivalent to f, but here the factorial 100 isn't a
constant (it depends on a), so the compiler would have to go
to extra lengths (known as full laziness) to ensure that
the factorial was kept for each application of g. It's
certainly possible for a compiler to do this, but the
problem is that if the subexpression that gets retained is
infinite, it takes up a lot of space, and there's no way for
the programmer to say that it's no longer needed. So
compilers tend not to do this.

  Jón


-- 
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2005-10-08 Thread Gerd M
Thanks to everyone for the answers, I'm getting a picture now. Maybe I will 
give the memoizing Y combinator a try later.



On 2005-10-07 at 22:42- Gerd M wrote:
 As (memory) is a function, it
 cannot be memoized (the function can be, but not its result, which is
 what you're after).
 How can a funcion be memoized but not it's result (what does this 
mean)!?

 Since there are no side effects in Haskell why is it important that the
 array is a CAF? Or let's say it that way, why can't the results of a 
(pure)
 function be memoized since it always returns the same result for the 
same

 parameters?

I'm a bit rusty on this, but here's an attempt at an
explanation.

This is an implementation issue; a matter of choice for the
implementor. In a function like this:

 f x = factorial 100 + x

factorial 100 doesn't depend on x -- is a CAF -- so it can
be lifted out and computed only once. Note that since the
value of f doesn't depend on whether this is done, there's
no /requirement/ that the compiler do it.

In this:

 g a = \ x - factorial a + x

g 100 is equivalent to f, but here the factorial 100 isn't a
constant (it depends on a), so the compiler would have to go
to extra lengths (known as full laziness) to ensure that
the factorial was kept for each application of g. It's
certainly possible for a compiler to do this, but the
problem is that if the subexpression that gets retained is
infinite, it takes up a lot of space, and there's no way for
the programmer to say that it's no longer needed. So
compilers tend not to do this.

  Jón


--
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk




_
Express yourself instantly with MSN Messenger! Download today it's FREE! 
http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2005-10-07 Thread Sebastian Sylvan
On 10/7/05, Gerd M [EMAIL PROTECTED] wrote:
 Hello,
 I'm trying to use Data.Map to memoize computations. Unfortunately this
 didn't improve the runtime of f at all, so there must be something wrong
 with my implementation. Thanks in advance!

 f 1 s (HMM s0 _   sts)  =  s ??? sts s0
 f t s hmm = memory hmm Map.! (t,s)

 memory hmm@(HMM s0 sss sts)
 = Map.fromList [ ((t,s),f' t s hmm) | t - [1..100], s - sss,
 s/=s0 ]

 f' 1 s (HMM s0 _   sts)  =  s ??? sts s0
 f' t s hmm@(HMM s0 sss sts)
 = sum [ (memory hmm)Map.!(t-1,s') * (s ??? sts s')  | s' - sss, s'
 /= s0 ]


I would use an array, which has O(1) lookup...
Instead of changing your code, I'll give a bit more well-known example
(partially because I'm in a bit of a rush :-)). Here's a fib function
memoized for the first 100 n (using a general approach with arrays,
instead of the zipWith thing)

import Data.Array

fib 0 = 1
fib 1 = 1
fib n | n = 100 = fibarr!n
  | otherwise = fib' n

fibarr = listArray (2,100) [ fib' x | x - [2..100]]
fib' n = fib (n-1) + fib (n-2)

The array is lazy in its elements (but not its indices) so the array
of 100 fibs won't actually be computed until you request a fib (then
all fibs  n will be computed).
So basically, define an array which contains the value of the function
at each entry, make sure you use the array in defining these elements
if your function is recursive (top-level, it doesn't change the
correctness but if you define it in a local scope your implementation
probably won't save the entries in the array between calls which kinda
ruins the point of memoization!).


/S
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2005-10-07 Thread Gerd M
I still don't get it. I changed my code to structurally match your example 
(see below) but the result is still the same...


f 1 s (HMM s0 _   sts)  =  s ??? sts s0
f t s hmm = memory hmm Map.! (t,s)

memory hmm@(HMM s0 sss sts)
= Map.fromList [ ((t,s),f' t s hmm) | t - [1..100], s - sss ]

f' 1 s (HMM s0 _   sts)  =  s ??? sts s0
f' t s hmm@(HMM s0 sss sts)
= sum [ (f (t-1) s' hmm) * (s ??? sts s')  | s' - sss ]



I would use an array, which has O(1) lookup...
Instead of changing your code, I'll give a bit more well-known example
(partially because I'm in a bit of a rush :-)). Here's a fib function
memoized for the first 100 n (using a general approach with arrays,
instead of the zipWith thing)

import Data.Array

fib 0 = 1
fib 1 = 1
fib n | n = 100 = fibarr!n
  | otherwise = fib' n

fibarr = listArray (2,100) [ fib' x | x - [2..100]]
fib' n = fib (n-1) + fib (n-2)

The array is lazy in its elements (but not its indices) so the array
of 100 fibs won't actually be computed until you request a fib (then
all fibs  n will be computed).
So basically, define an array which contains the value of the function
at each entry, make sure you use the array in defining these elements
if your function is recursive (top-level, it doesn't change the
correctness but if you define it in a local scope your implementation
probably won't save the entries in the array between calls which kinda
ruins the point of memoization!).


_
Express yourself instantly with MSN Messenger! Download today it's FREE! 
http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2005-10-07 Thread David Roundy
On Fri, Oct 07, 2005 at 06:08:48PM +, Gerd M wrote:
 I still don't get it. I changed my code to structurally match your
 example (see below) but the result is still the same...

How are you timing your function?
-- 
David Roundy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2005-10-07 Thread Gerd M
That's what I got from profiling, for some reason the memoized version is 
awfully slow:


Memoized version:
total time  =  143.74 secs   (7187 ticks @ 20 ms)
total alloc = 25,404,766,256 bytes  (excludes profiling overheads)

COST CENTREMODULE   %time %alloc

memory Main   96.9   99.0
con2tag_State# Main1.60.0


Non memoized version:
total time  =6.02 secs   (301 ticks @ 20 ms)
total alloc = 990,958,296 bytes  (excludes profiling overheads)

COST CENTREMODULE   %time %alloc

??? Prob   61.1   73.1
fMain   10.3   17.8
con2tag_State# Main7.60.0
sumProb   Prob6.61.5
tag2con_State# Main3.31.9
con2tag_Out#Main2.70.0
tag2con_Out#Main2.31.9
sumProb  Prob2.03.0
stateTrMain2.00.0
mul   Prob1.70.8




From: David Roundy [EMAIL PROTECTED]
To: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Memoization
Date: Fri, 7 Oct 2005 14:12:39 -0400

On Fri, Oct 07, 2005 at 06:08:48PM +, Gerd M wrote:
 I still don't get it. I changed my code to structurally match your
 example (see below) but the result is still the same...

How are you timing your function?
--
David Roundy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


_
Express yourself instantly with MSN Messenger! Download today it's FREE! 
http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2005-10-07 Thread Udo Stenzel
Gerd M wrote:
 I still don't get it. I changed my code to structurally match your example 
 (see below) but the result is still the same...
 
 f 1 s (HMM s0 _   sts)  =  s ??? sts s0
 f t s hmm = memory hmm Map.! (t,s)
 
 memory hmm@(HMM s0 sss sts)
 = Map.fromList [ ((t,s),f' t s hmm) | t - [1..100], s - sss ]
 
 f' 1 s (HMM s0 _   sts)  =  s ??? sts s0
 f' t s hmm@(HMM s0 sss sts)
 = sum [ (f (t-1) s' hmm) * (s ??? sts s')  | s' - sss ]

I have a hard time following your code, since it is incomplete, but I
think, you're not memoizing anything.  As (memory) is a function, it
cannot be memoized (the function can be, but not its result, which is
what you're after).  You want to memoize (memory hmm), but there's not
place where this could happen.  It is no CAF and it is no common
subexpression that could be pullen out of the recursion.  Try this:

 ff t s hmm@(HMM s0 sss sts) = f t s
   where
   f 1 s  =  s ??? sts s0
   f t s  =  memory Map.! (t,s)
 
   f' 1 s  =  s ??? sts s0
   f' t s  =  sum [ (f (t-1) s') * (s ??? sts s')  | s' - sss ]

   memory  =  Map.fromList [ ((t,s), f' t s) | t - [1..100], s - sss ]

...which is of course completely untested.  Of course, the memoizing
fixed point combinator Chris Okasaki posted a while ago would be far
more elegant, I'm just too lazy to dig it up.



Udo.
-- 
Basically my wife was immature.  I'd be at home in the bath and she'd
come in and sink my boats.
-- Woody Allen


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2005-10-07 Thread Gerd M

This works, thanks a lot, you saved my day/night! :-)


As (memory) is a function, it
cannot be memoized (the function can be, but not its result, which is
what you're after).
How can a funcion be memoized but not it's result (what does this mean)!? 
Since there are no side effects in Haskell why is it important that the 
array is a CAF? Or let's say it that way, why can't the results of a (pure) 
function be memoized since it always returns the same result for the same 
parameters?


Regards



 ff t s hmm@(HMM s0 sss sts) = f t s
   where
f 1 s  =  s ??? sts s0
f t s  =  memory Map.! (t,s)

f' 1 s  =  s ??? sts s0
f' t s  =  sum [ (f (t-1) s') * (s ??? sts s')  | s' - sss ]

memory  =  Map.fromList [ ((t,s), f' t s) | t - [1..100], s - sss ]

...which is of course completely untested.  Of course, the memoizing
fixed point combinator Chris Okasaki posted a while ago would be far
more elegant, I'm just too lazy to dig it up.



_
FREE pop-up blocking with the new MSN Toolbar - get it now! 
http://toolbar.msn.click-url.com/go/onm00200415ave/direct/01/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Memoization

2005-10-07 Thread Cale Gibbard
There are too many issues with memoisation to make it completely
automatic. There are however, ways to construct tools to turn
functions into memoising functions selectively.

This paper should be useful to you:
http://research.microsoft.com/Users/simonpj/Papers/weak.htm
It contains a number of implementations of functions which produce
memoized  variants of other functions, with varying semantics. The
methods use unsafePerformIO to create a memo table in an IORef and
pass back a modified version of the function which does a bit of IO
when evaluated to do a lookup in the table and check if there is a
cached result already, and if not, write the IORef back with a
modified memo table and return the value of the function.

The easiest way to memoise a single function however, is simply to
declare a top level value with a bunch of results of the function, and
if it's recursive, make that function use those values of course. You
can use a Map if the input type is in Ord and you don't mind the
log(n) lookup time, or an Array, which works if the input type is in
Ix. Remember when you do this that fromList/array are not going to
force the elements of the list you pass to be computed, so you're safe
to make a list of values of your function and apply fromList or array
to it, and then only when you look in the Map or Array will your
function actually be evaluated.  :)

 - Cale

On 07/10/05, Gerd M [EMAIL PROTECTED] wrote:
 This works, thanks a lot, you saved my day/night! :-)

 As (memory) is a function, it
 cannot be memoized (the function can be, but not its result, which is
 what you're after).
 How can a funcion be memoized but not it's result (what does this mean)!?
 Since there are no side effects in Haskell why is it important that the
 array is a CAF? Or let's say it that way, why can't the results of a (pure)
 function be memoized since it always returns the same result for the same
 parameters?

 Regards


   ff t s hmm@(HMM s0 sss sts) = f t s
 where
   f 1 s  =  s ??? sts s0
   f t s  =  memory Map.! (t,s)
  
   f' 1 s  =  s ??? sts s0
   f' t s  =  sum [ (f (t-1) s') * (s ??? sts s')  | s' - sss ]
  
   memory  =  Map.fromList [ ((t,s), f' t s) | t - [1..100], s - sss ]
 
 ...which is of course completely untested.  Of course, the memoizing
 fixed point combinator Chris Okasaki posted a while ago would be far
 more elegant, I'm just too lazy to dig it up.
 


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe