A bit of a shock - Memoizing functions

Hi, um, well, I'm not even sure if I have correctly understood this. Some of the memoizing functions, they actually "remember" stuff *between* calls? Günther

Hello Gü?nther, Friday, March 27, 2009, 11:30:41 PM, you wrote:
Some of the memoizing functions, they actually "remember" stuff *between* calls?
what i've seen in haskell - functions relying on lazy datastructures that ensure computation on first usage so this looks exactly like as memoizing: power 2 n | n>=0 && n<100 = powersOfTwo!n power x y = x^y powersOfTwo = array (0,99) [2^n | n <- [0..99] ] it's almost exact definition from ghc Prelude -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi Bulat, that is so cool! Günther Bulat Ziganshin schrieb:
Hello Gü?nther,
Friday, March 27, 2009, 11:30:41 PM, you wrote:
Some of the memoizing functions, they actually "remember" stuff *between* calls?
what i've seen in haskell - functions relying on lazy datastructures that ensure computation on first usage so this looks exactly like as memoizing:
power 2 n | n>=0 && n<100 = powersOfTwo!n power x y = x^y
powersOfTwo = array (0,99) [2^n | n <- [0..99] ]
it's almost exact definition from ghc Prelude

It seems there is a very close correspondence between data structures and
functions in Haskell. Your powersOfTwo function, since it gets memoized
automatically (is this the case for all functions of zero arguments?), seems
exactly like a data structure. This harks back to my Scheme days when we
learned about the close relationship between code and data.
I wonder: does the converse exist? Haskell data constructors which are
really functions? How and for what might one use those?
Thanks,
Kirk
On Fri, Mar 27, 2009 at 1:58 PM, GüŸnther Schmidt
Hi Bulat,
that is so cool!
Günther
Bulat Ziganshin schrieb:
Hello Gü?nther,
Friday, March 27, 2009, 11:30:41 PM, you wrote:
Some of the memoizing functions, they actually "remember" stuff
*between* calls?
what i've seen in haskell - functions relying on lazy datastructures that ensure computation on first usage so this looks exactly like as memoizing:
power 2 n | n>=0 && n<100 = powersOfTwo!n power x y = x^y
powersOfTwo = array (0,99) [2^n | n <- [0..99] ]
it's almost exact definition from ghc Prelude
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, 2009-03-27 at 14:26 -0700, Kirk Martinez wrote:
Your powersOfTwo function, since it gets memoized automatically (is this the case for all functions of zero arguments?),
It is the case for all functions which have zero arguments *at the time they are presented to the code generator*. The infamous evil monomorphism restriction arises from the fact that overloaded expressions, such as negative_one = exp(pi * sqrt(-1)) look like functions of zero arguments, but are not, and hence do not get memoized. This behavior was considered sufficiently surprising, when it was discovered in early Haskell compilers, that the construct was outlawed from the language entirely. jcc

2009/3/27 Kirk Martinez
It seems there is a very close correspondence between data structures and functions in Haskell. Your powersOfTwo function, since it gets memoized automatically (is this the case for all functions of zero arguments?), seems exactly like a data structure.
That's because it is. It's an array whose elements are computed on demand.
This harks back to my Scheme days when we learned about the close relationship between code and data.
I wonder: does the converse exist? Haskell data constructors which are really functions? How and for what might one use those?
Sure. You can use Church encoding to represent any Haskell data type
as a function.
--
Dave Menendez

2009/3/27 Kirk Martinez
I wonder: does the converse exist? Haskell data constructors which are really functions? How and for what might one use those?
You might enjoy reading about the use of tries for memoisation. Conal Elliott explains nicely how you can an isomorphism between certain types of function and certain types of tree structure: http://conal.net/blog/posts/elegant-memoization-with-functional-memo-tries/ It's neat because the rules for constructing the isomorphism are just like some well known rules of high school algebra, but interpreted in a new way. -- Dan

Hi Dan, yep, I've come across that one too and wouldn't you know it, the by now infamous Luke Palmer has left an interesting insight on that blog too :). So I reckon here the cycle closes. Günther Dan Piponi schrieb:
2009/3/27 Kirk Martinez
: I wonder: does the converse exist? Haskell data constructors which are really functions? How and for what might one use those?
You might enjoy reading about the use of tries for memoisation. Conal Elliott explains nicely how you can an isomorphism between certain types of function and certain types of tree structure: http://conal.net/blog/posts/elegant-memoization-with-functional-memo-tries/
It's neat because the rules for constructing the isomorphism are just like some well known rules of high school algebra, but interpreted in a new way. -- Dan

Kirk Martinez wrote:
It seems there is a very close correspondence between data structures and functions in Haskell. Your powersOfTwo function, since it gets memoized automatically (is this the case for all functions of zero arguments?), seems exactly like a data structure. This harks back to my Scheme days when we learned about the close relationship between code and data.
You might also find Neil's blog post about CAFs interesting: http://neilmitchell.blogspot.com/2009/02/monomorphism-and-defaulting.html Fijne avond, Martijn.

Hello, I've seen it done explicitly as is shown in the code below. 'f' in 'longest' is the function which is being memoized by the 'dp'. It's pretty slick, IMO. (not sure where this code came from. Also I may have broken it, but you get the idea): module Diff where import Data.Array -- * Dynamic Programming dp :: (Ix a) => (a,a) -> ((a->b) -> a -> b) -> a -> b dp bounds f = (memo!) where memo = tabulate bounds (f (memo!)) tabulate :: (Ix a) => (a,a) -> (a -> b) -> Array a b tabulate bounds f = array bounds [(i,f i) | i <- range bounds] -- * Two-way diff -- NOTE: I copied lcs/longest off the web somewhere, not sure what the license is lcs :: Ord a => [a] -> [a] -> [(Int, Int)] lcs xs ys = snd $ longest lenx leny xarr yarr (0,0) where lenx = length xs leny = length ys xarr = listArray (0,lenx-1) xs yarr = listArray (0,leny-1) ys longest :: Ord a => Int -> Int -> Array Int a -> Array Int a -> (Int, Int) -> (Int, [(Int, Int)]) longest a b c d| a `seq` b `seq` c `seq` d `seq` False = undefined longest lenx leny xarr yarr = dp ((0,0),(lenx,leny)) f where f rec (x,y) | x'ge'lenx && y'ge'leny = (0, []) | x'ge'lenx = y' | y'ge'leny = x' | xarr ! x == yarr ! y = max (match $ rec (x+1,y+1)) m | otherwise = m where m = max y' x' x'ge'lenx = x >= lenx y'ge'leny = y >= leny y' = miss (rec (x,y+1)) x' = miss (rec (x+1,y)) match (n,xs) = (n+1, (x,y):xs) miss = id -- miss z (n,xs) = (n,z:xs)
participants (9)
-
Bulat Ziganshin
-
Dan Piponi
-
David Menendez
-
Gü?nther Schmidt
-
Günther Schmidt
-
Jeremy Shaw
-
Jonathan Cast
-
Kirk Martinez
-
Martijn van Steenbergen