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

2008-04-29 Thread Jake Mcarthur

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


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

2008-04-29 Thread Jake Mcarthur
*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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

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


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

2008-04-28 Thread 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 


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


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

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

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


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

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


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

2008-04-28 Thread Jake Mcarthur

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


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

2008-04-28 Thread Conal Elliott
Thanks, Ryan, for the reminder and explanation of this problem.  - Conal

On Mon, Apr 28, 2008 at 8:01 PM, Ryan Ingram [EMAIL PROTECTED] 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.

 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

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