[Haskell] Repeated evaluation of a constant value.
Lemmih
lemmih at gmail.com
Mon Sep 25 15:20:50 EDT 2006
On 9/25/06, Paul Johnson <paul at cogito.org.uk> wrote:
> I recently wanted to pass a lookup table around a program. Rather than
> having something explicitly typed as Map.Map I wrote a function that
> assembled
> a Map and then used Map.lookup to return a function, like this:
>
> > module Main where
> >
> > import qualified Data.Map as Map
> > import Debug.Trace
> >
> > alist :: [(String, Integer)]
> > alist = map (\i -> (show i, i)) [1..100]
> >
Change:
> > table :: [(String, Integer)] -> String -> Maybe Integer
> > table ls str = Map.lookup str fm
> > where fm = trace "Trace: making the map" $ Map.fromList ls
to:
> > table :: [(String, Integer)] -> String -> Maybe Integer
> > table ls = \str -> Map.lookup str fm
> > where fm = trace "Trace: making the map" $ Map.fromList ls
>
> "table" can be seen as a function from an association list to a look-up
> function.
>
> > demo :: [(String, Integer)] -> IO ()
Change:
> > demo ls = do
to:
> > demo ls = func `seq` do
> > showLookup "5"
> > showLookup "70"
> > showLookup "164"
> > showLookup "wibble"
> > where
> > func = table ls
> > showLookup str =
> > putStrLn $ "Look up " ++ show str ++ " gives " ++
> > show (func str) ++ "."
> >
> > main :: IO ()
> > main = demo alist
>
> I reasoned that closure returned by "table ls" would contain a thunk
> for "fm", which in turn would be evaluted the first time it was
> called. But it isn't: instead "fm" gets evaluated for every call to
> "table", as shown by the repeated trace messages.
>
> Store this message as "Thunk.lhs". Compile with ghc -O2 and run "main".
> What you get is:
>
> Trace: making the map
> Look up "5" gives Just 5.
> Trace: making the map
> Look up "70" gives Just 70.
> Trace: making the map
> Look up "164" gives Nothing.
> Trace: making the map
> Look up "wibble" gives Nothing.
>
> So my question is: how do I write "table" to return a function which does
> not build the lookup table for every call? Or is this a bug in GHC?
>
> (I should add that my real "table" function is rather more complicated, and
> only invokes Map.lookup on a subset of its arguments.)
>
>
> Paul.
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>
I've just given it a quick look so it may be flawed.
--
Cheers,
Lemmih
More information about the Haskell
mailing list