[Haskell-beginners] Lambda Functions
Peter Verswyvelen
bugfact at gmail.com
Fri Feb 27 18:40:57 EST 2009
On Fri, Feb 27, 2009 at 6:31 PM, Brent Yorgey <byorgey at seas.upenn.edu>wrote:
> The only disadvantage is that some things you might expect to be
> constants will actually get recomputed every time they are used. For
> example, suppose you define
>
> foo = very expensive computation involving a bunch of numbers
>
> You might think that foo will get computed just once, the first time
> it is needed. However, if foo ends up with a polymorphic type, like,
> say
>
> foo :: Num a => a
>
> then it is not actually a constant, but a function which takes a Num
> dictionary (i.e. a record of the Num methods) as an argument. So it
> will be recomputed every time it is used, since it might have
> different values for different types.
Yes indeed. Beginners might want to verify this with the following little
program (just assume 42 takes a very long to compute, on some alien computer
this took 7½ million years ;-)
import Debug.Trace
foo :: Num a => a
foo = trace "foo" $ 42
bar :: Int
bar = trace "bar" $ 42
When evaluating foo (e.g in GHCi) "foo" will be printed every time, bar only
once.
I guess a clever implementation would only compute foo once for each
different type of a? But then of course you'll hit a runtime performance
penalty every time when accessing foo since this will require a lookup...
Mmm, this feels as a case where you can't determine at compile time if a
function - in this case a polymorphic CAF - will need memoization or not...
For example (just a quick hack)
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 is cached" n)
Nothing -> (M.insert key value cache, value)
Now, you might wonder why this is such a big deal. The answer is: it
> isn't. I have the MR automatically turned off in my .ghci file, and
> I've never missed it. Furthermore, the monomorphism restriction will
> be removed in the next version of the Haskell language standard.
Cool. But I guess the next version of the standard will take a while? :)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20090228/91955b29/attachment.htm
More information about the Beginners
mailing list