[Haskell-cafe] Re: Caching the Result of a Transaction?
Conal Elliott
conal at conal.net
Mon Apr 28 16:13:19 EDT 2008
Hi Chris,
Thanks a bunch for the new angle.
Question & comments:
* I like the simplicity of using a single TVar whose state reflects the
not-computed/computed state of the IVal.
* I also like the public interface of taking an STM argument (newTIVal(IO))
over returning a sink (newEmptyTIVal(IO)), which came from some non-STM
thinking. In fact, maybe 'cached' is a better public interface yet. I'm
going to try it out, renaming "cached" to "ival". (Oh yeah, I'm shortening
"TIVal" to "IVal".)
* Why tryPutTMVar in place of putTMVar? Perhaps to encourage checking that
var hasn't been written?
* A perhaps prettier version of force:
force (TIVal tv) = readTVar tv >>= either compute return
where
compute wait = do a <- wait
writeTVar tv (Right a)
return a
* The Applicative STM instance can be simplified:
instance Applicative STM where { pure = return; (<*>) = ap }
Cheers, - Conal
On Mon, Apr 28, 2008 at 7:40 AM, ChrisK <haskell at list.mightyreason.com>
wrote:
> The garbage collector never gets to collect either the action used to
> populate the cached value, or the private TMVar used to hold the cached
> value.
>
> A better type for TIVal is given below. It is a newtype of a TVal. The
> contents are either a delayed computation or the previously forced value.
>
> Thew newTIVal(IO) functions immediately specify the delayed action.
>
> The newEmptyTIVal(IO) functions create a private TMVar that allows the
> delayed action to be specified once later. Note the use of tryPutTMVar to
> return a Bool instead of failing, in the event that the user tries to store
> more that one action.
>
> When force is called, the previous action (and any private TMVar) are
> forgotten. The garbage collector might then be free to collect them.
>
> --
> Chris
>
> -- By Chris Kuklewicz (April 2008), public domain
> > module TIVal(TIVal,newTIVal,newTIValIO,force,cached) where
> >
> > import Control.Applicative(Applicative(..))
> > import
> > Control.Concurrent.STM(STM,TVar,newTVar,newTVarIO,readTVar,writeTVar
> >
> > ,TMVar,newEmptyTMVar,newEmptyTMVarIO,tryPutTMVar,readTMVar)
> > import Control.Monad(Monad(..),join,liftM2)
> > import System.IO.Unsafe(unsafePerformIO)
> >
> > newtype TIVal a = TIVal (TVar (Either (STM a) a))
> >
> > -- the non-empty versions take a computation to delay
> >
> > newTIVal :: STM a -> STM (TIVal a)
> > newTIVal = fmap TIVal . newTVar . Left
> >
> > newTIValIO :: STM a -> IO (TIVal a)
> > newTIValIO = fmap TIVal . newTVarIO . Left
> >
> > -- The empty versions stage things with a TMVar, note the use of join
> > -- Plain values 'a' can be stored with (return a)
> >
> > newEmptyTIVal :: STM ( TIVal a, STM a -> STM Bool)
> > newEmptyTIVal = do
> > private <- newEmptyTMVar
> > tv <- newTVar (Left (join $ readTMVar private))
> > return (TIVal tv, tryPutTMVar private)
> >
> > newEmptyTIValIO :: IO ( TIVal a, STM a -> STM Bool )
> > newEmptyTIValIO = do
> > private <- newEmptyTMVarIO
> > tv <- newTVarIO (Left (join $ readTMVar private))
> > return (TIVal tv, tryPutTMVar private)
> >
> > -- force will clearly let go of the computation (and any private TMVar)
> >
> > force :: TIVal a -> STM a
> > force (TIVal tv) = do
> > v <- readTVar tv
> > case v of
> > Right a -> return a
> > Left wait -> do a <- wait
> > writeTVar tv (Right a)
> > return a
> >
> > -- Conal's "cached" function. This is actually safe.
> >
> > cached :: STM a -> TIVal a
> > cached = unsafePerformIO . newTIValIO
> >
> > -- The instances
> >
> > 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)
> >
> > instance Applicative STM where
> > pure x = return x
> > ivf <*> ivx = liftM2 ($) ivf ivx
> >
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080428/9ff5057c/attachment.htm
More information about the Haskell-Cafe
mailing list