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

Description

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

Synopsis

Networks

data Network a Source #

A network consists of cells and connections which propagate data between them.

empty :: Network a Source #

Represents an empty network.

data Error a Source #

Represents possible errors that may occur when modifying or using a network.

Constructors

InvalidCell CellKey

The specified cell could not be found.

InvalidConnect ConnectKey

The specified connection could not be found.

NoPropagation ConnectKey

The specified did not produce a value.

Conflict CellKey a a

The old value of the specified cell is incompatible with a new value propagated to it.

Cycle CellKey

The specified cell propagated a value to itself (directly or indirectly), leading to a cycle.

Instances

Instances details
Show a => Show (Error a) Source # 
Instance details

Defined in Data.Propagator

Methods

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

show :: Error a -> String #

showList :: [Error a] -> ShowS #

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

Defined in Data.Propagator

Methods

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

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

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

Defined in Data.Propagator

Methods

compare :: Error a -> Error a -> Ordering #

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

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

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

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

max :: Error a -> Error a -> Error a #

min :: Error a -> Error a -> Error a #

data Propagator a b Source #

Network modifications and data propagations are captured by the Propagator monad.

Instances

Instances details
Applicative (Propagator a) Source # 
Instance details

Defined in Data.Propagator

Methods

pure :: a0 -> Propagator a a0 #

(<*>) :: Propagator a (a0 -> b) -> Propagator a a0 -> Propagator a b #

liftA2 :: (a0 -> b -> c) -> Propagator a a0 -> Propagator a b -> Propagator a c #

(*>) :: Propagator a a0 -> Propagator a b -> Propagator a b #

(<*) :: Propagator a a0 -> Propagator a b -> Propagator a a0 #

Functor (Propagator a) Source # 
Instance details

Defined in Data.Propagator

Methods

fmap :: (a0 -> b) -> Propagator a a0 -> Propagator a b #

(<$) :: a0 -> Propagator a b -> Propagator a a0 #

Monad (Propagator a) Source # 
Instance details

Defined in Data.Propagator

Methods

(>>=) :: Propagator a a0 -> (a0 -> Propagator a b) -> Propagator a b #

(>>) :: Propagator a a0 -> Propagator a b -> Propagator a b #

return :: a0 -> Propagator a a0 #

runPropagator :: Propagator a b -> Network a -> Either (Error a) (Network a, b) Source #

Applies modifications captured by the propagator monad to a network, thus producing a new network if no error occurred.

Cells

data CellKey Source #

Represents a unique identification of a network cell.

Instances

Instances details
Show CellKey Source # 
Instance details

Defined in Data.Propagator

Eq CellKey Source # 
Instance details

Defined in Data.Propagator

Methods

(==) :: CellKey -> CellKey -> Bool #

(/=) :: CellKey -> CellKey -> Bool #

Ord CellKey Source # 
Instance details

Defined in Data.Propagator

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.

-> Propagator a CellKey

The identification of 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 :: CellKey -> Propagator a a Source #

Reads the value of a specific cell.

writeCell :: CellKey -> a -> Propagator a () Source #

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

removeCell :: CellKey -> Propagator a () Source #

Removes a cell from the network. This also removes all connections related to the cell.

label :: (a -> [b]) -> (b -> a) -> [CellKey] -> Propagator a [[b]] Source #

If the content of a cell 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.

This function does not perform any permanent network modifications.

Connections

data ConnectKey Source #

Represents a unique identification of a network connection.

data ConnectState Source #

When connecting cells, the ConnectState defines the initial behaviour of the connection.

Constructors

Live

The connection immediately starts to propagate data between the connected cells.

Idle

The connection is established, but no initial data propagation takes place.

connect :: ConnectState -> CellKey -> CellKey -> (a -> Maybe a) -> Propagator a ConnectKey Source #

Connects a source cell to a target cell in order to propagate changes from the source to the target. The returned ConnectKey can be used to remove the connection via disconnect.

connect_ :: ConnectState -> CellKey -> CellKey -> (a -> Maybe a) -> Propagator a () Source #

Same as connect, but discards the returned ConnectKey.

sync :: ConnectState -> CellKey -> CellKey -> Propagator a (ConnectKey, ConnectKey) 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 Just Just.

sync_ :: ConnectState -> CellKey -> CellKey -> Propagator a () Source #

Same as sync, but discards the returned ConnectKeys.

syncWith :: (a -> Maybe a) -> (a -> Maybe a) -> ConnectState -> CellKey -> CellKey -> Propagator a (ConnectKey, ConnectKey) 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.

syncWith_ :: (a -> Maybe a) -> (a -> Maybe a) -> ConnectState -> CellKey -> CellKey -> Propagator a () Source #

Same as syncWith, but discards the returned ConnectKeys.

combine :: ConnectState -> CellKey -> CellKey -> CellKey -> (a -> a -> Maybe a) -> Propagator a ConnectKey Source #

Connects two source cells to a target cell in order to propagate changes from the sources to the target. The returned ConnectKey can be used to remove the connection via disconnect.

combine_ :: ConnectState -> CellKey -> CellKey -> CellKey -> (a -> a -> Maybe a) -> Propagator a () Source #

Same as combine, but discards the returned ConnectKey.

combineMany :: ConnectState -> [CellKey] -> CellKey -> ([a] -> Maybe a) -> Propagator a ConnectKey Source #

Connects several source cells to a target cell in order to propagate changes from the sources to the target. The returned ConnectKey can be used to remove the connection via disconnect.

combineMany_ :: ConnectState -> [CellKey] -> CellKey -> ([a] -> Maybe a) -> Propagator a () Source #

Same as combineMany, but discards the returned ConnectKey.

distribute :: ConnectState -> CellKey -> [CellKey] -> (a -> Maybe a) -> Propagator a ConnectKey Source #

Connects a source cells to several target cells in order to propagate changes from the source to the targets. The returned ConnectKey can be used to remove the connection via disconnect.

distribute_ :: ConnectState -> CellKey -> [CellKey] -> (a -> Maybe a) -> Propagator a () Source #

Same as distribute, but discards the returned ConnectKey.

manyToMany :: ConnectState -> [CellKey] -> [CellKey] -> ([a] -> Maybe a) -> Propagator a ConnectKey Source #

Connects several source cells to several target cells in order to propagate changes from the sources to the targets. The returned ConnectKey can be used to remove the connection via disconnect.

manyToMany_ :: ConnectState -> [CellKey] -> [CellKey] -> ([a] -> Maybe a) -> Propagator a () Source #

Same as manyToMany, but discards the returned ConnectKey.

disconnect :: ConnectKey -> Propagator a () Source #

Removes a connection from the network.

Numeric

plus :: Num a => ConnectState -> CellKey -> CellKey -> CellKey -> Propagator a () Source #

plus s 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 => ConnectState -> CellKey -> CellKey -> CellKey -> Propagator a () Source #

minus s 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 => ConnectState -> CellKey -> CellKey -> CellKey -> Propagator a () Source #

times s 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) -> ConnectState -> CellKey -> CellKey -> CellKey -> Propagator a () Source #

timesWith divOp s 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 => ConnectState -> CellKey -> CellKey -> Propagator a () Source #

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

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

absWith :: Num a => (a -> a) -> ConnectState -> CellKey -> CellKey -> Propagator a () Source #

absWith inv s 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 => ConnectState -> CellKey -> CellKey -> Propagator a () Source #

negate s 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 => ConnectState -> CellKey -> CellKey -> Propagator a () Source #

signum s 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) -> ConnectState -> CellKey -> CellKey -> Propagator a () Source #

signumWith inv s 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.