holmes-0.1.0.1: Tools and combinators for solving constraint problems.

Copyright(c) Tom Harding 2020
LicenseMIT
Safe HaskellNone
LanguageHaskell2010

Data.Holmes

Description

This module includes almost everything you'd need to build a constraint-solving computation. The module uses the Holmes solver, but you may want to use the functions in the Control.Monad.Watson module to avoid executing your code in IO.

Synopsis

Documentation

data Holmes (x :: Type) Source #

A monad capable of solving constraint problems using IO as the evaluation type. Cells are represented using IORef references, and provenance is tracked to optimise backtracking search across multiple branches.

Instances
Monad Holmes Source # 
Instance details

Defined in Control.Monad.Holmes

Methods

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

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

return :: a -> Holmes a #

fail :: String -> Holmes a #

Functor Holmes Source # 
Instance details

Defined in Control.Monad.Holmes

Methods

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

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

Applicative Holmes Source # 
Instance details

Defined in Control.Monad.Holmes

Methods

pure :: a -> Holmes a #

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

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

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

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

MonadCell Holmes Source # 
Instance details

Defined in Control.Monad.Holmes

Associated Types

data Cell Holmes a :: Type Source #

Methods

discard :: Holmes x Source #

fill :: x -> Holmes (Cell Holmes x) Source #

watch :: Cell Holmes x -> (x -> Holmes ()) -> Holmes () Source #

with :: Cell Holmes x -> (x -> Holmes ()) -> Holmes () Source #

write :: Merge x => Cell Holmes x -> x -> Holmes () Source #

newtype Cell Holmes x Source # 
Instance details

Defined in Control.Monad.Holmes

newtype Cell Holmes x = Cell {}

class Monad m => MonadCell (m :: Type -> Type) Source #

The DSL for network construction primitives. The following interface provides the building blocks upon which the rest of the library is constructed.

If you are looking to implement the class yourself, you should note the lack of functionality for ambiguity/searching. This is deliberate: for backtracking search (as opposed to truth maintenance-based approaches), the ability to create computation branches dynamically makes it much harder to establish a reliable mechanism for tracking the effects of these choices.

For example: the approach used in the MoriarT implementation is to separate the introduction of ambiguity into one definite, explicit step, and all parameters must be declared ahead of time so that they can be assigned indices. Other implementations should feel free to take other approaches, but these will be implementation-specific.

Minimal complete definition

discard, fill, watch, with, write

Instances
MonadCell Holmes Source # 
Instance details

Defined in Control.Monad.Holmes

Associated Types

data Cell Holmes a :: Type Source #

Methods

discard :: Holmes x Source #

fill :: x -> Holmes (Cell Holmes x) Source #

watch :: Cell Holmes x -> (x -> Holmes ()) -> Holmes () Source #

with :: Cell Holmes x -> (x -> Holmes ()) -> Holmes () Source #

write :: Merge x => Cell Holmes x -> x -> Holmes () Source #

MonadCell (Watson h) Source # 
Instance details

Defined in Control.Monad.Watson

Associated Types

data Cell (Watson h) a :: Type Source #

Methods

discard :: Watson h x Source #

fill :: x -> Watson h (Cell (Watson h) x) Source #

watch :: Cell (Watson h) x -> (x -> Watson h ()) -> Watson h () Source #

with :: Cell (Watson h) x -> (x -> Watson h ()) -> Watson h () Source #

write :: Merge x => Cell (Watson h) x -> x -> Watson h () Source #

forward :: (Typeable x, Merge x, Merge y) => (forall m. MonadCell m => Prop m x -> Prop m y) -> x -> Maybe y Source #

Run a function between propagators with a raw value, writing the given value to the "input" cell and reading the result from the "output" cell.

backward :: (Typeable x, Merge x, Merge y) => (forall m. MonadCell m => Prop m x -> Prop m y) -> y -> Maybe x Source #

Run a function between propagators "backwards", writing the given value as the output and then trying to push information backwards to the input cell.

satisfying :: (EqR x b, Typeable x) => Config Holmes x -> (forall m. MonadCell m => [Prop m x] -> Prop m b) -> IO (Maybe [x]) Source #

Given an input configuration, and a predicate on those input variables, return the first configuration that satisfies the predicate.

shuffle :: Config Holmes x -> Config Holmes x Source #

Shuffle the refinements in a configuration. If we make a configuration like 100 from [1 .. 10], the first configuration will be one hundred 1 values. Sometimes, we might find we get to a first solution faster by randomising the order in which refinements are given. This is similar to the "random restart" strategy in hill-climbing problems.

Another nice use for this function is procedural generation: often, your results will look more "natural" if you introduce an element of randomness.

whenever :: (EqR x b, Typeable x) => Config Holmes x -> (forall m. MonadCell m => [Prop m x] -> Prop m b) -> IO [[x]] Source #

Given an input configuration, and a predicate on those input variables, return all configurations that satisfy the predicate. It should be noted that there's nothing lazy about this; if your problem has a lot of solutions, or your search space is very big, you'll be waiting a long time!

data Config (m :: Type -> Type) (x :: Type) Source #

An input configuration.

This stores both an initial configuration of input parameters, as well as a function that can look for ways to refine an input. In other words, if the initial value is an Data.JoinSemilattice.Intersect of [1 .. 5], the refinements might be singleton values of every remaining possibility.

Constructors

Config 

Fields

class Input (x :: Type) where Source #

The simplest way of generating an input configuration is to say that a problem has m variables that will all be one of n possible values. For example, a sudoku board is 81 variables of 9 possible values. This class allows us to generate these simple input configurations like a game of countdown: "81 from 1 .. 9, please, Carol!"

Associated Types

type Raw x :: Type Source #

Different parameter types will have different representations for their values. The Raw type means that I can say 81 from [1 .. 9], and have the parameter type determine how it will represent 1, for example. It's a little bit of syntactic sugar for the benefit of the user, so they don't need to know as much about how the parameter types work to use the library.

Methods

from :: Applicative m => Int -> [Raw x] -> Config m x Source #

Generate m variables who are one of n values. 81 from [1 .. 9], 5 from [ True, False ], and so on.

Instances
Input (Defined content) Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

Associated Types

type Raw (Defined content) :: Type Source #

Methods

from :: Applicative m => Int -> [Raw (Defined content)] -> Config m (Defined content) Source #

Intersectable x => Input (Intersect x) Source # 
Instance details

Defined in Data.JoinSemilattice.Intersect

Associated Types

type Raw (Intersect x) :: Type Source #

Methods

from :: Applicative m => Int -> [Raw (Intersect x)] -> Config m (Intersect x) Source #

permute :: (Applicative m, Eq x, Hashable x) => Config m x -> m (HashSet [x]) Source #

For debugging purposes, produce a HashSet of all possible refinements that a Config might produce for a given problem. This set could potentially be very large!

class Merge x => AbsR (x :: Type) where Source #

Unlike the abs we know, which is a function from a value to its absolute value, absR is a relationship between a value and its absolute.

For some types, while we can't truly reverse the abs function, we can say that there are two possible inputs to consider, and so we can push some information in the reverse direction.

Minimal complete definition

Nothing

Methods

absR :: (x, x) -> (x, x) Source #

Given a value and its absolute, try to learn something in either direction.

absR :: Num x => (x, x) -> (x, x) Source #

Given a value and its absolute, try to learn something in either direction.

Instances
(Eq x, Num x) => AbsR (Defined x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Abs

Methods

absR :: (Defined x, Defined x) -> (Defined x, Defined x) Source #

(Bounded x, Enum x, Eq x, Hashable x, Num x) => AbsR (Intersect x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Abs

Methods

absR :: (Intersect x, Intersect x) -> (Intersect x, Intersect x) Source #

class Merge x => BooleanR (x :: Type) where Source #

Rather than the not, and, and or functions we know and love, the BooleanR class presents relationships that are analogous to these. The main difference is that relationships are not one-way. For example, if I tell you that the output of x && y is True, you can tell me what the inputs are, even if your computer can't. The implementations of BooleanR should be such that all directions of inference are considered.

Methods

falseR :: x Source #

An overloaded False value.

trueR :: x Source #

An overloaded True value.

notR :: (x, x) -> (x, x) Source #

A relationship between a boolean value and its opposite.

andR :: (x, x, x) -> (x, x, x) Source #

A relationship between two boolean values and their conjunction.

orR :: (x, x, x) -> (x, x, x) Source #

A relationship between two boolean values and their disjunction.

class (BooleanR b, Merge x) => EqR (x :: Type) (b :: Type) | x -> b where Source #

Equality between two variables as a relationship between them and their result. The hope here is that, if we learn the output before the inputs, we can often "work backwards" to learn something about them. If we know the result is exactly true, for example, we can effectively then unify the two input cells, as we know that their values will always be the same.

Methods

eqR :: (x, x, b) -> (x, x, b) Source #

Instances
Eq x => EqR (Defined x) (Defined Bool) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Eq

(Bounded x, Enum x, Eq x, Hashable x) => EqR (Intersect x) (Intersect Bool) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Eq

neR :: EqR x b => (x, x, b) -> (x, x, b) Source #

A relationship between two variables and the result of a not-equals comparison between them.

class Zipping f c => FlatMapping (f :: Type -> Type) (c :: Type -> Constraint) | f -> c where Source #

Some types, such as Intersect, contain multiple "candidate values". This function allows us to take each candidate, apply a function, and then union all the results. Perhaps fanOut would have been a better name for this function, but we use `(>>=)` to lend an intuition when we lift this into Prop via `(Data.Propagator..>>=)`.

There's not normally much reverse-flow information here, sadly, as it typically requires us to have a way to generate an "empty candidate" a la mempty. It's quite hard to articulate this in a succinct way, but try implementing the reverse flow for Defined or Intersect, and see what happens.

Methods

flatMapR :: (c x, c y) => ((x, f y) -> (x, f y)) -> (f x, f y) -> (f x, f y) Source #

Instances
FlatMapping Defined Eq Source # 
Instance details

Defined in Data.JoinSemilattice.Class.FlatMapping

Methods

flatMapR :: (Eq x, Eq y) => ((x, Defined y) -> (x, Defined y)) -> (Defined x, Defined y) -> (Defined x, Defined y) Source #

FlatMapping Intersect Intersectable Source # 
Instance details

Defined in Data.JoinSemilattice.Class.FlatMapping

Methods

flatMapR :: (Intersectable x, Intersectable y) => ((x, Intersect y) -> (x, Intersect y)) -> (Intersect x, Intersect y) -> (Intersect x, Intersect y) Source #

class SumR x => FractionalR (x :: Type) where Source #

Reversible (fractional or floating-point) multiplication as a three-value relationship between two values and their product.

Minimal complete definition

Nothing

Methods

multiplyR :: (x, x, x) -> (x, x, x) Source #

multiplyR :: Fractional x => (x, x, x) -> (x, x, x) Source #

Instances
(Eq x, Fractional x) => FractionalR (Defined x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Fractional

Methods

multiplyR :: (Defined x, Defined x, Defined x) -> (Defined x, Defined x, Defined x) Source #

(Bounded x, Enum x, Eq x, Fractional x, Hashable x) => FractionalR (Intersect x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Fractional

class SumR x => IntegralR (x :: Type) where Source #

A four-way divMod relationship between two values, the result of integral division, and the result of the first modulo the second.

Methods

divModR :: (x, x, x, x) -> (x, x, x, x) Source #

Instances
(Eq x, Integral x) => IntegralR (Defined x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Integral

Methods

divModR :: (Defined x, Defined x, Defined x, Defined x) -> (Defined x, Defined x, Defined x, Defined x) Source #

(Bounded x, Enum x, Eq x, Hashable x, Integral x) => IntegralR (Intersect x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Integral

class (forall x. c x => Merge (f x)) => Mapping (f :: Type -> Type) (c :: Type -> Constraint) | f -> c where Source #

Lift a relationship between two values over some type constructor. Typically, this type constructor will be the parameter type.

Minimal complete definition

Nothing

Methods

mapR :: (c x, c y) => ((x, y) -> (x, y)) -> (f x, f y) -> (f x, f y) Source #

mapR :: Applicative f => ((x, y) -> (x, y)) -> (f x, f y) -> (f x, f y) Source #

Instances
Mapping Defined Eq Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Mapping

Methods

mapR :: (Eq x, Eq y) => ((x, y) -> (x, y)) -> (Defined x, Defined y) -> (Defined x, Defined y) Source #

Mapping Intersect Intersectable Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Mapping

Methods

mapR :: (Intersectable x, Intersectable y) => ((x, y) -> (x, y)) -> (Intersect x, Intersect y) -> (Intersect x, Intersect y) Source #

class EqR x b => OrdR (x :: Type) (b :: Type) | x -> b where Source #

Comparison relationships between two values and their comparison result.

Methods

lteR :: (x, x, b) -> (x, x, b) Source #

A relationship between two values and whether the left is less than or equal to the right.

Instances
Ord x => OrdR (Defined x) (Defined Bool) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Ord

(Bounded x, Enum x, Hashable x, Ord x) => OrdR (Intersect x) (Intersect Bool) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Ord

ltR :: OrdR x b => (x, x, b) -> (x, x, b) Source #

Comparison between two values and their '(<)' result.

gtR :: OrdR x b => (x, x, b) -> (x, x, b) Source #

Comparison between two values and their '(>)' result.

gteR :: OrdR x b => (x, x, b) -> (x, x, b) Source #

Comparison between two values and their '(>=)' result.

class Merge x => SumR (x :: Type) where Source #

A relationship between two values and their sum.

Minimal complete definition

Nothing

Methods

addR :: (x, x, x) -> (x, x, x) Source #

addR :: Num x => (x, x, x) -> (x, x, x) Source #

Instances
(Eq x, Num x) => SumR (Defined x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Sum

Methods

addR :: (Defined x, Defined x, Defined x) -> (Defined x, Defined x, Defined x) Source #

(Bounded x, Enum x, Eq x, Hashable x, Num x) => SumR (Intersect x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Sum

negateR :: (Num x, SumR x) => (x, x) -> (x, x) Source #

A relationship between a value and its negation.

subR :: SumR x => (x, x, x) -> (x, x, x) Source #

A relationship between two values and their difference.

class Mapping f c => Zipping (f :: Type -> Type) (c :: Type -> Constraint) | f -> c where Source #

Lift a relationship between three values over some f (usually a parameter type).

Minimal complete definition

Nothing

Methods

zipWithR :: (c x, c y, c z) => ((x, y, z) -> (x, y, z)) -> (f x, f y, f z) -> (f x, f y, f z) Source #

zipWithR :: Applicative f => ((x, y, z) -> (x, y, z)) -> (f x, f y, f z) -> (f x, f y, f z) Source #

Instances
Zipping Defined Eq Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Zipping

Methods

zipWithR :: (Eq x, Eq y, Eq z) => ((x, y, z) -> (x, y, z)) -> (Defined x, Defined y, Defined z) -> (Defined x, Defined y, Defined z) Source #

Zipping Intersect Intersectable Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Zipping

Methods

zipWithR :: (Intersectable x, Intersectable y, Intersectable z) => ((x, y, z) -> (x, y, z)) -> (Intersect x, Intersect y, Intersect z) -> (Intersect x, Intersect y, Intersect z) Source #

class Monoid x => Merge (x :: Type) where Source #

Join semilattice '(<>)' specialised for propagator network needs. Allows types to implement the notion of "knowledge combination".

Methods

(<<-) :: x -> x -> Result x Source #

Merge the news (right) into the current value (left), returning an instruction on how to update the network.

Instances
Eq content => Merge (Defined content) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Merge

Methods

(<<-) :: Defined content -> Defined content -> Result (Defined content) Source #

(Bounded x, Enum x, Eq x, Hashable x) => Merge (Intersect x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Merge

Methods

(<<-) :: Intersect x -> Intersect x -> Result (Intersect x) Source #

data Result (x :: Type) Source #

The result of merging some news into a cell's current knowledge.

Constructors

Unchanged

We've learnt nothing; no updates elsewhere are needed.

Changed x

We've learnt something; fire the propagators!

Failure

We've hit a failure state; discard the computation.

Instances
Functor Result Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Merge

Methods

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

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

Eq x => Eq (Result x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Merge

Methods

(==) :: Result x -> Result x -> Bool #

(/=) :: Result x -> Result x -> Bool #

Ord x => Ord (Result x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Merge

Methods

compare :: Result x -> Result x -> Ordering #

(<) :: Result x -> Result x -> Bool #

(<=) :: Result x -> Result x -> Bool #

(>) :: Result x -> Result x -> Bool #

(>=) :: Result x -> Result x -> Bool #

max :: Result x -> Result x -> Result x #

min :: Result x -> Result x -> Result x #

Show x => Show (Result x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Merge

Methods

showsPrec :: Int -> Result x -> ShowS #

show :: Result x -> String #

showList :: [Result x] -> ShowS #

Semigroup x => Semigroup (Result x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Merge

Methods

(<>) :: Result x -> Result x -> Result x #

sconcat :: NonEmpty (Result x) -> Result x #

stimes :: Integral b => b -> Result x -> Result x #

Semigroup x => Monoid (Result x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Merge

Methods

mempty :: Result x #

mappend :: Result x -> Result x -> Result x #

mconcat :: [Result x] -> Result x #

data Defined (x :: Type) Source #

Defines simple "levels of knowledge" about a value.

Constructors

Unknown

Nothing has told me what this value is.

Exactly x

Everyone who has told me this value agrees.

Conflict

Two sources disagree on what this value should be.

Instances
Functor Defined Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

Methods

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

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

Applicative Defined Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

Methods

pure :: a -> Defined a #

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

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

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

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

Mapping Defined Eq Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Mapping

Methods

mapR :: (Eq x, Eq y) => ((x, y) -> (x, y)) -> (Defined x, Defined y) -> (Defined x, Defined y) Source #

Zipping Defined Eq Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Zipping

Methods

zipWithR :: (Eq x, Eq y, Eq z) => ((x, y, z) -> (x, y, z)) -> (Defined x, Defined y, Defined z) -> (Defined x, Defined y, Defined z) Source #

FlatMapping Defined Eq Source # 
Instance details

Defined in Data.JoinSemilattice.Class.FlatMapping

Methods

flatMapR :: (Eq x, Eq y) => ((x, Defined y) -> (x, Defined y)) -> (Defined x, Defined y) -> (Defined x, Defined y) Source #

Bounded x => Bounded (Defined x) Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

Enum content => Enum (Defined content) Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

Methods

succ :: Defined content -> Defined content #

pred :: Defined content -> Defined content #

toEnum :: Int -> Defined content #

fromEnum :: Defined content -> Int #

enumFrom :: Defined content -> [Defined content] #

enumFromThen :: Defined content -> Defined content -> [Defined content] #

enumFromTo :: Defined content -> Defined content -> [Defined content] #

enumFromThenTo :: Defined content -> Defined content -> Defined content -> [Defined content] #

Eq x => Eq (Defined x) Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

Methods

(==) :: Defined x -> Defined x -> Bool #

(/=) :: Defined x -> Defined x -> Bool #

Fractional x => Fractional (Defined x) Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

Methods

(/) :: Defined x -> Defined x -> Defined x #

recip :: Defined x -> Defined x #

fromRational :: Rational -> Defined x #

Integral content => Integral (Defined content) Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

Methods

quot :: Defined content -> Defined content -> Defined content #

rem :: Defined content -> Defined content -> Defined content #

div :: Defined content -> Defined content -> Defined content #

mod :: Defined content -> Defined content -> Defined content #

quotRem :: Defined content -> Defined content -> (Defined content, Defined content) #

divMod :: Defined content -> Defined content -> (Defined content, Defined content) #

toInteger :: Defined content -> Integer #

Num x => Num (Defined x) Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

Methods

(+) :: Defined x -> Defined x -> Defined x #

(-) :: Defined x -> Defined x -> Defined x #

(*) :: Defined x -> Defined x -> Defined x #

negate :: Defined x -> Defined x #

abs :: Defined x -> Defined x #

signum :: Defined x -> Defined x #

fromInteger :: Integer -> Defined x #

Ord x => Ord (Defined x) Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

Methods

compare :: Defined x -> Defined x -> Ordering #

(<) :: Defined x -> Defined x -> Bool #

(<=) :: Defined x -> Defined x -> Bool #

(>) :: Defined x -> Defined x -> Bool #

(>=) :: Defined x -> Defined x -> Bool #

max :: Defined x -> Defined x -> Defined x #

min :: Defined x -> Defined x -> Defined x #

Real content => Real (Defined content) Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

Methods

toRational :: Defined content -> Rational #

Show x => Show (Defined x) Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

Methods

showsPrec :: Int -> Defined x -> ShowS #

show :: Defined x -> String #

showList :: [Defined x] -> ShowS #

Generic (Defined x) Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

Associated Types

type Rep (Defined x) :: Type -> Type #

Methods

from :: Defined x -> Rep (Defined x) x0 #

to :: Rep (Defined x) x0 -> Defined x #

Eq content => Semigroup (Defined content) Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

Methods

(<>) :: Defined content -> Defined content -> Defined content #

sconcat :: NonEmpty (Defined content) -> Defined content #

stimes :: Integral b => b -> Defined content -> Defined content #

Eq content => Monoid (Defined content) Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

Methods

mempty :: Defined content #

mappend :: Defined content -> Defined content -> Defined content #

mconcat :: [Defined content] -> Defined content #

Hashable x => Hashable (Defined x) Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

Methods

hashWithSalt :: Int -> Defined x -> Int #

hash :: Defined x -> Int #

Input (Defined content) Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

Associated Types

type Raw (Defined content) :: Type Source #

Methods

from :: Applicative m => Int -> [Raw (Defined content)] -> Config m (Defined content) Source #

Eq content => Merge (Defined content) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Merge

Methods

(<<-) :: Defined content -> Defined content -> Result (Defined content) Source #

(Eq x, Num x) => SumR (Defined x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Sum

Methods

addR :: (Defined x, Defined x, Defined x) -> (Defined x, Defined x, Defined x) Source #

(Eq x, Integral x) => IntegralR (Defined x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Integral

Methods

divModR :: (Defined x, Defined x, Defined x, Defined x) -> (Defined x, Defined x, Defined x, Defined x) Source #

(Eq x, Fractional x) => FractionalR (Defined x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Fractional

Methods

multiplyR :: (Defined x, Defined x, Defined x) -> (Defined x, Defined x, Defined x) Source #

BooleanR (Defined Bool) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Boolean

(Eq x, Num x) => AbsR (Defined x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Abs

Methods

absR :: (Defined x, Defined x) -> (Defined x, Defined x) Source #

Eq x => EqR (Defined x) (Defined Bool) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Eq

Ord x => OrdR (Defined x) (Defined Bool) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Ord

type Rep (Defined x) Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

type Rep (Defined x) = D1 (MetaData "Defined" "Data.JoinSemilattice.Defined" "holmes-0.1.0.1-CghJRrKr1HAJcmez9ZnNsQ" False) (C1 (MetaCons "Unknown" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Exactly" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 x)) :+: C1 (MetaCons "Conflict" PrefixI False) (U1 :: Type -> Type)))
type Raw (Defined content) Source # 
Instance details

Defined in Data.JoinSemilattice.Defined

type Raw (Defined content) = content

newtype Intersect (x :: Type) Source #

A set type with intersection as the '(<>)' operation.

Constructors

Intersect 

Fields

Instances
Foldable Intersect Source # 
Instance details

Defined in Data.JoinSemilattice.Intersect

Methods

fold :: Monoid m => Intersect m -> m #

foldMap :: Monoid m => (a -> m) -> Intersect a -> m #

foldr :: (a -> b -> b) -> b -> Intersect a -> b #

foldr' :: (a -> b -> b) -> b -> Intersect a -> b #

foldl :: (b -> a -> b) -> b -> Intersect a -> b #

foldl' :: (b -> a -> b) -> b -> Intersect a -> b #

foldr1 :: (a -> a -> a) -> Intersect a -> a #

foldl1 :: (a -> a -> a) -> Intersect a -> a #

toList :: Intersect a -> [a] #

null :: Intersect a -> Bool #

length :: Intersect a -> Int #

elem :: Eq a => a -> Intersect a -> Bool #

maximum :: Ord a => Intersect a -> a #

minimum :: Ord a => Intersect a -> a #

sum :: Num a => Intersect a -> a #

product :: Num a => Intersect a -> a #

Mapping Intersect Intersectable Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Mapping

Methods

mapR :: (Intersectable x, Intersectable y) => ((x, y) -> (x, y)) -> (Intersect x, Intersect y) -> (Intersect x, Intersect y) Source #

Zipping Intersect Intersectable Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Zipping

Methods

zipWithR :: (Intersectable x, Intersectable y, Intersectable z) => ((x, y, z) -> (x, y, z)) -> (Intersect x, Intersect y, Intersect z) -> (Intersect x, Intersect y, Intersect z) Source #

FlatMapping Intersect Intersectable Source # 
Instance details

Defined in Data.JoinSemilattice.Class.FlatMapping

Methods

flatMapR :: (Intersectable x, Intersectable y) => ((x, Intersect y) -> (x, Intersect y)) -> (Intersect x, Intersect y) -> (Intersect x, Intersect y) Source #

Eq x => Eq (Intersect x) Source # 
Instance details

Defined in Data.JoinSemilattice.Intersect

Methods

(==) :: Intersect x -> Intersect x -> Bool #

(/=) :: Intersect x -> Intersect x -> Bool #

(Intersectable x, Fractional x) => Fractional (Intersect x) Source # 
Instance details

Defined in Data.JoinSemilattice.Intersect

(Intersectable content, Num content) => Num (Intersect content) Source # 
Instance details

Defined in Data.JoinSemilattice.Intersect

Methods

(+) :: Intersect content -> Intersect content -> Intersect content #

(-) :: Intersect content -> Intersect content -> Intersect content #

(*) :: Intersect content -> Intersect content -> Intersect content #

negate :: Intersect content -> Intersect content #

abs :: Intersect content -> Intersect content #

signum :: Intersect content -> Intersect content #

fromInteger :: Integer -> Intersect content #

Ord x => Ord (Intersect x) Source # 
Instance details

Defined in Data.JoinSemilattice.Intersect

Show x => Show (Intersect x) Source # 
Instance details

Defined in Data.JoinSemilattice.Intersect

(Eq content, Hashable content) => Semigroup (Intersect content) Source # 
Instance details

Defined in Data.JoinSemilattice.Intersect

Methods

(<>) :: Intersect content -> Intersect content -> Intersect content #

sconcat :: NonEmpty (Intersect content) -> Intersect content #

stimes :: Integral b => b -> Intersect content -> Intersect content #

Intersectable content => Monoid (Intersect content) Source # 
Instance details

Defined in Data.JoinSemilattice.Intersect

Methods

mempty :: Intersect content #

mappend :: Intersect content -> Intersect content -> Intersect content #

mconcat :: [Intersect content] -> Intersect content #

Hashable x => Hashable (Intersect x) Source # 
Instance details

Defined in Data.JoinSemilattice.Intersect

Methods

hashWithSalt :: Int -> Intersect x -> Int #

hash :: Intersect x -> Int #

Intersectable x => Input (Intersect x) Source # 
Instance details

Defined in Data.JoinSemilattice.Intersect

Associated Types

type Raw (Intersect x) :: Type Source #

Methods

from :: Applicative m => Int -> [Raw (Intersect x)] -> Config m (Intersect x) Source #

(Bounded x, Enum x, Eq x, Hashable x) => Merge (Intersect x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Merge

Methods

(<<-) :: Intersect x -> Intersect x -> Result (Intersect x) Source #

(Bounded x, Enum x, Eq x, Hashable x, Num x) => SumR (Intersect x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Sum

(Bounded x, Enum x, Eq x, Hashable x, Integral x) => IntegralR (Intersect x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Integral

(Bounded x, Enum x, Eq x, Fractional x, Hashable x) => FractionalR (Intersect x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Fractional

BooleanR (Intersect Bool) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Boolean

(Bounded x, Enum x, Eq x, Hashable x, Num x) => AbsR (Intersect x) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Abs

Methods

absR :: (Intersect x, Intersect x) -> (Intersect x, Intersect x) Source #

(Bounded x, Enum x, Eq x, Hashable x) => EqR (Intersect x) (Intersect Bool) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Eq

(Bounded x, Enum x, Hashable x, Ord x) => OrdR (Intersect x) (Intersect Bool) Source # 
Instance details

Defined in Data.JoinSemilattice.Class.Ord

type Raw (Intersect x) Source # 
Instance details

Defined in Data.JoinSemilattice.Intersect

type Raw (Intersect x) = x

using :: (Applicative m, Intersectable x) => [Intersect x] -> Config m (Intersect x) Source #

Produce a Config with the given initial value, where the refine function just tries each remaining candidate as a singleton.

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.

Instances
(AbsR x, Fractional x, FractionalR x, Num x, MonadCell m) => Fractional (Prop m x) Source # 
Instance details

Defined in Data.Propagator

Methods

(/) :: Prop m x -> Prop m x -> Prop m x #

recip :: Prop m x -> Prop m x #

fromRational :: Rational -> Prop m x #

(AbsR x, SumR x, Num x, MonadCell m) => Num (Prop m x) Source # 
Instance details

Defined in Data.Propagator

Methods

(+) :: Prop m x -> Prop m x -> Prop m x #

(-) :: Prop m x -> Prop m x -> Prop m x #

(*) :: Prop m x -> Prop m x -> Prop m x #

negate :: Prop m x -> Prop m x #

abs :: Prop m x -> Prop m x #

signum :: Prop m x -> Prop m x #

fromInteger :: Integer -> Prop m x #

(.$) :: (Mapping f c, c x, c y) => (x -> y) -> Prop m (f x) -> Prop m (f y) Source #

Lift a regular function over a propagator network and its parameter type. Unlike over, this function abstracts away the specific behaviour of the parameter type (such as Defined).

(.>>=) :: (FlatMapping f c, c x, c y) => Prop m (f x) -> (x -> f y) -> Prop m (f y) Source #

Produce a network in which the raw values of a given network are used to produce new parameter types. See the "wave function collapse" demo for an example usage.

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.

(.&&) :: 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".

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".

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.

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.

(.*) :: (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.

(.+) :: (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.

(.<) :: (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".

(.>) :: (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".

(.==) :: (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?

(.%.) :: (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.

(.*.) :: (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.

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.

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.

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.