tweak-0.1.0.1: A library for incremental computing

Safe HaskellNone

Control.Tweak

Contents

Description

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 Vars

Var is a mututable reference with dependency information, which propagates changes through a graph of Vars.

Under the hood everything is done using TVars 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 Vars into Makers 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

Synopsis

Maker Interface

make :: Tweakable a -> Maker aSource

Turn a Tweakable into a Maker so it can be combined with other Makers

(.$.) :: 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.

Tweakable Interface

data Tweakable a whereSource

An expression that can be incrementally updated. Tweakable is basically an simple Applicative with a cached value.

Constructors

App :: Var b -> Tweakable (a -> b) -> Tweakable a -> Tweakable b 
Pure :: Var a -> Tweakable a 

readCache :: Tweakable a -> IO aSource

Read the cache of a Tweakable. This is nothing more than

 
   readCache = atomically . readCacheSTM  

readCacheSTM :: Tweakable a -> STM aSource

Read the cache of a Tweakable. See readCache for an IO version.

Var interface

data Var a Source

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.

Instances

Comply Maker Var 
Funktor Maker Var 
Eq (Var a)

Just checks pointer equality not value equality

Ord (Var a) 
Cacheable (Var a) 

IO Var CRU

newVar :: a -> IO (Var a)Source

Create a new Var. See newVarSTM for the STM version.

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

readVar :: Var a -> IO aSource

Read the cached value of a Var. See readVarSTM for an STM version

STM Var CRU

newVarSTM :: a -> STM (Var a)Source

Create a new Var. See newVar for the IO version.

modifyVarSTM :: Var a -> (a -> a) -> STM ()Source

Modify a Var and update the children. See modifyVar for the IO version

writeVarSTM :: Var a -> a -> STM ()Source

Write a new value into a Var and update all of the children. See writeVar for the IO version

readVarSTM :: Var a -> STM aSource

Read the cached value of a Var. See readVar for an IO version