Copyright | (c) Tom Harding 2020 |
---|---|
License | MIT |
Safe Haskell | None |
Language | Haskell2010 |
Watson works in a near-identical way to Holmes, but with one distinction: its
base type is ST
rather than IO
, so the API calculates the results with
"observably pure" functions. There are downsides: for example, Watson
can't
perform random restart with operations like shuffle
.
However, this is often an acceptable compromise to avoid IO
entirely!
Synopsis
- data Watson (h :: Type) (x :: Type)
- class Monad m => MonadCell (m :: Type -> Type) where
- backward :: (Typeable x, Merge x, Merge y) => (forall m. MonadCell m => Prop m x -> Prop m y) -> y -> Maybe x
- forward :: (Typeable x, Merge x, Merge y) => (forall m. MonadCell m => Prop m x -> Prop m y) -> x -> Maybe y
- runAll :: (forall h. Watson h x) -> [x]
- runOne :: (forall h. Watson h x) -> Maybe x
- satisfying :: (EqC f x, EqR f, Typeable x) => (forall h. Config (Watson h) (f x)) -> (forall m. MonadCell m => [Prop m (f x)] -> Prop m (f Bool)) -> Maybe [f x]
- unsafeRead :: Cell (Watson h) x -> Watson h x
- whenever :: (EqC f x, EqR f, Typeable x) => (forall h. Config (Watson h) (f x)) -> (forall m. MonadCell m => [Prop m (f x)] -> Prop m (f Bool)) -> [[f x]]
Documentation
data Watson (h :: Type) (x :: Type) Source #
A monad capable of solving constraint problems using ST
as the
evaluation type. Cells are represented using STRef
references,
and provenance is tracked to optimise backtracking search across
multiple branches.
class Monad m => MonadCell (m :: Type -> Type) where 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.
Mark the current computation as failed. For more advanced implementations that utilise backtracking and branching, this is an indication that we should begin a different branch of the search. Otherwise, the computation should simply fail without a result.
fill :: x -> m (Cell m x) Source #
Create a new cell with the given value. Although this value's type has
no constraints, it will be immutable unless it also implements Merge
,
which exists to enforce monotonic updates.
watch :: Cell m x -> (x -> m ()) -> m () Source #
Create a callback that is fired whenever the value in a given cell is updated. Typically, this callback will involve potential writes to other cells based on the current value of the given cell. If such a write occurs, we say that we have propagated information from the first cell to the next.
with :: Cell m x -> (x -> m ()) -> m () Source #
Execute a callback with the current value of a cell. Unlike watch
,
this will only fire once, and subsequent changes to the cell should not
re-trigger this callback. This callback should therefore not be
"registered" on any cell.
write :: Merge x => Cell m x -> x -> m () Source #
Write an update to a cell. This update should be merged into the
current value using the (<<-)
operation,
which should behave the same way as (<>)
for commutative and idempotent
monoids. This therefore preserves the monotonic behaviour: updates can
only refine a value. The result of a write
must be more refined
than the value before, with no exception.
Instances
MonadCell Holmes Source # | |
Defined in Control.Monad.Holmes | |
PrimMonad m => MonadCell (MoriarT m) Source # | |
Defined in Control.Monad.MoriarT 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 # | |
Defined in Control.Monad.Watson |
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.
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.
runAll :: (forall h. Watson h x) -> [x] Source #
Interpret a Watson
program, 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 :: (forall h. Watson h x) -> Maybe x Source #
Interpret a Watson
program, 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) => (forall h. Config (Watson h) (f x)) -> (forall m. MonadCell m => [Prop m (f x)] -> Prop m (f Bool)) -> Maybe [f x] Source #
Given an input configuration, and a predicate on those input variables, return the first configuration that satisfies the predicate.
unsafeRead :: Cell (Watson h) x -> Watson h 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) => (forall h. Config (Watson h) (f x)) -> (forall m. MonadCell m => [Prop m (f x)] -> Prop m (f Bool)) -> [[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!