Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- type Search c = SearchT c Identity
- runSearch :: (Ord c, Monoid c) => Search c a -> [(c, a)]
- runSearchBest :: (Ord c, Monoid c) => Search c a -> Maybe (c, a)
- data SearchT c m a
- runSearchT :: (Ord c, Monoid c, Monad m) => SearchT c m a -> m [(c, a)]
- runSearchBestT :: (Ord c, Monoid c, Monad m) => SearchT c m a -> m (Maybe (c, a))
- class (Ord c, Monoid c, Monad m) => MonadSearch c m | m -> c
- cost :: MonadSearch c m => c -> c -> m ()
- cost' :: MonadSearch c m => c -> m ()
- junction :: MonadSearch c m => m a -> m a -> m a
- abandon :: MonadSearch c m => m a
- seal :: MonadSearch c m => m a -> m a
- collapse :: MonadSearch c m => m ()
- winner :: MonadSearch c m => m a -> m a
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
The SearchT monad transformer
Instances
MonadRWS r w s m => MonadRWS r w s (SearchT c m) Source # | |
Defined in Control.Monad.Search | |
(Ord c, Monoid c, Monad m) => MonadSearch c (SearchT c m) Source # | |
MonadError e m => MonadError e (SearchT c m) Source # | |
Defined in Control.Monad.Search 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 # | |
MonadState s m => MonadState s (SearchT c m) Source # | |
MonadWriter w m => MonadWriter w (SearchT c m) Source # | |
MonadTrans (SearchT c) Source # | |
Defined in Control.Monad.Search | |
MonadIO m => MonadIO (SearchT c m) Source # | |
Defined in Control.Monad.Search | |
(Ord c, Monoid c, Monad m) => Alternative (SearchT c m) Source # | |
Applicative (SearchT c m) Source # | |
Defined in Control.Monad.Search | |
Functor (SearchT c m) Source # | |
Monad (SearchT c m) Source # | |
(Ord c, Monoid c, Monad m) => MonadPlus (SearchT c m) Source # | |
MonadCont m => MonadCont (SearchT c m) Source # | |
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 Source #
Minimal definition is cost
, junction
, and abandon
.
Instances
(Ord c, Monoid c, Monad m) => MonadSearch c (SearchT c m) Source # | |
MonadSearch c m => MonadSearch c (ExceptT e m) Source # | |
MonadSearch c m => MonadSearch c (ReaderT r m) Source # | |
MonadSearch c m => MonadSearch c (StateT s m) Source # | |
MonadSearch c m => MonadSearch c (StateT s m) Source # | |
(Monoid w, MonadSearch c m) => MonadSearch c (WriterT w m) Source # | |
(Monoid w, MonadSearch c m) => MonadSearch c (WriterT w m) Source # | |
(Monoid w, MonadSearch c m) => MonadSearch c (RWST r w s m) Source # | |
(Monoid w, MonadSearch c m) => MonadSearch c (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)