Caching the Result of a Transaction?

I have a problem I've been trying to work around using the existing STM API, and so far it seems that I may be unable to do it. For more background, see my blog post at <http://geekrant.wordpress.com/2008/04/25/stm-caching-need/
. Here, for brevity, I will only describe exactly what I think I need, not what it's for.
Say I have a function f :: STM a. The transaction reads from one or more TMVars, performs some computation, and returns the result in the STM monad. Also, in this scenario, it is known that once the TMVars have values, those values will never be changed again (write once, read many, somewhat like IVars before they were removed). Now say I try to use this function as so. liftM2 (,) f f So the desired result is a pair in the STM monad where both components are the result from f. The problem I have is that, in the above example, the TMVars are all read twice and the computations are all performed twice, once for each of the components of the resulting pair. In many cases, this may be the correct thing to do because the values of the TMVars may have changed, but what about this case where I _know_ that the values have not been modified? What I need is a way to cache the result of f so that future uses of f don't have to reread from the TMVars, even across multiple transactions, maybe even leading to the eventual garbage collection of the TMVars if they are not used elsewhere. Right now I think the only way to do this would be to change the STM implementation slightly and create a new primitive function. If there is a way to do something like this with the current STM API, I would love to hear suggestions. Any ideas? - Jake McArthur

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.
- Conal
On Sat, Apr 26, 2008 at 9:54 AM, Jake Mcarthur
I have a problem I've been trying to work around using the existing STM API, and so far it seems that I may be unable to do it. For more background, see my blog post at < http://geekrant.wordpress.com/2008/04/25/stm-caching-need/>. Here, for brevity, I will only describe exactly what I think I need, not what it's for.
Say I have a function f :: STM a. The transaction reads from one or more TMVars, performs some computation, and returns the result in the STM monad. Also, in this scenario, it is known that once the TMVars have values, those values will never be changed again (write once, read many, somewhat like IVars before they were removed). Now say I try to use this function as so.
liftM2 (,) f f
So the desired result is a pair in the STM monad where both components are the result from f. The problem I have is that, in the above example, the TMVars are all read twice and the computations are all performed twice, once for each of the components of the resulting pair. In many cases, this may be the correct thing to do because the values of the TMVars may have changed, but what about this case where I _know_ that the values have not been modified?
What I need is a way to cache the result of f so that future uses of f don't have to reread from the TMVars, even across multiple transactions, maybe even leading to the eventual garbage collection of the TMVars if they are not used elsewhere.
Right now I think the only way to do this would be to change the STM implementation slightly and create a new primitive function. If there is a way to do something like this with the current STM API, I would love to hear suggestions. Any ideas?
- Jake McArthur _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Conal Elliott said:
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.
Perhaps what you and Jake are looking for are fully-fledged "triggers" on transactional memory. To solve the fmap problem, have each TIVar backed by a separate TVar. Then the TIVar returned by fmap would act as a cache for the original TIVar. A trigger would watch the TVar which backs the original TIVar, updating the cache TVar when the original TIVar is written. Nested fmaps would work simply as a cascade of triggers. The STM authors considered the possibility of triggers in their paper on invariants [1], but instead took the safer option of read-only invariants. [1]http://research.microsoft.com/~simonpj/papers/stm/stm-invariants.pdf

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.

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
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.

On Apr 27, 2008, at 9:36 AM, Conal Elliott wrote:
First, I think we want readTMVar instead of takeTMVar in newTIVal.
I don't see any reason it would hurt to use takeTMVar, and I suspect the garbage collector might be slightly happier this way since it potentially means once less reference to the data stored in the TMVar.
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)
Yes, this is essentially what I am working with in Reaction at the moment. It seems to be working great, but I have not specifically tested the caching behavior yet, only that it doesn't screw up what I had working in the first place. I must admit that I think I don't fully understand the implications of inlining vs. not inlining unsafePerformIO. - Jake

On Apr 27, 2008, at 10:05 AM, Jake Mcarthur wrote:
On Apr 27, 2008, at 9:36 AM, Conal Elliott wrote:
I think we *do* want unsafeNewEmptyTMVar inlined. Here's a convenient caching wrapper:
cached :: STM a -> TIVal a cached m = TIVal m (unsafePerformIO newEmptyTMVarIO)
Yes, this is essentially what I am working with in Reaction at the moment.
Actually, that is not quite what I have been doing. Here is what I had: cachedFuture :: STM (a, Time) -> Future a cachedFuture stm = unsafePerformIO $ return . Future stm =<< newEmptyTMVarIO {-# NOINLINE cachedFuture #-} (Clearly I am skipping right past an implementation of TIVals, despite the fact that they may be useful as a separate abstraction. This is just laziness.) If I replace the above with... cachedFuture :: STM (a, Time) -> Future a cachedFuture stm = Future stm (unsafePerformIO newEmptyTMVarIO) then my test program hangs, with or without the NOINLINE pragma. I can't guess why because, like I already said, I haven't yet thought all the way through the relationship between unsafePerformIO and NOINLINE. - Jake

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

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
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

The problem I have with all of these STM-based solutions to this problem is that they don't actually cache until the action fully executes successfully. For example, if you have a :: TIVal a, and f :: a -> TIVal b, and you execute force (a >>= f) and the action returned by f executes retry for whatever reason, then the caching done in "a" gets undone. Ideally I want to be able to provide some proof that the result of a is pure and have it committed immediately when it finishes. Every attempt I've had so far to solve this problem ends up being some type of the form newtype X a = IO (STM (Either a (X a))) which has its own problems. -- ryan

On Apr 28, 2008, at 10:01 PM, Ryan Ingram wrote:
[...] if you have a :: TIVal a, and f :: a -> TIVal b, and you execute force (a >>= f)
and the action returned by f executes retry for whatever reason, then the caching done in "a" gets undone.
Dangit, you're right. You just rained on the parade! Hmm... Perhaps we could use the data structure Chris proposed and mix it with my first approach involving forkIO. Another thread can perform the caching in a separate transaction _or_ the main thread can perform the caching itself in case the extra thread doesn't get a chance first. This would ensure that it manages to get cached _sometime_ even when the main transaction itself retries, but it loses some of the elegance we had gained by not forking a new thread and still doesn't _guarantee_ that the computations are run only once. This is not ideal. :( - Jake

Thanks, Ryan, for the reminder and explanation of this problem. - Conal
On Mon, Apr 28, 2008 at 8:01 PM, Ryan Ingram
The problem I have with all of these STM-based solutions to this problem is that they don't actually cache until the action fully executes successfully.
For example, if you have a :: TIVal a, and f :: a -> TIVal b, and you execute force (a >>= f)
and the action returned by f executes retry for whatever reason, then the caching done in "a" gets undone. Ideally I want to be able to provide some proof that the result of a is pure and have it committed immediately when it finishes.
Every attempt I've had so far to solve this problem ends up being some type of the form newtype X a = IO (STM (Either a (X a))) which has its own problems.
-- ryan

On Apr 28, 2008, at 10:01 PM, Ryan Ingram wrote:
The problem I have with all of these STM-based solutions to this problem is that they don't actually cache until the action fully executes successfully.
I just hacked together a new monad that I think might solve this, at least with a little extra work. I haven't tested it yet though because I have to do some studying now. I just want to go ahead and put it up for review and see if you guys think this is a good approach. To use it you use the "could" and "must" functions to specify which STM actions may be rolled back and which ones must be permanent. When you apply maybeAtomicallyC to a CachedSTM action, all the "must" actions are performed individually, where any that fail do not affect any of the others. Once the "must" actions are done, the "could" actions are performed, returning Just the result. If that fails then the whole thing simply returns Nothing, but the "must" actions are still committed. At least, I _hope_ the above is what it actually does!
module CachedSTM where
import Control.Applicative import Control.Concurrent.STM import Control.Monad
data CachedSTM a = CSTM { getMust :: STM (), getShould :: STM a }
instance Functor CachedSTM where f `fmap` (CSTM m s) = CSTM m $ f <$> s
joinCSTM :: CachedSTM (CachedSTM a) -> CachedSTM a joinCSTM cstm = CSTM m s where m = do cstm' <- getShould cstm getMust cstm' `orElse` return () getMust cstm `orElse` return () s = getShould =<< getShould cstm
instance Applicative CachedSTM where pure = return (<*>) = ap
instance Monad CachedSTM where return = CSTM (return ()) . return x >>= f = joinCSTM $ f <$> x
maybeAtomicallyC :: CachedSTM a -> IO (Maybe a) maybeAtomicallyC cstm = atomically $ do getMust cstm liftM Just (getShould cstm) `orElse` return Nothing
could :: STM a -> CachedSTM a could stm = CSTM (return ()) stm
must :: STM () -> CachedSTM () must stm = CSTM stm $ return ()
Now the IVal stuff might look something like:
module IVal where
import CachedSTM import Control.Applicative import Control.Concurrent.STM import Control.Monad import System.IO.Unsafe
newtype IVal a = IVal (TVar (Either (CachedSTM a) a))
newIVal :: CachedSTM a -> CachedSTM (IVal a) newIVal = fmap IVal . could . newTVar . Left
newIValIO :: CachedSTM a -> IO (IVal a) newIValIO = fmap IVal . newTVarIO . Left
cached :: CachedSTM a -> IVal a cached = unsafePerformIO . newIValIO
force :: IVal a -> CachedSTM a force (IVal tv) = could (readTVar tv) >>= either compute return where compute wait = do x <- wait must . writeTVar tv $ Right x return x
instance Functor IVal where f `fmap` x = cached $ f <$> force x
instance Applicative IVal where pure = return (<*>) = ap
instance Monad IVal where return = cached . return x >>= f = cached (force x >>= force . f)
- Jake

Alright, I have tested it now. I still feel funny about most of the names I chose for the types and functions, and it's still very ugly, but the code appears to work correctly. In this version I have also added "retry" and "orElse" functions so that it can feel more like the STM monad. I think the biggest downside to this monad is the potential confusion about whether to use "could" or "must," but I have a feeling that better naming choices would reduce the ambiguity. Thoughts?
module CachedSTM where
import Control.Applicative import Control.Concurrent.STM as S import Control.Monad
data CachedSTM a = CSTM { getMust :: STM (), getCould :: STM a }
instance Functor CachedSTM where f `fmap` (CSTM m s) = CSTM m $ f <$> s
joinCSTM :: CachedSTM (CachedSTM a) -> CachedSTM a joinCSTM cstm = CSTM m s where m = do cstm' <- getCould cstm getMust cstm' `S.orElse` return () getMust cstm `S.orElse` return () s = getCould =<< getCould cstm
instance Applicative CachedSTM where pure = return (<*>) = ap
instance Monad CachedSTM where return = CSTM (return ()) . return x >>= f = joinCSTM $ f <$> x
maybeAtomicallyC :: CachedSTM a -> IO (Maybe a) maybeAtomicallyC cstm = atomically $ do getMust cstm liftM Just (getCould cstm) `S.orElse` return Nothing
could :: STM a -> CachedSTM a could stm = CSTM (return ()) stm
must :: STM () -> CachedSTM () must stm = CSTM (stm `S.orElse` return ()) $ return ()
retry :: CachedSTM a retry = could S.retry
orElse :: CachedSTM a -> CachedSTM a -> CachedSTM a orElse a b = do must $ getMust a temp <- could newEmptyTMVar must $ (getCould a >>= putTMVar temp) `S.orElse` getMust b could $ takeTMVar temp `S.orElse` getCould b
I don't think the IVar code has changed (no version control for this), but here it is again for quick reference:
module IVal where
import CachedSTM import Control.Applicative import Control.Concurrent.STM import Control.Monad import System.IO.Unsafe
newtype IVal a = IVal (TVar (Either (CachedSTM a) a))
newIVal :: CachedSTM a -> CachedSTM (IVal a) newIVal = fmap IVal . could . newTVar . Left
newIValIO :: CachedSTM a -> IO (IVal a) newIValIO = fmap IVal . newTVarIO . Left
cached :: CachedSTM a -> IVal a cached = unsafePerformIO . newIValIO
force :: IVal a -> CachedSTM a force (IVal tv) = could (readTVar tv) >>= either compute return where compute wait = do x <- wait must . writeTVar tv $ Right x return x
instance Functor IVal where f `fmap` x = cached $ f <$> force x
instance Applicative IVal where pure = return (<*>) = ap
instance Monad IVal where return = cached . return x >>= f = cached (force x >>= force . f)
- Jake

*sigh* As is usual with my untested code, the code I just sent was wrong. I will be able to actually test, correct, and refine it tonight. If nobody else has picked it up by then I will do so. - Jake
participants (5)
-
ChrisK
-
Conal Elliott
-
Jake Mcarthur
-
Matthew Brecknell
-
Ryan Ingram