propeller-0.2.0.0: A Propagator Library
Copyright(c) Michael Szvetits 2024
LicenseBSD3 (see the file LICENSE)
Maintainertypedbyte@qualified.name
Stabilitystable
Portabilityportable
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Propagator.ST

Description

This module exports ST-based types and functions needed to create cells, manipulate their data and wire them up for data propagation.

Synopsis

Networks

data Propagation s Source #

The result of a propagation which allows to rollback changes and inspect its success.

undo :: Propagation s -> ST s () Source #

An action that reverts all cell changes of a propagation (both direct and transitive ones).

succeeded :: Propagation s -> Bool Source #

True if the propagation was successful (i.e., it did not lead to a cell change that is Incompatible), otherwise False.

Note that unsuccessful propagations are not automatically reverted. Use undo to do this.

Cells

data Cell s a Source #

The type of a cell holding a value of type a. The type parameter s serves to keep the internal states of different cell networks separate from each other (see ST for details).

Instances

Instances details
Eq (Cell s a) Source # 
Instance details

Defined in Data.Propagator.ST

Methods

(==) :: Cell s a -> Cell s a -> Bool #

(/=) :: Cell s a -> Cell s a -> Bool #

data Change a Source #

Represents a potential change of a cell value.

Constructors

Changed a

Indicates that a cell value has been changed to the new value a.

Unchanged a

Indicates that a cell value did not change, i.e. needs no propagation.

Incompatible

Indicates that a new cell value contradicts the one that is already stored in the cell.

Instances

Instances details
Applicative Change Source # 
Instance details

Defined in Data.Propagator.Change

Methods

pure :: a -> Change a #

(<*>) :: Change (a -> b) -> Change a -> Change b #

liftA2 :: (a -> b -> c) -> Change a -> Change b -> Change c #

(*>) :: Change a -> Change b -> Change b #

(<*) :: Change a -> Change b -> Change a #

Functor Change Source # 
Instance details

Defined in Data.Propagator.Change

Methods

fmap :: (a -> b) -> Change a -> Change b #

(<$) :: a -> Change b -> Change a #

Monad Change Source # 
Instance details

Defined in Data.Propagator.Change

Methods

(>>=) :: Change a -> (a -> Change b) -> Change b #

(>>) :: Change a -> Change b -> Change b #

return :: a -> Change a #

Show a => Show (Change a) Source # 
Instance details

Defined in Data.Propagator.Change

Methods

showsPrec :: Int -> Change a -> ShowS #

show :: Change a -> String #

showList :: [Change a] -> ShowS #

Eq a => Eq (Change a) Source # 
Instance details

Defined in Data.Propagator.Change

Methods

(==) :: Change a -> Change a -> Bool #

(/=) :: Change a -> Change a -> Bool #

Ord a => Ord (Change a) Source # 
Instance details

Defined in Data.Propagator.Change

Methods

compare :: Change a -> Change a -> Ordering #

(<) :: Change a -> Change a -> Bool #

(<=) :: Change a -> Change a -> Bool #

(>) :: Change a -> Change a -> Bool #

(>=) :: Change a -> Change a -> Bool #

max :: Change a -> Change a -> Change a #

min :: Change a -> Change a -> Change a #

cell Source #

Arguments

:: a

The initial value of the cell.

-> (a -> a -> Change a)

A function that describes how to join an existing cell value with a new one that the cell has received via propagation.

-> ST s (Cell s a)

The newly constructed cell.

Constructs a new cell with a given initial value and a function which defines how to react if a new value is about to be written to the cell.

readCell :: Cell s a -> ST s a Source #

Reads the value of a specific cell.

writeCell :: a -> Cell s a -> ST s (Propagation s) Source #

Writes a new value to a specific cell and starts to propagate potential changes through the network of connected cells.

label Source #

Arguments

:: (a -> [b])

A function which extracts testable values from a cell content.

-> (b -> a)

A function which translates a testable value into a value which can be written back to the cell.

-> [Cell s a]

The set of cells for which the values are enumerated.

-> ST s [[b]]

Returns all valid assignments for the given cells.

If the content of a Cell s a is an accumulation of multiple values [b], and every value b itself can be used as content a for the cell, then we can write every value b one after another to the cell and check if the network converges to a successful state.

As a result, we can enumerate all possible combinations of valid values for a given set of cells. This is often used in constraint solving algorithms.

Connections

connect Source #

Arguments

:: Cell s a

The source cell.

-> Cell s b

The target cell.

-> (a -> ST s b)

A function that describes how the value for the target cell is constructed, based on the value of the source cell.

-> ST s ()

Note that no propagation takes place (i.e., no Propagation is returned).

Connects a source cell to a target cell in order to propagate changes from the source to the target.

Note that newly connected cells do not start to propagate changes immediately after wiring up. Use propagate or propagateMany to do this.

sync :: Cell s a -> Cell s a -> ST s () Source #

Connects and synchronizes two cells, i.e. new values are propagated from the source to the target cell, and vice versa. Short form of syncWith id id.

Note that newly connected cells do not start to propagate changes immediately after wiring up. Use propagate or propagateMany to do this.

syncWith :: (a -> b) -> (b -> a) -> Cell s a -> Cell s b -> ST s () Source #

Connects and synchronizes two cells using two translation functions f and g, i.e. new values are propagated from the source to the target cell using f, and vice versa using g.

Note that newly connected cells do not start to propagate changes immediately after wiring up. Use propagate or propagateMany to do this.

propagate :: Cell s a -> ST s (Propagation s) Source #

Propagates the value of a specific cell to its connected cells in a transitive manner. The propagation ends if no more cell changes occur or if an Incompatible cell value change is encountered.

propagateMany :: [Cell s a] -> ST s (Propagation s) Source #

Propagates the values of specific cells to their connected cells in a transitive manner. The propagation ends if no more cell changes occur or if an Incompatible cell value change is encountered.

Numeric

plus :: Num a => Cell s a -> Cell s a -> Cell s a -> ST s () Source #

plus a b c connects three cells using the following propagation schema:

  • a + b is propagated to c if a or b changes.
  • c - b is propagated to a if b or c changes.
  • c - a is propagated to b if a or c changes.

minus :: Num a => Cell s a -> Cell s a -> Cell s a -> ST s () Source #

minus a b c connects three cells using the following propagation schema:

  • a - b is propagated to c if a or b changes.
  • b + c is propagated to a if b or c changes.
  • a - c is propagated to b if a or c changes.

times :: Num a => Cell s a -> Cell s a -> Cell s a -> ST s () Source #

times a b c connects three cells using the following propagation schema:

  • a * b is propagated to c if a or b changes.

timesWith :: Num a => (a -> a -> a) -> Cell s a -> Cell s a -> Cell s a -> ST s () Source #

timesWith divOp a b c connects three cells using the following propagation schema:

  • a * b is propagated to c if a or b changes.
  • divOp c b is propagated to a if b or c changes.
  • divOp c a is propagated to b if a or c changes.

abs :: Num a => Cell s a -> Cell s a -> ST s () Source #

abs a b connects two cells using the following propagation schema:

  • |a| is propagated to b if a changes.

absWith :: Num a => (a -> a) -> Cell s a -> Cell s a -> ST s () Source #

absWith inv a b connects two cells using the following propagation schema:

  • |a| is propagated to b if a changes.
  • inv b is propagated to a if b changes.

negate :: Num a => Cell s a -> Cell s a -> ST s () Source #

negate a b connects two cells using the following propagation schema:

  • -a is propagated to b if a changes.
  • -b is propagated to a if b changes.

signum :: Num a => Cell s a -> Cell s a -> ST s () Source #

signum a b connects two cells using the following propagation schema:

  • Prelude.signum a is propagated to b if a changes.

signumWith :: Num a => (a -> a) -> Cell s a -> Cell s a -> ST s () Source #

signumWith inv a b connects two cells using the following propagation schema:

  • Prelude.signum a is propagated to b if a changes.
  • inv b is propagated to a if b changes.