Re: [Haskell-cafe] Caching the Result of a Transaction?

2008-04-27 Thread Jake Mcarthur

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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Caching the Result of a Transaction?

2008-04-26 Thread Conal Elliott
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 [EMAIL PROTECTED]
wrote:

 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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Caching the Result of a Transaction?

2008-04-26 Thread Matthew Brecknell
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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Caching the Result of a Transaction?

2008-04-26 Thread 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.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe