monad-dijkstra-0.1.0.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.

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.

The SearchT monad transformer

data SearchT c m a Source

The SearchT monad transformer

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

Generate all solutions in order of increasing cost.

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.

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

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

Mark an operation with a cost.

cost' c = cost c mempty

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

Limit a given computation to the first successful return.

winner m = seal (m <* collapse)