astar-monad-0.3.0.0

Safe HaskellSafe
LanguageHaskell2010

Control.Monad.AStar.Class

Synopsis

Documentation

class (MonadPlus m, Monoid c) => MonadAStar c r m | m -> r, m -> c where Source #

A class which represents the ability to do A* search.

The laws aren't completely pinned down yet, but these should probably hold:

It should short-circuit on 'done'
done a >> mx == done a
done a <|> mx == done a

It should fail a branch using `empty`.
empty >> mx == empty
empty <|> mx == mx

It should branch respecting costs using `<|>` from its 'Alternative' instance.
(updateCost 2 >> mx) <|> (updateCost 1 >> my) == mx <|> my

Methods

spend :: c -> m () Source #

ADD to your current branch's CUMULATIVE cost. May cause a branch switch.

estimate :: c -> m () Source #

SET the current branch's BEST-CASE-COST cost. May cause a branch switch.

done :: r -> m a Source #

Return a solution and short-circuit any remaining branches.

Instances
(Ord c, Monoid c, Monad m) => MonadAStar c r (AStarT s c r m) Source #

Run a pure A* search but short-circuit when the lowest cost fails a predicate.

This is useful for detecting if your search is diverging, or is likely to fail. tryWhile :: Monoid c => (s -> c -> Bool) -> AStar s c r a -> s -> (Maybe (r, s)) tryWhile p m s = runIdentity $ tryWhileT p m s

Effectful version of tryWhile tryWhileT :: (Monoid c, Monad m) => (s -> c -> Bool) -> AStarT s c r m a -> s -> m (Maybe (r, s)) tryWhileT p m s = fmap (second branchState) $ tryWhileT' p m (BranchState s mempty mempty)

Instance details

Defined in Control.Monad.AStar

Methods

spend :: c -> AStarT s c r m () Source #

estimate :: c -> AStarT s c r m () Source #

done :: r -> AStarT s c r m a Source #

branch :: MonadAStar c r m => m a -> m a -> m a Source #

Branch the search.

branch == (<|>)

failure :: MonadAStar c r m => m a Source #

Fail the current branch.

branch == empty