[Haskell-cafe] memoization
staafmeister
g.c.stavenga at uu.nl
Fri Sep 11 08:57:01 EDT 2009
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.
More information about the Haskell-Cafe
mailing list