Copyright | (c) Michael Szvetits 2024 |
---|---|
License | BSD3 (see the file LICENSE) |
Maintainer | typedbyte@qualified.name |
Stability | stable |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
This module exports the types and functions needed to create cells of heterogeneous types, manipulate their data and wire them up for data propagation.
Synopsis
- data Network
- empty :: Network
- data Error
- = InvalidCell (Some CellKey)
- | InvalidConnect ConnectKey
- | NoPropagation ConnectKey
- | Conflict (Some CellKey)
- data Propagator a
- runPropagator :: Propagator a -> Network -> Either Error (Network, a)
- newtype CellKey (a :: Type) = CellKey {
- rawCellKey :: Int
- data CellKeys ts where
- data CellValues ts where
- VNil :: CellValues '[]
- VCons :: a -> CellValues ts -> CellValues (a ': ts)
- data Change a
- = Changed a
- | Unchanged a
- | Incompatible
- cell :: (CellKey a -> a) -> (a -> a -> Change a) -> Propagator (CellKey a)
- readCell :: CellKey a -> Propagator a
- writeCell :: a -> CellKey a -> Propagator ()
- removeCell :: CellKey a -> Propagator ()
- label :: (a -> [b]) -> (b -> a) -> [CellKey a] -> Propagator [[b]]
- newtype ConnectKey = ConnectKey {
- rawConnectKey :: Int
- data ConnectState
- connect :: ConnectState -> CellKey a -> CellKey b -> (a -> Maybe b) -> Propagator ConnectKey
- connect_ :: ConnectState -> CellKey a -> CellKey b -> (a -> Maybe b) -> Propagator ()
- sync :: ConnectState -> CellKey a -> CellKey a -> Propagator (ConnectKey, ConnectKey)
- sync_ :: ConnectState -> CellKey a -> CellKey a -> Propagator ()
- syncWith :: (a -> Maybe b) -> (b -> Maybe a) -> ConnectState -> CellKey a -> CellKey b -> Propagator (ConnectKey, ConnectKey)
- syncWith_ :: (a -> Maybe b) -> (b -> Maybe a) -> ConnectState -> CellKey a -> CellKey b -> Propagator ()
- combine :: ConnectState -> CellKey a -> CellKey b -> CellKey c -> (a -> b -> Maybe c) -> Propagator ConnectKey
- combine_ :: ConnectState -> CellKey a -> CellKey b -> CellKey c -> (a -> b -> Maybe c) -> Propagator ()
- combineMany :: ConnectState -> CellKeys ts -> CellKey a -> (CellValues ts -> Maybe a) -> Propagator ConnectKey
- combineMany_ :: ConnectState -> CellKeys ts -> CellKey a -> (CellValues ts -> Maybe a) -> Propagator ()
- distribute :: ConnectState -> CellKey a -> [CellKey b] -> (a -> Maybe b) -> Propagator ConnectKey
- distribute_ :: ConnectState -> CellKey a -> [CellKey b] -> (a -> Maybe b) -> Propagator ()
- manyToMany :: ConnectState -> CellKeys xs -> [CellKey a] -> (CellValues xs -> Maybe a) -> Propagator ConnectKey
- manyToMany_ :: ConnectState -> CellKeys xs -> [CellKey a] -> (CellValues xs -> Maybe a) -> Propagator ()
- disconnect :: ConnectKey -> Propagator ()
- plus :: Num a => ConnectState -> CellKey a -> CellKey a -> CellKey a -> Propagator ()
- minus :: Num a => ConnectState -> CellKey a -> CellKey a -> CellKey a -> Propagator ()
- times :: Num a => ConnectState -> CellKey a -> CellKey a -> CellKey a -> Propagator ()
- timesWith :: Num a => (a -> a -> a) -> ConnectState -> CellKey a -> CellKey a -> CellKey a -> Propagator ()
- abs :: Num a => ConnectState -> CellKey a -> CellKey a -> Propagator ()
- absWith :: Num a => (a -> a) -> ConnectState -> CellKey a -> CellKey a -> Propagator ()
- negate :: Num a => ConnectState -> CellKey a -> CellKey a -> Propagator ()
- signum :: Num a => ConnectState -> CellKey a -> CellKey a -> Propagator ()
- signumWith :: Num a => (a -> a) -> ConnectState -> CellKey a -> CellKey a -> Propagator ()
Networks
Represents possible errors that may occur when modifying or using a network.
InvalidCell (Some CellKey) | The specified cell could not be found. |
InvalidConnect ConnectKey | The specified connection could not be found. |
NoPropagation ConnectKey | The specified connection did not produce a value. |
Conflict (Some CellKey) | The old value of the specified cell is incompatible with a new value propagated to it. |
data Propagator a Source #
Network modifications and data propagations are captured by the Propagator
monad.
Instances
Applicative Propagator Source # | |
Defined in Data.Propagator.Hetero pure :: a -> Propagator a # (<*>) :: Propagator (a -> b) -> Propagator a -> Propagator b # liftA2 :: (a -> b -> c) -> Propagator a -> Propagator b -> Propagator c # (*>) :: Propagator a -> Propagator b -> Propagator b # (<*) :: Propagator a -> Propagator b -> Propagator a # | |
Functor Propagator Source # | |
Defined in Data.Propagator.Hetero fmap :: (a -> b) -> Propagator a -> Propagator b # (<$) :: a -> Propagator b -> Propagator a # | |
Monad Propagator Source # | |
Defined in Data.Propagator.Hetero (>>=) :: Propagator a -> (a -> Propagator b) -> Propagator b # (>>) :: Propagator a -> Propagator b -> Propagator b # return :: a -> Propagator a # |
runPropagator :: Propagator a -> Network -> Either Error (Network, a) Source #
Applies modifications captured by the propagator monad to a network, thus producing a new network if no error occurred.
Cells
newtype CellKey (a :: Type) Source #
Represents a unique identification of a network cell.
Such an identification should not be constructed manually, or else
InvalidCell
errors are possible. The raw identification is exposed for
situations where cells should be managed externally, like in an IntMap
.
CellKey | |
|
data CellValues ts where Source #
Represents a list of cell values of heterogeneous types.
VNil :: CellValues '[] | |
VCons :: a -> CellValues ts -> CellValues (a ': ts) infixr 3 |
Represents a potential change of a cell value.
Changed a | Indicates that a cell value has been changed to the new value |
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. |
:: (CellKey a -> a) | Function which produces 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 (CellKey a) | 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 a -> Propagator a Source #
Reads the value of a specific cell.
writeCell :: a -> CellKey a -> Propagator () Source #
Writes a new value to a specific cell and starts to propagate potential changes through the network of connected cells.
removeCell :: CellKey a -> Propagator () Source #
Removes a cell from the network. This also removes all connections related to the cell.
label :: (a -> [b]) -> (b -> a) -> [CellKey a] -> Propagator [[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
newtype ConnectKey Source #
Represents a unique identification of a network connection.
Such an identification should not be constructed manually, or else
InvalidConnect
errors are possible. The raw identification is exposed for
situations where connections should be managed externally, like in an IntMap
.
Instances
Show ConnectKey Source # | |
Defined in Data.Propagator.Hetero showsPrec :: Int -> ConnectKey -> ShowS # show :: ConnectKey -> String # showList :: [ConnectKey] -> ShowS # | |
Eq ConnectKey Source # | |
Defined in Data.Propagator.Hetero (==) :: ConnectKey -> ConnectKey -> Bool # (/=) :: ConnectKey -> ConnectKey -> Bool # | |
Ord ConnectKey Source # | |
Defined in Data.Propagator.Hetero compare :: ConnectKey -> ConnectKey -> Ordering # (<) :: ConnectKey -> ConnectKey -> Bool # (<=) :: ConnectKey -> ConnectKey -> Bool # (>) :: ConnectKey -> ConnectKey -> Bool # (>=) :: ConnectKey -> ConnectKey -> Bool # max :: ConnectKey -> ConnectKey -> ConnectKey # min :: ConnectKey -> ConnectKey -> ConnectKey # |
data ConnectState Source #
When connecting cells, the ConnectState
defines the initial behaviour of the connection.
Live | The connection immediately starts to propagate data between the connected cells. |
Idle | The connection is established, but no initial data propagation takes place. |
Instances
Show ConnectState Source # | |
Defined in Data.Propagator.Hetero showsPrec :: Int -> ConnectState -> ShowS # show :: ConnectState -> String # showList :: [ConnectState] -> ShowS # | |
Eq ConnectState Source # | |
Defined in Data.Propagator.Hetero (==) :: ConnectState -> ConnectState -> Bool # (/=) :: ConnectState -> ConnectState -> Bool # | |
Ord ConnectState Source # | |
Defined in Data.Propagator.Hetero compare :: ConnectState -> ConnectState -> Ordering # (<) :: ConnectState -> ConnectState -> Bool # (<=) :: ConnectState -> ConnectState -> Bool # (>) :: ConnectState -> ConnectState -> Bool # (>=) :: ConnectState -> ConnectState -> Bool # max :: ConnectState -> ConnectState -> ConnectState # min :: ConnectState -> ConnectState -> ConnectState # |
connect :: ConnectState -> CellKey a -> CellKey b -> (a -> Maybe b) -> Propagator 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 a -> CellKey b -> (a -> Maybe b) -> Propagator () Source #
Same as connect
, but discards the returned ConnectKey
.
sync :: ConnectState -> CellKey a -> CellKey a -> Propagator (ConnectKey, ConnectKey) Source #
sync_ :: ConnectState -> CellKey a -> CellKey a -> Propagator () Source #
Same as sync
, but discards the returned ConnectKey
s.
syncWith :: (a -> Maybe b) -> (b -> Maybe a) -> ConnectState -> CellKey a -> CellKey b -> Propagator (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 b) -> (b -> Maybe a) -> ConnectState -> CellKey a -> CellKey b -> Propagator () Source #
Same as syncWith
, but discards the returned ConnectKey
s.
combine :: ConnectState -> CellKey a -> CellKey b -> CellKey c -> (a -> b -> Maybe c) -> Propagator 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 a -> CellKey b -> CellKey c -> (a -> b -> Maybe c) -> Propagator () Source #
Same as combine
, but discards the returned ConnectKey
.
combineMany :: ConnectState -> CellKeys ts -> CellKey a -> (CellValues ts -> Maybe a) -> Propagator 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 -> CellKeys ts -> CellKey a -> (CellValues ts -> Maybe a) -> Propagator () Source #
Same as combineMany
, but discards the returned ConnectKey
.
distribute :: ConnectState -> CellKey a -> [CellKey b] -> (a -> Maybe b) -> Propagator 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 a -> [CellKey b] -> (a -> Maybe b) -> Propagator () Source #
Same as distribute
, but discards the returned ConnectKey
.
manyToMany :: ConnectState -> CellKeys xs -> [CellKey a] -> (CellValues xs -> Maybe a) -> Propagator 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 -> CellKeys xs -> [CellKey a] -> (CellValues xs -> Maybe a) -> Propagator () Source #
Same as manyToMany
, but discards the returned ConnectKey
.
disconnect :: ConnectKey -> Propagator () Source #
Removes a connection from the network.
Numeric
plus :: Num a => ConnectState -> CellKey a -> CellKey a -> CellKey a -> Propagator () Source #
plus s a b c
connects three cells using the following propagation schema:
a + b
is propagated toc
ifa
orb
changes.c - b
is propagated toa
ifb
orc
changes.c - a
is propagated tob
ifa
orc
changes.
minus :: Num a => ConnectState -> CellKey a -> CellKey a -> CellKey a -> Propagator () Source #
minus s a b c
connects three cells using the following propagation schema:
a - b
is propagated toc
ifa
orb
changes.b + c
is propagated toa
ifb
orc
changes.a - c
is propagated tob
ifa
orc
changes.
times :: Num a => ConnectState -> CellKey a -> CellKey a -> CellKey a -> Propagator () Source #
times s a b c
connects three cells using the following propagation schema:
a * b
is propagated toc
ifa
orb
changes.
timesWith :: Num a => (a -> a -> a) -> ConnectState -> CellKey a -> CellKey a -> CellKey a -> Propagator () Source #
timesWith divOp s a b c
connects three cells using the following propagation schema:
a * b
is propagated toc
ifa
orb
changes.divOp c b
is propagated toa
ifb
orc
changes.divOp c a
is propagated tob
ifa
orc
changes.
abs :: Num a => ConnectState -> CellKey a -> CellKey a -> Propagator () Source #
abs s a b
connects two cells using the following propagation schema:
|a|
is propagated tob
ifa
changes.
absWith :: Num a => (a -> a) -> ConnectState -> CellKey a -> CellKey a -> Propagator () Source #
absWith inv s a b
connects two cells using the following propagation schema:
|a|
is propagated tob
ifa
changes.inv b
is propagated toa
ifb
changes.
negate :: Num a => ConnectState -> CellKey a -> CellKey a -> Propagator () Source #
negate s a b
connects two cells using the following propagation schema:
-a
is propagated tob
ifa
changes.-b
is propagated toa
ifb
changes.
signum :: Num a => ConnectState -> CellKey a -> CellKey a -> Propagator () Source #
signum s a b
connects two cells using the following propagation schema:
Prelude.signum a
is propagated tob
ifa
changes.
signumWith :: Num a => (a -> a) -> ConnectState -> CellKey a -> CellKey a -> Propagator () Source #
signumWith inv s a b
connects two cells using the following propagation schema:
Prelude.signum a
is propagated tob
ifa
changes.inv b
is propagated toa
ifb
changes.