stm-incremental-0.1.1.0: A library for constructing incremental computations
Copyright(c) Samuel Schlesinger 2020
LicenseMIT
Maintainersgschlesinger@gmail.com
Stabilityexperimental
PortabilityPOSIX, Windows
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Concurrent.STM.Incremental

Description

This library exposes a minimal interface for incremental computation, where we decompose our computation into the explicit computational dependencies and only recompute things when their dependencies have been recomputed. Here is a basic example:

main = do
  (a, b, c, d) <- atomically $ do
    a <- incremental 0
    b <- incremental 1
    c <- imap (+ 1) b
    d <- combine (+) c b
    pure (a, b, c, d)

  guard =<< (atomically $ do
    (== 3) $ observe d)

  guard =<< (atomically $ do
    set a 1
    set b 0
    (== 1) $ observe d)

Here, we see that we can set some variables and notice their changes, all done in STM atomically blocks which allows us to combine these computations transactionally with other logic we've written in STM. What happens if we try to write to c? Well, we get a type error! The only Incremental computations which we can set new values for are the leaves of the computation, constructed with incremental. This is this way because we don't want to mutate Incrementals downstream of dependencies, because then we cannot know that those computations remain consistent. Most operations are polymorphic over Mutable and Immutable Incrementals, but imap, combine, and choose all produce an Incremental Immutable, whereas incremental produces a Incremental Mutable.

Synopsis

Documentation

data Mutability Source #

A data kind intended to help us expose a safe interface, only allowing us to modify leaf nodes of computational graphs as to avoid inconsistent states.

Constructors

Immutable 
Mutable 

data Incremental (mutability :: Mutability) a Source #

An incremental computation, only updated when one of its dependencies is.

incremental :: a -> STM (Incremental 'Mutable a) Source #

Construct a trivial, mutable incremental computation. This is mutable precisely because it is trivial, as modifications to anything else cannot cause it to be modified. Thus, we can change it willy nilly without fear that we've invalidated someone else's changes to it.

observe :: Incremental m a -> STM a Source #

Observes the present value of any incremental computation.

set :: Incremental 'Mutable a -> a -> STM () Source #

Sets the value of a mutable incremental computation.

setEq :: Eq a => Incremental 'Mutable a -> a -> STM () Source #

Sets the value of a mutable incremental computation, with the added optimization that if the value is equal to the old one, this does not update the dependents of this Incremental value.

imap :: (a -> b) -> Incremental m a -> STM (Incremental 'Immutable b) Source #

Create an incrementally mapped computation, producing an immutable incremental computation that will always contain the function mapped over the value inside of the original computation.

imapEq :: Eq b => (a -> b) -> Incremental m a -> STM (Incremental 'Immutable b) Source #

Create an incrementally mapped computation, producing an immutable incremental computation that will always contain the function mapped over the value inside of the original computation.

combine :: (a -> b -> c) -> Incremental m a -> Incremental m' b -> STM (Incremental 'Immutable c) Source #

Combines the results of two incremental computation into a third, producing an immutable incremental computation that will always contain the function mapped over both of the values inside of the respective incremental computations.

combineEq :: Eq c => (a -> b -> c) -> Incremental m a -> Incremental m' b -> STM (Incremental 'Immutable c) Source #

Like combine, but with the added optimization that if the value computed is equal to the old one, it will not propagate the update through any further.

choose :: Incremental m' a -> (a -> Incremental m b) -> STM (Incremental 'Immutable b) Source #

Chooses an incremental computation depending on the value inside of another one. When using map and combine, you are constructing a static dependency graph, whereas when you use this function you are making it dynamic, the linkages depending on the actual contents of the incremental computation nodes.

chooseEq :: Eq b => Incremental m' a -> (a -> Incremental m b) -> STM (Incremental 'Immutable b) Source #

Like choose, but with the added optimization that we do not propagate changes when we don't have to in a similar way to setEq, combineEq, and imapEq.

immutable :: Incremental 'Mutable b -> Incremental 'Immutable b Source #

Sometimes, we need to consider an Incremental Mutable in a setting alongside Incremental Immutable values, unifying their type. One example where this is common is in choose:

...
x <- incremental True
y <- map not x
z <- choose y (bool y x)
...

This code will not compile, because y and x have different types, but this will:

...
x <- incremental True
y <- map not x
z <- choose y (bool y (immutable x))
...

onUpdate :: Incremental m b -> (b -> STM ()) -> STM () Source #

Add monitoring hooks which can do arbitrary actions in STM with the changed value whenever this Incremental is updated. One useful example of this is used for testing this module, recording the history of an Incremental computation:

history :: Incremental m b -> STM (STM [b])
history i = do
  x <- observe i
  h <- newTVar [x]
  onUpdate i b -> do
    bs <- readTVar h
    writeTVar h (b : bs)
  pure (readTVar h)

history :: Incremental m b -> STM (STM [b]) Source #

Instruments the given Incremental with functionality to save the history of its values. This is useful for testing.