Copyright | (c) Tom Harding 2020 |
---|---|
License | MIT |
Safe Haskell | None |
Language | Haskell2010 |
The real heart of a propagator network is the cell-level interaction, but it
doesn't come with a particularly pleasant API. The solution is the Prop
abstraction, which hides away some of the more gruesome internals.
This module exposes a set of functions to construct propagator networks with a "focal point", which we can intuit as being the "output" of the functions we're used to writing.
The important thing to note is that most of these functions allow for multi-directional information flow. While '(.&&)' might look like '(&&)', it allows the inputs to be computed from the outputs, so it's a lot more capable. Think of these functions as a way to build equations that we can re-arrange as need be.
Synopsis
- data Prop (m :: Type -> Type) (content :: Type)
- up :: Applicative m => Cell m x -> Prop m x
- down :: (MonadCell m, Monoid x) => Prop m x -> m (Cell m x)
- lift :: MonadCell m => x -> Prop m x
- over :: (Merge x, Merge y) => (x -> y) -> Prop m x -> Prop m y
- lift2 :: (Merge x, Merge y, Merge z) => (x -> y -> z) -> Prop m x -> Prop m y -> Prop m z
- unary :: (Merge x, Merge y) => ((x, y) -> (x, y)) -> Prop m x -> Prop m y
- binary :: (Merge x, Merge y, Merge z) => ((x, y, z) -> (x, y, z)) -> Prop m x -> Prop m y -> Prop m z
- (.&&) :: BooleanR b => Prop m b -> Prop m b -> Prop m b
- all' :: (BooleanR b, MonadCell m) => (x -> Prop m b) -> [x] -> Prop m b
- allWithIndex' :: (BooleanR b, MonadCell m) => (Int -> x -> Prop m b) -> [x] -> Prop m b
- and' :: (BooleanR b, MonadCell m) => [Prop m b] -> Prop m b
- (.||) :: BooleanR b => Prop m b -> Prop m b -> Prop m b
- any' :: (BooleanR b, MonadCell m) => (x -> Prop m b) -> [x] -> Prop m b
- anyWithIndex' :: (BooleanR b, MonadCell m) => (Int -> x -> Prop m b) -> [x] -> Prop m b
- or' :: (BooleanR b, MonadCell m) => [Prop m b] -> Prop m b
- false :: (BooleanR b, MonadCell m) => Prop m b
- not' :: (BooleanR b, MonadCell m) => Prop m b -> Prop m b
- true :: (BooleanR b, MonadCell m) => Prop m b
- (.==) :: (EqR x b, MonadCell m) => Prop m x -> Prop m x -> Prop m b
- (./=) :: (EqR x b, MonadCell m) => Prop m x -> Prop m x -> Prop m b
- distinct :: (EqR x b, MonadCell m) => [Prop m x] -> Prop m b
- (.>) :: (OrdR x b, MonadCell m) => Prop m x -> Prop m x -> Prop m b
- (.>=) :: (OrdR x b, MonadCell m) => Prop m x -> Prop m x -> Prop m b
- (.<) :: (OrdR x b, MonadCell m) => Prop m x -> Prop m x -> Prop m b
- (.<=) :: (OrdR x b, MonadCell m) => Prop m x -> Prop m x -> Prop m b
- (.+) :: (SumR x, MonadCell m) => Prop m x -> Prop m x -> Prop m x
- (.-) :: (SumR x, MonadCell m) => Prop m x -> Prop m x -> Prop m x
- negate' :: (Num x, SumR x, MonadCell m) => Prop m x -> Prop m x
- (.*.) :: (Num x, IntegralR x) => Prop m x -> Prop m x -> Prop m x
- (./.) :: (IntegralR x, MonadCell m) => Prop m x -> Prop m x -> Prop m x
- (.%.) :: (IntegralR x, MonadCell m) => Prop m x -> Prop m x -> Prop m x
- (.*) :: (FractionalR x, MonadCell m) => Prop m x -> Prop m x -> Prop m x
- (./) :: (FractionalR x, MonadCell m) => Prop m x -> Prop m x -> Prop m x
- recip' :: (Num x, FractionalR x, MonadCell m) => Prop m x -> Prop m x
- abs' :: (AbsR x, MonadCell m) => Prop m x -> Prop m x
- (.$) :: (Mapping f c, c x, c y) => (x -> y) -> Prop m (f x) -> Prop m (f y)
- zipWith' :: (Zipping f c, c x, c y, c z) => ((x, y, z) -> (x, y, z)) -> Prop m (f x) -> Prop m (f y) -> Prop m (f z)
- (.>>=) :: (FlatMapping f c, c x, c y) => Prop m (f x) -> (x -> f y) -> Prop m (f y)
Documentation
data Prop (m :: Type -> Type) (content :: Type) Source #
A propagator network with a "focus" on a particular cell. The focus is the cell that typically holds the result we're trying to compute.
up :: Applicative m => Cell m x -> Prop m x Source #
Lift a cell into a propagator network. Mostly for internal library use.
down :: (MonadCell m, Monoid x) => Prop m x -> m (Cell m x) Source #
Lower a propagator network's focal point down to a cell. Mostly for internal library use.
lift :: MonadCell m => x -> Prop m x Source #
Lift a regular value into a propagator network. This is analogous to
pure
for some Applicative
type.
over :: (Merge x, Merge y) => (x -> y) -> Prop m x -> Prop m y Source #
Lift a regular function into a propagator network. The function is lifted into a relationship with one-way information flow.
lift2 :: (Merge x, Merge y, Merge z) => (x -> y -> z) -> Prop m x -> Prop m y -> Prop m z Source #
Lift a regular binary function into a propagator network. The function is lifted into a relationship between three variables where information only flows in one direction.
unary :: (Merge x, Merge y) => ((x, y) -> (x, y)) -> Prop m x -> Prop m y Source #
Lift a unary relationship into a propagator network. Unlike over
, this
allows information to travel in both directions.
binary :: (Merge x, Merge y, Merge z) => ((x, y, z) -> (x, y, z)) -> Prop m x -> Prop m y -> Prop m z Source #
Lift a binary relationship into a propagator network. This allows three-way information flow.
(.&&) :: BooleanR b => Prop m b -> Prop m b -> Prop m b infixr 3 Source #
Different parameter types come with different representations for Bool
.
This function takes two propagator networks focusing on boolean values, and
produces a new network in which the focus is the conjunction of the two
values.
It's a lot of words, but the intuition is, "'(&&)' over propagators".
all' :: (BooleanR b, MonadCell m) => (x -> Prop m b) -> [x] -> Prop m b Source #
Run a predicate on all values in a list, producing a list of propagator networks focusing on boolean values. Then, produce a new network with a focus on the conjunction of all these values.
In other words, "all
over propagators".
allWithIndex' :: (BooleanR b, MonadCell m) => (Int -> x -> Prop m b) -> [x] -> Prop m b Source #
The same as the all'
function, but with access to the index of the
element within the array. Typically, this is useful when trying to relate
each element to other elements within the array.
For example, cells "surrounding" the current cell in a conceptual "board".
and' :: (BooleanR b, MonadCell m) => [Prop m b] -> Prop m b Source #
Given a list of propagator networks with a focus on boolean values, create a new network with a focus on the conjugation of all these values.
In other words, "and
over propagators".
(.||) :: BooleanR b => Prop m b -> Prop m b -> Prop m b infixr 2 Source #
Calculate the disjunction of two boolean propagator network values.
any' :: (BooleanR b, MonadCell m) => (x -> Prop m b) -> [x] -> Prop m b Source #
Run a predicate on all values in a list, producing a list of propagator networks focusing on boolean values. Then, produce a new network with a focus on the disjunction of all these values.
In other words, "any
over propagators".
anyWithIndex' :: (BooleanR b, MonadCell m) => (Int -> x -> Prop m b) -> [x] -> Prop m b Source #
The same as the any'
function, but with access to the index of the
element within the array. Typically, this is useful when trying to relate
each element to other elements within the array.
For example, cells "surrounding" the current cell in a conceptual "board".
or' :: (BooleanR b, MonadCell m) => [Prop m b] -> Prop m b Source #
Given a list of propagator networks with a focus on boolean values, create a new network with a focus on the disjunction of all these values.
In other words, "or
over propagators".
false :: (BooleanR b, MonadCell m) => Prop m b Source #
Different parameter types come with different representations for Bool
.
This value is a propagator network with a focus on a polymorphic "falsey"
value.
not' :: (BooleanR b, MonadCell m) => Prop m b -> Prop m b Source #
Given a propagator network with a focus on a boolean value, produce a network with a focus on its negation.
... It's "not
over propagators".
true :: (BooleanR b, MonadCell m) => Prop m b Source #
Different parameter types come with different representations for Bool
.
This value is a propagator network with a focus on a polymorphic "truthy"
value.
(.==) :: (EqR x b, MonadCell m) => Prop m x -> Prop m x -> Prop m b infix 4 Source #
Given two propagator networks, produce a new propagator network with the result of testing the two for equality.
In other words, "it's '(==)' for propagators".
(./=) :: (EqR x b, MonadCell m) => Prop m x -> Prop m x -> Prop m b infix 4 Source #
Given two propagator networks, produce a new propagator network with the result of testing the two for inequality.
In other words, "it's '(/=)' for propagators".
distinct :: (EqR x b, MonadCell m) => [Prop m x] -> Prop m b Source #
Given a list of networks, produce the conjunction of '(./=)' applied to every possible pair. The resulting network's focus is the answer to whether every propagator network's focus is different to the others.
Are all the values in this list distinct?
(.>) :: (OrdR x b, MonadCell m) => Prop m x -> Prop m x -> Prop m b infix 4 Source #
Given two propagator networks, produce a new network that calculates whether the first network's focus be greater than the second.
In other words, "it's '(>)' for propagators".
(.>=) :: (OrdR x b, MonadCell m) => Prop m x -> Prop m x -> Prop m b infix 4 Source #
Given two propagator networks, produce a new network that calculates whether the first network's focus be greater than or equal to the second.
In other words, "it's '(>=)' for propagators".
(.<) :: (OrdR x b, MonadCell m) => Prop m x -> Prop m x -> Prop m b infix 4 Source #
Given two propagator networks, produce a new network that calculates whether the first network's focus be less than the second.
In other words, "it's '(<)' for propagators".
(.<=) :: (OrdR x b, MonadCell m) => Prop m x -> Prop m x -> Prop m b infix 4 Source #
Given two propagator networks, produce a new network that calculates whether the first network's focus be less than or equal to the second.
In other words, "it's '(<=)' for propagators".
(.+) :: (SumR x, MonadCell m) => Prop m x -> Prop m x -> Prop m x infixl 6 Source #
Given two propagator networks, produce a new network that focuses on the sum of the two given networks' foci.
... It's '(+)' lifted over propagator networks.
(.-) :: (SumR x, MonadCell m) => Prop m x -> Prop m x -> Prop m x infixl 6 Source #
Given two propagator networks, produce a new network that focuses on the difference between the two given networks' foci.
... It's '(-)' lifted over propagator networks.
negate' :: (Num x, SumR x, MonadCell m) => Prop m x -> Prop m x Source #
Produce a network that focuses on the negation of another network's focus.
... It's negate
lifted over propagator networks.
(.*.) :: (Num x, IntegralR x) => Prop m x -> Prop m x -> Prop m x infixl 7 Source #
Given two propagator networks, produce a new network that focuses on the product between the two given networks' integral foci.
... It's '(*)' lifted over propagator networks. Crucially, the reverse
information flow uses integral division, which should work the same way
as div
.
(./.) :: (IntegralR x, MonadCell m) => Prop m x -> Prop m x -> Prop m x infixl 7 Source #
Given two propagator networks, produce a new network that focuses on the division of the two given networks' integral foci.
... It's div
lifted over propagator networks.
(.%.) :: (IntegralR x, MonadCell m) => Prop m x -> Prop m x -> Prop m x infixl 7 Source #
Given two propagator networks, produce a new network that focuses on the modulo of the two given networks' integral foci.
... It's mod
lifted over propagator networks.
(.*) :: (FractionalR x, MonadCell m) => Prop m x -> Prop m x -> Prop m x infixl 7 Source #
Given two propagator networks, produce a new network that focuses on the product of the two given networks' foci.
... It's '(*)' lifted over propagator networks. The reverse information flow is fractional division, '(/)'.
(./) :: (FractionalR x, MonadCell m) => Prop m x -> Prop m x -> Prop m x infixl 7 Source #
Given two propagator networks, produce a new network that focuses on the division of the two given networks' foci.
... It's '(/)' lifted over propagator networks.
recip' :: (Num x, FractionalR x, MonadCell m) => Prop m x -> Prop m x Source #
Produce a network that focuses on the reciprocal of another network's focus.
... It's recip
lifted over propagator networks.
abs' :: (AbsR x, MonadCell m) => Prop m x -> Prop m x Source #
Produce a network that focuses on the absolute value of another network's focus.
... It's abs
lifted over propagator networks.
zipWith' :: (Zipping f c, c x, c y, c z) => ((x, y, z) -> (x, y, z)) -> Prop m (f x) -> Prop m (f y) -> Prop m (f z) Source #
Lift a three-way relationship over two propagator networks' foci to produce a third propagator network with a focus on the third value in the relationship.
... It's liftA2
for propagators.