
I kind a mention this because it might be easy for a polymorphic CAF to do
memoization so its value gets computed maximum once per type, e.g (quick and
dirty code follows)
import Data.Typeable
import Data.IORef
import qualified Data.IntMap as M
import System.IO.Unsafe
import Debug.Trace
fooCache :: IORef (M.IntMap a)
fooCache = unsafePerformIO $ newIORef M.empty
foo :: (Typeable a, Num a) => a
foo = unsafePerformIO $ do
key <- typeRepKey (typeOf value)
atomicModifyIORef fooCache (updateCache key)
where
value = trace "foo is computed" $ 42
updateCache key cache =
case key `M.lookup` cache of
Just n -> (cache, trace "foo was cached" n)
Nothing -> (M.insert key value cache, value)
A compiler (and Haskellers more clever than myself) could certainly come up
with something much more efficient here.
On Sat, Mar 28, 2009 at 12:51 AM, Peter Verswyvelen
From a previous email in the beginners list I more or less understood that
the monomorphism restriction will not exist anymore in Haskell Prime.
Is this correct? On Fri, Mar 27, 2009 at 10:32 PM, Jonathan Cast
wrote: 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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe