[Haskell-cafe] Re: Memoization in Haskell?

2010-07-10 Thread Heinrich Apfelmus

Gregory Crosswhite wrote:

Heinrich Apfelmus wrote:

Gregory Crosswhite wrote:

 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.)


It should be

f = \n - memo ! n
where
memo = ..

so that  memo  is shared across multiple calls like  f 1 , f 2  etc.


That actually doesn't work as long as memo is an array, since then it
has fixed size;  you have to also make memo an infinitely large data
(but lazy) structure so that it can hold results for arbitrary n.  One
option for doing this of course is to make memo be an infinite list, but
a more space and time efficient option is to use a trie like in MemoTrie.


Oops, silly me! I erroneously thought that the code was using  f 
instead  of  (memo !) in the definition of the array, like this


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

But since  memo  depends on  n , it cannot be lifted outside the lambda 
abstraction.



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


[Haskell-cafe] Re: Memoization in Haskell?

2010-07-09 Thread Heinrich Apfelmus

Gregory Crosswhite wrote:
 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.)


It should be

f = \n - memo ! n
where
memo = ..

so that  memo  is shared across multiple calls like  f 1 , f 2  etc.

Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] Re: Memoization in Haskell?

2010-07-09 Thread Gregory Crosswhite
 That actually doesn't work as long as memo is an array, since then it 
has fixed size;  you have to also make memo an infinitely large data 
(but lazy) structure so that it can hold results for arbitrary n.  One 
option for doing this of course is to make memo be an infinite list, but 
a more space and time efficient option is to use a trie like in MemoTrie.


Cheers,
Greg

On 7/9/10 12:50 AM, Heinrich Apfelmus wrote:

Gregory Crosswhite wrote:
 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.)


It should be

f = \n - memo ! n
where
memo = ..

so that  memo  is shared across multiple calls like  f 1 , f 2  etc.

Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

___
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] Re: memoization

2009-09-06 Thread John Lato
Hello,

I agree that your answer is elegant, but it's not an efficient
algorithm in any language.  How about this, keeping the rest of your
code the same?

import Data.Array.Diff
import Data.IArray

update :: (Char - [Int]) - DiffArray Int ModP - Char - DiffArray Int ModP
update lookup arr c = arr // (map calc . lookup $ c)
  where
calc i = (i, (arr ! i) + (arr ! (i-1)))

solve line sol = (foldl' (update lookup) iArray line) ! snd (bounds iArray)
  where
iArray = listArray (0, length sol) $ 1 : map (const 0) sol
lookup c = map (+1) . findIndices (== c) $ sol

I would expect that at least some of the C programs would use the same
algorithm.  It's not the most efficient Haskell implementation, but on
my computer it runs the large dataset in a little under 3 seconds,
which is probably good enough.

Cheers,
John


 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). 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
 --
 View this message in context: 
 http://www.nabble.com/memoization-tp25306687p25306687.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


[Haskell-cafe] Re: memoization

2009-09-06 Thread John Lato
I just discovered that changing DiffArray to a plain Array improves
performance of my code by almost a factor of 10.  Bitten by DiffArray
yet again!

John

-- this is no good, just change DiffArray to Array.
 update :: (Char - [Int]) - DiffArray Int ModP - Char - DiffArray Int ModP
 update lookup arr c = arr // (map calc . lookup $ c)
  where
    calc i = (i, (arr ! i) + (arr ! (i-1)))
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: memoization

2009-09-06 Thread Daniel Fischer
Am Sonntag 06 September 2009 13:36:57 schrieb John Lato:
 I just discovered that changing DiffArray to a plain Array improves
 performance of my code by almost a factor of 10.  Bitten by DiffArray
 yet again!

That's strange. Compiled without optimisations, using plain Array instead of 
DiffArray 
gives a speedup factor of about 38 here, with optimisations it's a factor of 
100 (thus 
it's about on par with the list-only version of the same algorithm).


 John

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


Re: [Haskell-cafe] Re: memoization

2009-09-06 Thread John Lato
On Sun, Sep 6, 2009 at 4:30 PM, Daniel Fischerdaniel.is.fisc...@web.de wrote:
 Am Sonntag 06 September 2009 13:36:57 schrieb John Lato:
 I just discovered that changing DiffArray to a plain Array improves
 performance of my code by almost a factor of 10.  Bitten by DiffArray
 yet again!

 That's strange. Compiled without optimisations, using plain Array instead of 
 DiffArray
 gives a speedup factor of about 38 here, with optimisations it's a factor of 
 100 (thus
 it's about on par with the list-only version of the same algorithm).


My mistake; I misread the time output.  My results are the same as yours.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Memoization

2007-06-08 Thread Peter Berry

Sorry for digging up such an old thread, but my undergraduate
dissertation is on this topic so I couldn't resist. :)

(Some credit in the following goes to my supervisor, Ulrich Berger.)


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

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


The type you actually want is more like:

memoFix :: ((a - b) - a - b) - a - b

which is like the normal fixpoint function (defined only over
functions) except that it adds the memoization magic. The reason being
that you can then memoize recursive calls as well (without having to
figure out how to dive into the function definition and replace
recursive calls with calls to the memoized version).

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

Note that due to parametricity, any function of this type is necessarily
either id or _|_. In other words, there are only two functions of type

  ∀a∀b. (a-b) - (a-b)


Of course, this only talks about the value of id, not its behaviour.
fix :: ((a - b) - a - b) - a - b = memoFix in the sense that the
values they compute are the same, but practically speaking they are
different since the latter does memoization.


That's because the functions has to work for all types a and b in the
same way, i.e. it may not even inspect how the given types a or b look
like. You need type classes to get a reasonable type for the function
you want

  memoize :: Memoizable a = (a-b) - (a-b)


Now, how to implement something like this? Of course, one needs a finite
map that stores values b for keys of type a. It turns out that such a
map can be constructed recursively based on the structure of a:

  Map ()b  := b
  Map (Either a a') b  := (Map a b, Map a' b)
  Map (a,a')b  := Map a (Map a' b)

Here,  Map a b  is the type of a finite map from keys a to values b. Its
construction is based on the following laws for functions

() - b  =~=  b
  (a + a') - b  =~=  (a - b) x (a' - b) -- = case analysis
  (a x a') - b  =~=  a - (a' - b)   -- = currying


class Memoizable a f | a - f where
   memIso :: (a - b) :~= f b

where a :~= b represents an isomorphism between two types, and f is
the generalized trie functor indexed on the type a and storing values
of its parameter type (here b). Note that this only works if a is
algebraic (i.e. can be represented as a generalized trie using the
isomorphisms above and a couple more to deal with recursive and higher
kinded types[1]). And it almost goes without saying that you can only
memoize pure functions.

Then memoFix actually has a constrained type, namely:

memoFix :: Memoizable a f = ((a - b) - a - b) - a - b

You can then take a recursive function like:

f :: A - B
f x = ... f y ...

and transform it so it takes its own fixpoint as an argument:

f' :: (A - B) - A - B
f' f x = ... f y ...

and then, if you have an instance

instance Memoizable A F where
   memIso = ...

after defining F, you can create the memo function with

fM : A - B
fM = memoFix f'

You could generate F and the Memoizable instance using TH or DrIFT or
the like (allowing derivation would be really nice :). Actually F
could be considered a dependent type, so you could define a pretty
much universal instance using TH with that mechanism.


For further and detailed explanations, see


[1]

  R. Hinze. Memo functions, polytypically!
  http://www.informatik.uni-bonn.de/~ralf/publications.html#P11

and

  R. Hinze. Generalizing generalized tries.
  http://www.informatik.uni-bonn.de/~ralf/publications.html#J4


also:
T. Altenkirch. Representations of first order function types as
terminal coalgebras.
http://www.cs.nott.ac.uk/~txa/publ/tlca01a.pdf

which unfortunately you probably won't understand unless you know
about category/domain theory (I haven't figured it all out myself).

--
Peter Berry [EMAIL PROTECTED]
Please avoid sending me Word or PowerPoint attachments.
See http://www.gnu.org/philosophy/no-word-attachments.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Memoization

2007-06-08 Thread Peter Berry

On 08/06/07, Peter Berry [EMAIL PROTECTED] wrote:

You could generate F and the Memoizable instance using TH or DrIFT or
the like (allowing derivation would be really nice :). Actually F
could be considered a dependent type, so you could define a pretty
much universal instance using TH with that mechanism.


I meant associated type of course.

--
Peter Berry [EMAIL PROTECTED]
Please avoid sending me Word or PowerPoint attachments.
See http://www.gnu.org/philosophy/no-word-attachments.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Memoization

2007-05-30 Thread Simon Marlow

Rodrigo Queiro wrote:
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?


An implementation of that memo table scheme can be found here:

http://darcs.haskell.org/testsuite/tests/ghc-regress/lib/should_run/Memo.lhs

It's probably too slow for general use, though.  You might find it useful if 
your keys are huge (or infinite) and comparing them directly is impractical.


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


[Haskell-cafe] Re: Memoization

2007-05-27 Thread apfelmus
Mark Engelberg 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.

Note that due to parametricity, any function of this type is necessarily
either id or _|_. In other words, there are only two functions of type

  ∀a∀b. (a-b) - (a-b)

That's because the functions has to work for all types a and b in the
same way, i.e. it may not even inspect how the given types a or b look
like. You need type classes to get a reasonable type for the function
you want

  memoize :: Memoizable a = (a-b) - (a-b)


Now, how to implement something like this? Of course, one needs a finite
map that stores values b for keys of type a. It turns out that such a
map can be constructed recursively based on the structure of a:

  Map ()b  := b
  Map (Either a a') b  := (Map a b, Map a' b)
  Map (a,a')b  := Map a (Map a' b)

Here,  Map a b  is the type of a finite map from keys a to values b. Its
construction is based on the following laws for functions

() - b  =~=  b
  (a + a') - b  =~=  (a - b) x (a' - b) -- = case analysis
  (a x a') - b  =~=  a - (a' - b)   -- = currying

For further and detailed explanations, see

  R. Hinze. Memo functions, polytypically!
  http://www.informatik.uni-bonn.de/~ralf/publications.html#P11

and

  R. Hinze. Generalizing generalized tries.
  http://www.informatik.uni-bonn.de/~ralf/publications.html#J4


Regards,
apfelmus

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


Re: [Haskell-cafe] Re: Memoization

2007-05-27 Thread Andrew Coppin

apfelmus wrote:

Note that due to parametricity, any function of this type is necessarily
either id or _|_. In other words, there are only two functions of type

  ∀a∀b. (a-b) - (a-b)

  


You managed to type ∀  but you couldn't find ⊥ ?

OOC, can anybody tell me what ∀ actually means anyway?


That's because the functions has to work for all types a and b in the
same way, i.e. it may not even inspect how the given types a or b look
like. You need type classes to get a reasonable type for the function
you want

  memoize :: Memoizable a = (a-b) - (a-b)

  


Ah... most optimal!

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


Re: [Haskell-cafe] Re: Memoization

2007-05-27 Thread Tony Morris
 You managed to type ∀  but you couldn't find ⊥ ?
 
 OOC, can anybody tell me what ∀ actually means anyway?

It is called the 'universal quantifier' and means for all. It is often
used implicitly in natural language. e.g. cars are red can be expanded
to [for all elements of the set of cars] cars [all elements of the set]
are red. This statement can be formally expressed (though i won't for now).

The universal quantifier, although most often used implicitly in natural
language, is most often used explicitly in formal logic.

You might also be interested in knowing of the existential quantifier
which means there exists. If I said there exists a car [an element
from the set of all cars] that is blue, then I have refuted the earlier
logical proposition (that cars are red).

The existential quantifier looks like a backward capital E
∃

Look up first-order logic if you're interested in learning more about
this topic.

PS: What does OOC stand for? Out Of Curiosity?

Tony Morris
http://tmorris.net/


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


Re: [Haskell-cafe] Re: Memoization

2007-05-27 Thread Andrew Coppin

Tony Morris wrote:

You managed to type ∀  but you couldn't find ⊥ ?

OOC, can anybody tell me what ∀ actually means anyway?



It is called the 'universal quantifier' and means for all. It is often
used implicitly in natural language. e.g. cars are red can be expanded
to [for all elements of the set of cars] cars [all elements of the set]
are red. This statement can be formally expressed (though i won't for now).

The universal quantifier, although most often used implicitly in natural
language, is most often used explicitly in formal logic.

You might also be interested in knowing of the existential quantifier
which means there exists. If I said there exists a car [an element
from the set of all cars] that is blue, then I have refuted the earlier
logical proposition (that cars are red).

The existential quantifier looks like a backward capital E
∃

Look up first-order logic if you're interested in learning more about
this topic.
  


I see...

I do recall that GHC has some weird extension called existential 
quantification, which makes absolutely no sense at all. So I looked up 
the term on Wikipedia, which says see predicate logic. So I looked up 
predicate logic, which says it's an extension of propositional logic, 
so I looked that up... and at this point I became increadibly confused! LOL.



PS: What does OOC stand for? Out Of Curiosity?
  


Indeed yes.

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


[Haskell-cafe] Re: Memoization

2007-05-27 Thread apfelmus
Andrew Coppin wrote:
 OOC, can anybody tell me what ∀ actually means anyway?

http://en.wikipedia.org/wiki/Universal_quantification
http://en.wikipedia.org/wiki/System_F

 I do recall that GHC has some weird extension called existential
 quantification

http://haskell.org/haskellwiki/Existential_types
http://en.wikibooks.org/wiki/Haskell/Existentially_quantified_types

Regards,
apfelmus

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


Re: [Haskell-cafe] Re: Memoization

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

apfelmus wrote:
 Mark Engelberg 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.
 
 Note that due to parametricity, any function of this type is necessarily
 either id or _|_. In other words, there are only two functions of type
 
   ∀a∀b. (a-b) - (a-b)
 
 That's because the functions has to work for all types a and b in the
 same way, i.e. it may not even inspect how the given types a or b look
 like. You need type classes to get a reasonable type for the function
 you want
 
   memoize :: Memoizable a = (a-b) - (a-b)

Due to modified parametricity, we have not only
id, ($), undefined :: ∀a∀b. (a-b) - (a-b)
- --($) = id is a correct definition
but also
($!) :: ∀a∀b. (a-b) - (a-b)
, because of the decision not to require a type-class context for seq.

Also GHC has special id-like functions such as 'lazy' and 'inline'... if
memoize is indistinguishable from id except in space/time usage, it
would be permissible as a compiler primitive.

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

iD8DBQFGWZPSHgcxvIWYTTURAigfAJ0eOBSP5zcXFxj/E/IlhqZRj0y06gCggAjq
We0TmsRK5jYHk9L3SEijEzE=
=wO/L
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe