monus-weighted-search-0.1.0.0: Efficient search weighted by an ordered monoid with monus.
Copyright(c) Donnacha Oisín Kidney 2021
Maintainermail@doisinkidney.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

MonusWeightedSearch.Examples.Dijkstra

Description

An implementation of Dijkstra's algorithm, using the HeapT monad.

This is taken from section 6.1.3 of the paper

  • Donnacha Oisín Kidney and Nicolas Wu. 2021. Algebras for weighted search. Proc. ACM Program. Lang. 5, ICFP, Article 72 (August 2021), 30 pages. DOI:https://doi.org/10.1145/3473577

This is a pretty simple implementation of the algorithm, defined monadically, but it retains the time complexity of a standard purely functional implementation.

We use the state monad here to avoid searching from the same node more than once (which would lead to an infinite loop). Different algorithms use different permutations of the monad transformers: for Dijkstra's algorithm, we use HeapT w (State (Set a)) a, i.e. the HeapT is outside of the State. This means that each branch of the search proceeds with a different state; if we switch the order (to StateT s (Heap w) a, for example), we get "global" state, which has the semantics of a parser. For an example of that, see the module MonusWeightedSearch.Examples.Parsing, where the heap is used to implement a probabilistic parser.

Synopsis

Documentation

unique :: Ord a => a -> HeapT w (State (Set a)) a Source #

unique x checks that x has not yet been seen in this branch of the computation.

star :: MonadPlus m => (a -> m a) -> a -> m a Source #

This is the Kleene star on the semiring of MonadPlus. It is analagous to the many function on Alternatives.

pathed :: MonadPlus m => (a -> m a) -> a -> m (NonEmpty a) Source #

This is a version of star which keeps track of the inputs it was given.

dijkstra :: Ord a => Graph a -> a -> [(a, Dist)] Source #

Dijkstra's algorithm. This function returns the length of the shortest path from a given vertex to every vertex in the graph.

>>> dijkstra graph 1
[(1,0),(2,7),(3,9),(6,11),(5,20),(4,20)]

A version which actually produces the paths is shortestPaths

shortestPaths :: Ord a => Graph a -> a -> [(NonEmpty a, Dist)] Source #

Dijkstra's algorithm, which produces a path.

The only difference between this function and shortestPaths is that this uses pathed rather than star.

The following finds the shortest path from vertex 1 to 5:

>>> filter ((5==) . head . fst) (shortestPaths graph 1)
[(5 :| [6,3,1],20)]

And it is indeed [1,3,6,5]. (it's returned in reverse)