Copyright | (c) Tom Harding 2020 |
---|---|
License | MIT |
Safe Haskell | None |
Language | Haskell2010 |
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
- data Holmes (x :: Type)
- class Monad m => MonadCell (m :: Type -> Type)
- unsafeRead :: Cell Holmes x -> Holmes x
- backward :: (Typeable x, Merge x, Merge y) => (forall m. MonadCell m => Prop m x -> Prop m y) -> y -> IO (Maybe x)
- forward :: (Typeable x, Merge x, Merge y) => (forall m. MonadCell m => Prop m x -> Prop m y) -> x -> IO (Maybe y)
- runAll :: Holmes x -> IO [x]
- runOne :: Holmes x -> IO (Maybe x)
- satisfying :: (EqR x b, Typeable x) => Config Holmes x -> (forall m. MonadCell m => [Prop m x] -> Prop m b) -> IO (Maybe [x])
- shuffle :: Config Holmes x -> Config Holmes x
- whenever :: (EqR x b, Typeable x) => Config Holmes x -> (forall m. MonadCell m => [Prop m x] -> Prop m b) -> IO [[x]]
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.
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.
Instances
MonadCell Holmes Source # | |
Defined in Control.Monad.Holmes | |
MonadCell (Watson h) Source # | |
Defined in Control.Monad.Watson |
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.
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 :: (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
, the first configuration will be one hundred from
[1 .. 10]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!