astar-monad-0.3.0.0

Copyright(c) Chris Penner 2019
LicenseBSD3
Safe HaskellSafe
LanguageHaskell2010

Control.Monad.AStar

Contents

Description

See the README for usage info and examples.

Synopsis

Types

type AStar s c r a = AStarT s c r Identity a Source #

Non-transformer version of AStarT

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 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 #

(Ord c, Semigroup c, Monad m) => MonadState s (AStarT s c r m) Source # 
Instance details

Defined in Control.Monad.AStar

Methods

get :: AStarT s c r m s #

put :: s -> AStarT s c r m () #

state :: (s -> (a, s)) -> AStarT s c r m a #

MonadTrans (AStarT s c r) Source # 
Instance details

Defined in Control.Monad.AStar

Methods

lift :: Monad m => m a -> AStarT s c r m a #

(Monad m, Semigroup c, Ord c) => Monad (AStarT s c r m) Source # 
Instance details

Defined in Control.Monad.AStar

Methods

(>>=) :: AStarT s c r m a -> (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 b #

return :: a -> AStarT s c r m a #

fail :: String -> AStarT s c r m a #

Functor (AStarT s c r m) Source # 
Instance details

Defined in Control.Monad.AStar

Methods

fmap :: (a -> b) -> AStarT s c r m a -> AStarT s c r m b #

(<$) :: a -> AStarT s c r m b -> AStarT s c r m a #

(Ord c, Semigroup c, Monad m) => MonadFail (AStarT s c r m) Source # 
Instance details

Defined in Control.Monad.AStar

Methods

fail :: String -> AStarT s c r m a #

(Monad m, Semigroup c, Ord c) => Applicative (AStarT s c r m) Source # 
Instance details

Defined in Control.Monad.AStar

Methods

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 # 
Instance details

Defined in Control.Monad.AStar

Methods

liftIO :: IO a -> AStarT s c r m a #

(Ord c, Monad m, Semigroup c) => Alternative (AStarT s c r m) Source # 
Instance details

Defined in Control.Monad.AStar

Methods

empty :: AStarT s c r m a #

(<|>) :: AStarT s c r m a -> AStarT s c r m a -> AStarT s c r m a #

some :: AStarT s c r m a -> AStarT s c r m [a] #

many :: AStarT s c r m a -> AStarT s c r m [a] #

(Ord c, Semigroup c, Monad m) => MonadPlus (AStarT s c r m) Source # 
Instance details

Defined in Control.Monad.AStar

Methods

mzero :: AStarT s c r m a #

mplus :: AStarT s c r m a -> AStarT s c r m a -> AStarT s c r m a #

data BranchState s c Source #

Constructors

BranchState 
Instances
(Eq s, Eq c) => Eq (BranchState s c) Source # 
Instance details

Defined in Control.Monad.AStar

Methods

(==) :: BranchState s c -> BranchState s c -> Bool #

(/=) :: BranchState s c -> BranchState s c -> Bool #

(Show s, Show c) => Show (BranchState s c) Source # 
Instance details

Defined in Control.Monad.AStar

Methods

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

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

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.

runAStarT :: (Monad m, Monoid c) => AStarT s c r m a -> s -> m (Maybe (r, s)) Source #

Run an A* computation effect returning the solution and branch state if one was found.

evalAStar :: Monoid c => AStar s c r a -> s -> Maybe r Source #

evalAStarT :: (Monad m, Monoid c) => AStarT s c r m a -> s -> m (Maybe r) Source #

execAStar :: Monoid c => AStar s c r a -> s -> Maybe s Source #

execAStarT :: (Monad m, Monoid c) => AStarT s c r m a -> s -> m (Maybe s) Source #