monad-dijkstra-0.1.1.0: Monad transformer for weighted graph searches using Dijkstra's or A* algorithm

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Search

Contents

Description

The Search monad and SearchT monad transformer allow computations to be associated with costs and cost estimates, and explore possible solutions in order of overall cost. The solution space is explored using the A* algorithm, or Dijkstra's if estimates are omitted. The order of exploring computations with equal cost is not defined.

Costs must be monotonic (i.e. positive) and underestimated. If the cost of a computation is overestimated or a negative cost is applied, sub-optimal solutions may be produced first.

Note that while runSearchT will produce a lazy list of results and the computation space is only explored as far as the list is forced, using runSearchT with e.g. the IO base monad will not. You need to use collapse or abandon to prune the search space within the monadic computation.

Example:

import Control.Monad.Search
import Data.Monoid (Sum(..))

-- All naturals, weighted by the size of the number
naturals :: Search (Sum Integer) Integer
naturals = return 0 <|> (cost' (Sum 1) >> ((+ 1) <$> naturals))
  -- [ 0, 1, 2, 3, 4, 5, ... ]

-- All pairs of naturals
pairs :: Search (Sum Integer) (Integer, Integer)
pairs = (,) <$> naturals <*> naturals
  --    [ (0, 0), (1, 0), (0, 1), (1, 1), (2, 0), ... ]
  -- or [ (0, 0), (0, 1), (1, 0), (2, 0), (1, 1), ... ]
  -- or ...

Synopsis

The Search monad

type Search c = SearchT c Identity Source #

The Search monad

runSearch :: (Ord c, Monoid c) => Search c a -> [(c, a)] Source #

Generate all solutions in order of increasing cost.

runSearchBest :: (Ord c, Monoid c) => Search c a -> Maybe (c, a) Source #

Generate only the best solution.

The SearchT monad transformer

data SearchT c m a Source #

The SearchT monad transformer

Instances

MonadRWS r w s m => MonadRWS r w s (SearchT c m) Source # 
MonadError e m => MonadError e (SearchT c m) Source # 

Methods

throwError :: e -> SearchT c m a #

catchError :: SearchT c m a -> (e -> SearchT c m a) -> SearchT c m a #

MonadReader r m => MonadReader r (SearchT c m) Source # 

Methods

ask :: SearchT c m r #

local :: (r -> r) -> SearchT c m a -> SearchT c m a #

reader :: (r -> a) -> SearchT c m a #

MonadState s m => MonadState s (SearchT c m) Source # 

Methods

get :: SearchT c m s #

put :: s -> SearchT c m () #

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

MonadWriter w m => MonadWriter w (SearchT c m) Source # 

Methods

writer :: (a, w) -> SearchT c m a #

tell :: w -> SearchT c m () #

listen :: SearchT c m a -> SearchT c m (a, w) #

pass :: SearchT c m (a, w -> w) -> SearchT c m a #

(Ord c, Monoid c, Monad m) => MonadSearch c (SearchT c m) Source # 

Methods

cost :: c -> c -> SearchT c m () Source #

junction :: SearchT c m a -> SearchT c m a -> SearchT c m a Source #

abandon :: SearchT c m a Source #

seal :: SearchT c m a -> SearchT c m a Source #

collapse :: SearchT c m () Source #

MonadTrans (SearchT c) Source # 

Methods

lift :: Monad m => m a -> SearchT c m a #

Monad m => Monad (SearchT c m) Source # 

Methods

(>>=) :: SearchT c m a -> (a -> SearchT c m b) -> SearchT c m b #

(>>) :: SearchT c m a -> SearchT c m b -> SearchT c m b #

return :: a -> SearchT c m a #

fail :: String -> SearchT c m a #

Monad m => Functor (SearchT c m) Source # 

Methods

fmap :: (a -> b) -> SearchT c m a -> SearchT c m b #

(<$) :: a -> SearchT c m b -> SearchT c m a #

Monad m => Applicative (SearchT c m) Source # 

Methods

pure :: a -> SearchT c m a #

(<*>) :: SearchT c m (a -> b) -> SearchT c m a -> SearchT c m b #

(*>) :: SearchT c m a -> SearchT c m b -> SearchT c m b #

(<*) :: SearchT c m a -> SearchT c m b -> SearchT c m a #

MonadIO m => MonadIO (SearchT c m) Source # 

Methods

liftIO :: IO a -> SearchT c m a #

(Ord c, Monoid c, Monad m) => Alternative (SearchT c m) Source # 

Methods

empty :: SearchT c m a #

(<|>) :: SearchT c m a -> SearchT c m a -> SearchT c m a #

some :: SearchT c m a -> SearchT c m [a] #

many :: SearchT c m a -> SearchT c m [a] #

(Ord c, Monoid c, Monad m) => MonadPlus (SearchT c m) Source # 

Methods

mzero :: SearchT c m a #

mplus :: SearchT c m a -> SearchT c m a -> SearchT c m a #

MonadCont m => MonadCont (SearchT c m) Source # 

Methods

callCC :: ((a -> SearchT c m b) -> SearchT c m a) -> SearchT c m a #

runSearchT :: (Ord c, Monoid c, Monad m) => SearchT c m a -> m [(c, a)] Source #

Generate all solutions in order of increasing cost.

runSearchBestT :: (Ord c, Monoid c, Monad m) => SearchT c m a -> m (Maybe (c, a)) Source #

Generate only the best solutions.

MonadClass and search monad operations

class (Ord c, Monoid c, Monad m) => MonadSearch c m | m -> c where Source #

Minimal definition is cost, junction, and abandon.

Minimal complete definition

cost, junction, abandon, seal, collapse

Methods

cost :: c -> c -> m () Source #

Mark a computation with a definitive cost and additional estimated cost. Definitive costs are accumulated and reported, while the estimate is reset with every call to cost and will not be included in the final result.

junction :: m a -> m a -> m a Source #

Introduce an alternative computational path to be evaluated concurrently.

abandon :: m a Source #

Abandon a computation.

seal :: m a -> m a Source #

Limit the effect of collapse to alternatives within the sealed scope.

collapse :: m () Source #

Abandon all other computations within the current sealed scope.

Instances

MonadSearch c m => MonadSearch c (ExceptT e m) Source # 

Methods

cost :: c -> c -> ExceptT e m () Source #

junction :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a Source #

abandon :: ExceptT e m a Source #

seal :: ExceptT e m a -> ExceptT e m a Source #

collapse :: ExceptT e m () Source #

MonadSearch c m => MonadSearch c (StateT s m) Source # 

Methods

cost :: c -> c -> StateT s m () Source #

junction :: StateT s m a -> StateT s m a -> StateT s m a Source #

abandon :: StateT s m a Source #

seal :: StateT s m a -> StateT s m a Source #

collapse :: StateT s m () Source #

MonadSearch c m => MonadSearch c (StateT s m) Source # 

Methods

cost :: c -> c -> StateT s m () Source #

junction :: StateT s m a -> StateT s m a -> StateT s m a Source #

abandon :: StateT s m a Source #

seal :: StateT s m a -> StateT s m a Source #

collapse :: StateT s m () Source #

(Monoid w, MonadSearch c m) => MonadSearch c (WriterT w m) Source # 

Methods

cost :: c -> c -> WriterT w m () Source #

junction :: WriterT w m a -> WriterT w m a -> WriterT w m a Source #

abandon :: WriterT w m a Source #

seal :: WriterT w m a -> WriterT w m a Source #

collapse :: WriterT w m () Source #

(Monoid w, MonadSearch c m) => MonadSearch c (WriterT w m) Source # 

Methods

cost :: c -> c -> WriterT w m () Source #

junction :: WriterT w m a -> WriterT w m a -> WriterT w m a Source #

abandon :: WriterT w m a Source #

seal :: WriterT w m a -> WriterT w m a Source #

collapse :: WriterT w m () Source #

(Ord c, Monoid c, Monad m) => MonadSearch c (SearchT c m) Source # 

Methods

cost :: c -> c -> SearchT c m () Source #

junction :: SearchT c m a -> SearchT c m a -> SearchT c m a Source #

abandon :: SearchT c m a Source #

seal :: SearchT c m a -> SearchT c m a Source #

collapse :: SearchT c m () Source #

MonadSearch c m => MonadSearch c (ReaderT * r m) Source # 

Methods

cost :: c -> c -> ReaderT * r m () Source #

junction :: ReaderT * r m a -> ReaderT * r m a -> ReaderT * r m a Source #

abandon :: ReaderT * r m a Source #

seal :: ReaderT * r m a -> ReaderT * r m a Source #

collapse :: ReaderT * r m () Source #

(Monoid w, MonadSearch c m) => MonadSearch c (RWST r w s m) Source # 

Methods

cost :: c -> c -> RWST r w s m () Source #

junction :: RWST r w s m a -> RWST r w s m a -> RWST r w s m a Source #

abandon :: RWST r w s m a Source #

seal :: RWST r w s m a -> RWST r w s m a Source #

collapse :: RWST r w s m () Source #

(Monoid w, MonadSearch c m) => MonadSearch c (RWST r w s m) Source # 

Methods

cost :: c -> c -> RWST r w s m () Source #

junction :: RWST r w s m a -> RWST r w s m a -> RWST r w s m a Source #

abandon :: RWST r w s m a Source #

seal :: RWST r w s m a -> RWST r w s m a Source #

collapse :: RWST r w s m () Source #

cost :: MonadSearch c m => c -> c -> m () Source #

Mark a computation with a definitive cost and additional estimated cost. Definitive costs are accumulated and reported, while the estimate is reset with every call to cost and will not be included in the final result.

cost' :: MonadSearch c m => c -> m () Source #

Mark an operation with a cost.

cost' c = cost c mempty

junction :: MonadSearch c m => m a -> m a -> m a Source #

Introduce an alternative computational path to be evaluated concurrently.

abandon :: MonadSearch c m => m a Source #

Abandon a computation.

seal :: MonadSearch c m => m a -> m a Source #

Limit the effect of collapse to alternatives within the sealed scope.

collapse :: MonadSearch c m => m () Source #

Abandon all other computations within the current sealed scope.

winner :: MonadSearch c m => m a -> m a Source #

Limit a given computation to the first successful return.

winner m = seal (m <* collapse)