[Haskell-cafe] Caching the Result of a Transaction?
Conal Elliott
conal at conal.net
Sun Apr 27 10:36:45 EDT 2008
Looks good to me, Jake. A few comments:
First, I think we want readTMVar instead of takeTMVar in newTIVal.
I think we *do* want unsafeNewEmptyTMVar inlined. Here's a convenient
caching wrapper:
cached :: STM a -> TIVal a
cached m = TIVal m (unsafePerformIO newEmptyTMVarIO)
The instances are then lovely:
instance Functor TIVal where
f `fmap` tiv = cached (f `fmap` force tiv)
instance Applicative TIVal where
pure x = cached (pure x)
ivf <*> ivx = cached (force ivf <*> force ivx)
instance Monad TIVal where
return x = cached (return x)
tiv >>= k = cached (force tiv >>= force . k)
I've assumed a standard monad-as-applicative instance for STM. Otherwise,
give one for TIVal.
Cheers, - Conal
On Sat, Apr 26, 2008 at 10:03 PM, Jake Mcarthur <jake.mcarthur at gmail.com>
wrote:
> 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.
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080427/69201f6b/attachment.htm
More information about the Haskell-Cafe
mailing list