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

Copyright(c) Tom Harding 2020
LicenseMIT
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Holmes

Description

Holmes is a type for solving constraint problems. These computations are executed with IO, which allows for extra features such as the ability to shuffle the input configuration.

If this isn't a feature you require, you may prefer to use the Control.Monad.Watson interface, which offers a pure version of the API thanks to its use of ST. The internal code is shared between the two, so results between the two are consistent.

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 #

MonadFail Holmes Source # 
Instance details

Defined in Control.Monad.Holmes

Methods

fail :: String -> 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 #

PrimMonad m => MonadCell (MoriarT m) Source # 
Instance details

Defined in Control.Monad.MoriarT

Associated Types

data Cell (MoriarT m) a :: Type Source #

Methods

discard :: MoriarT m x Source #

fill :: x -> MoriarT m (Cell (MoriarT m) x) Source #

watch :: Cell (MoriarT m) x -> (x -> MoriarT m ()) -> MoriarT m () Source #

with :: Cell (MoriarT m) x -> (x -> MoriarT m ()) -> MoriarT m () Source #

write :: Merge x => Cell (MoriarT m) x -> x -> MoriarT m () 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 #

backward :: (Typeable x, Merge x, Merge y) => (forall m. MonadCell m => Prop m x -> Prop m y) -> y -> IO (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.

forward :: (Typeable x, Merge x, Merge y) => (forall m. MonadCell m => Prop m x -> Prop m y) -> x -> IO (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.

runAll :: Holmes x -> IO [x] Source #

Interpret a Holmes program into IO, returning a list of all successful branches' outputs. It's unlikely that you want to call this directly, though; typically, satisfying or whenever are more likely the things you want.

runOne :: Holmes x -> IO (Maybe x) Source #

Interpret a Holmes program into IO, returning the first successful branch's result if any branch succeeds. It's unlikely that you want to call this directly, though; typically, satisfying or whenever are more likely the things you want.

satisfying :: (EqC f x, EqR f, Typeable x) => Config Holmes (f x) -> (forall m. MonadCell m => [Prop m (f x)] -> Prop m (f Bool)) -> IO (Maybe [f 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.

unsafeRead :: Cell Holmes x -> Holmes x Source #

Unsafely read from a cell. This operation is unsafe because it doesn't factor this cell into the provenance of any subsequent writes. If this value ends up causing a contradiction, we may end up removing branches of the search tree that are totally valid! This operation is safe as long as it is the very last thing you do in a computation, and its value is never used to influence any writes in any way.

whenever :: (EqC f x, EqR f, Typeable x) => Config Holmes (f x) -> (forall m. MonadCell m => [Prop m (f x)] -> Prop m (f Bool)) -> IO [[f 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!