Safe Haskell | None |
---|
Tweak exposes an interface for incremental computation.
There are three main types that work together to build expressions that can
updated incrementally: Maker
, Tweakable
, and Var
.
Maker
exposes a Functor
and Applicative
interface for building Tweakable
expressions
Tweakable
constructs expressions that can be re-evaluated incrementally by calling
readCache
. In contains caches of Var
s
Var
is a mututable reference with dependency information, which propagates changes
through a graph of Var
s.
Under the hood everything is done using TVar
s and the system is meant to be used
in a concurrent environment. There are STM
versions of functions that occur in IO
to help build more complex STM
transactions.
Here is a simple example.
Import Control.Tweak test = do foo <- newVar 1 baz <- newVar 2 quux <- runMaker $ (*) <$> make baz <*> make baz bar <- runMaker $ (+) <$> make foo <*> make quux -- prints 5 print =<< readCache bar writeVar foo 10 -- print =<< readCache bar
It is a little inconvient to explictly convert Var
s into Maker
s so there is some
Applicative
and Functor
like sugar for <$>
and <*>
, that also does the
proper wrapping of Var
and Tweakable
.
Using the sugar the example above looks like.
Import Control.Tweak test = do foo <- newVar 1 baz <- newVar 2 quux <- runMaker $ (*) .$. baz .*. baz bar <- runMaker $ (+) .$. foo .*. quux -- prints 5 print =<< readCache bar writeVar foo 10 -- print =<< readCache bar
The important people of the example above, is when the foo
is updated, only bar
is updated, not quux
- data Maker a
- runmaker :: Maker a -> IO (Tweakable a)
- make :: Tweakable a -> Maker a
- (.$.) :: Funktor g f => (a -> b) -> f a -> g b
- (.*.) :: Comply g h => g (a -> b) -> h a -> g b
- module Control.Applicative
- data Tweakable a where
- readCache :: Tweakable a -> IO a
- readCacheSTM :: Tweakable a -> STM a
- data Var a
- newVar :: a -> IO (Var a)
- modifyVar :: Var a -> (a -> a) -> IO ()
- writeVar :: Var a -> a -> IO ()
- readVar :: Var a -> IO a
- newVarSTM :: a -> STM (Var a)
- modifyVarSTM :: Var a -> (a -> a) -> STM ()
- writeVarSTM :: Var a -> a -> STM ()
- readVarSTM :: Var a -> STM a
Maker Interface
Maker
is the Applicative
used to create Tweakable
expressions
Use the Applicative
interface or the Applicative
helpers
.$.
and .*.
(.$.) :: Funktor g f => (a -> b) -> f a -> g bSource
This is slight variation on <$>
. Use .$.
and .*.
avoid explicit
calls to make
and Pure
.
Unlike Functor the input and output * -> * type can change. There is no reasoning or laws behind it, it is just sugar.
The Funktor type class is closed and private. There are only instances
for Maker
, Tweakable
, and Var
.
(.*.) :: Comply g h => g (a -> b) -> h a -> g bSource
This is slight variation on <*>
. Use .$.
and .*.
avoid explicit
calls to make
and Pure
.
Unlike Apply, with Comply the input and output * -> * type can change. Like Funktor, there is no reasoning or laws behind it, it is just sugar.
The Comply type class is closed and private. There are only instances
for Maker
, Tweakable
, and Var
.
module Control.Applicative
Tweakable Interface
An expression that can be incrementally updated.
Tweakable
is basically an simple Applicative
with a cached value.
readCache :: Tweakable a -> IO aSource
Read the cache of a Tweakable
. This is nothing more than
readCache = atomically . readCacheSTM
readCacheSTM :: Tweakable a -> STM aSource
Var interface
This a reference for incremental computation. Not only does it include a value, But is also has a list of actions to execute when it is updated.
IO Var CRU
modifyVar :: Var a -> (a -> a) -> IO ()Source
Modify a Var
and update the children.
See modifyVarSTM
for the STM
version
writeVar :: Var a -> a -> IO ()Source
Write a new value into a Var
and update all of the children.
See writeVarSTM
for the STM
version
STM Var CRU
modifyVarSTM :: Var a -> (a -> a) -> STM ()Source
writeVarSTM :: Var a -> a -> STM ()Source