Copyright | (c) Chris Penner 2019 |
---|---|
License | BSD3 |
Safe Haskell | Safe |
Language | Haskell2010 |
See the README for usage info and examples.
Synopsis
- type AStar s c r a = AStarT s c r Identity a
- data AStarT s c r m a
- data BranchState s c = BranchState {
- branchState :: s
- cumulativeCost :: c
- estimateTillDone :: c
- class (MonadPlus m, Monoid c) => MonadAStar c r m | m -> r, m -> c where
- branch :: MonadAStar c r m => m a -> m a -> m a
- failure :: MonadAStar c r m => m a
- runAStar :: Monoid c => AStar s c r a -> s -> Maybe (r, s)
- runAStarT :: (Monad m, Monoid c) => AStarT s c r m a -> s -> m (Maybe (r, s))
- evalAStar :: Monoid c => AStar s c r a -> s -> Maybe r
- evalAStarT :: (Monad m, Monoid c) => AStarT s c r m a -> s -> m (Maybe r)
- execAStar :: Monoid c => AStar s c r a -> s -> Maybe s
- execAStarT :: (Monad m, Monoid c) => AStarT s c r m a -> s -> m (Maybe s)
Types
data AStarT s c r m a Source #
The AStar
search monad transformer
Lots of type variables here:
s
: State; keep anything you want in here, it will stay coherent across
branch switches.
c
: Cost measure: The type you'll use for both your heuristic estimate and for your
accumulated total cost.
Usually requires Ord
(for comparing branch costs) and Monoid
(for appending and
instantiating cumulative costs).
r
: Result type, this is often redundant to State but is provided for convenience.
This is the type you pass to done
when you've found a solution.
m
: An arbitrary monad which will be threaded through.
Be wary that effects will be run in seemingly non-deterministic ordering as we switch chaotically between 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 |
(Ord c, Semigroup c, Monad m) => MonadState s (AStarT s c r m) Source # | |
MonadTrans (AStarT s c r) Source # | |
Defined in Control.Monad.AStar | |
(Monad m, Semigroup c, Ord c) => Monad (AStarT s c r m) Source # | |
Functor (AStarT s c r m) Source # | |
(Ord c, Semigroup c, Monad m) => MonadFail (AStarT s c r m) Source # | |
Defined in Control.Monad.AStar | |
(Monad m, Semigroup c, Ord c) => Applicative (AStarT s c r m) Source # | |
Defined in Control.Monad.AStar pure :: a -> AStarT s c r m a # (<*>) :: AStarT s c r m (a -> b) -> AStarT s c r m a -> AStarT s c r m b # liftA2 :: (a -> b -> c0) -> AStarT s c r m a -> AStarT s c r m b -> AStarT s c r m c0 # (*>) :: AStarT s c r m a -> AStarT s c r m b -> AStarT s c r m b # (<*) :: AStarT s c r m a -> AStarT s c r m b -> AStarT s c r m a # | |
(MonadIO m, Semigroup c, Ord c) => MonadIO (AStarT s c r m) Source # | |
Defined in Control.Monad.AStar | |
(Ord c, Monad m, Semigroup c) => Alternative (AStarT s c r m) Source # | |
(Ord c, Semigroup c, Monad m) => MonadPlus (AStarT s c r m) Source # | |
data BranchState s c Source #
BranchState | |
|
Instances
(Eq s, Eq c) => Eq (BranchState s c) Source # | |
Defined in Control.Monad.AStar (==) :: BranchState s c -> BranchState s c -> Bool # (/=) :: BranchState s c -> BranchState s c -> Bool # | |
(Show s, Show c) => Show (BranchState s c) Source # | |
Defined in Control.Monad.AStar showsPrec :: Int -> BranchState s c -> ShowS # show :: BranchState s c -> String # showList :: [BranchState s c] -> ShowS # |
Methods
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
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.
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 |
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
Executing Search
runAStar :: Monoid c => AStar s c r a -> s -> Maybe (r, s) Source #
Run a pure A* computation returning the solution and branch state if one was found.