[Haskell-cafe] Caching the Result of a Transaction?
Jake Mcarthur
jake.mcarthur at gmail.com
Sun Apr 27 01:03:57 EDT 2008
On Apr 26, 2008, at 7:18 PM, Conal Elliott wrote:
> Here's another angle on part of Jake's question:
>
> Can we implement a type 'TIVal a' (preferably without
> unsafePerformIO) with the following interface:
>
> newIVal :: STM (TIVal a, a -> STM ()) -- or IO (...)
> force :: TIVal a -> STM a
>
> instance Functor IVal
> instance Applicative IVal
> instance Monad IVal
>
> where
>
> * 'newIVal' makes something like an IVar that can be written/defined
> (just once) with the returned a->STM().
> * 'force' gets the value, retrying if not yet defined; once force is
> able to succeed, it always yields the same value.
> * 'fmap f tiv' becomes defined (force yields a value instead of
> retrying) when tiv does. Similarly for (<*>) and join.
> * Forcing 'fmap f tiv' more than once results in f being called only
> once, i.e., the result is cached and reused, as in pure values.
> Similarly for (<*>) and join.
Well, I think I may have done it! This is only code that I typed up
really quick. I haven't even made sure it compiles. Regardless, I
think the gist is pretty clear...
data TIVal a = TIVal (STM a) (TMVar a)
newTIVal = do uc <- newEmptyTMVar
c <- newEmptyTMVar
return (TIVal (takeTMVar uc) c, putTMVar uc)
force (TIVal uc c) = readTMVar c `orElse` cache
where cache = do x <- uc
putTMVar c x
return x
unsafeNewEmptyTMVar = unsafePerformIO newEmptyTMVarIO
-- insert NOINLINE and/or other magical pragmas here
instance Functor TIVal where
f `fmap` x = TIVal (return . f =<< force x) unsafeNewEmptyTMVar
-- Applicative, Monad, and Monoid omitted
I did have to resort to unsafePerformIO, but I think the reason is
innocent enough to still feel good about. This implementation, if it
works, seems to be embarrassingly simple.
More information about the Haskell-Cafe
mailing list