dijkstra-simple-0.1.0: A simpler Dijkstra shortest paths implementation

Safe HaskellSafe
LanguageHaskell2010

Graph.DijkstraSimple

Contents

Synopsis

How to use this library

This section contains basic step-by-step usage of the library.

The first step is to build a direct graph:

exampleGraph :: Graph Char Int
exampleGraph = Graph $ M.fromList [
                                    ('A', [EdgeTo 'B' 3, EdgeTo 'C' 1])
                                  , ('B', [EdgeTo 'A' 3, EdgeTo 'C' 7, EdgeTo 'D' 5, EdgeTo 'E' 1])
                                  , ('C', [EdgeTo 'A' 1, EdgeTo 'B' 7, EdgeTo 'D' 2])
                                  , ('D', [EdgeTo 'B' 5, EdgeTo 'C' 2, EdgeTo 'E' 5])
                                  , ('E', [EdgeTo 'B' 1, EdgeTo 'D' 7])
                                  ]

Then pick or create a weighter (see Graph.DijkstraSimple.Weighters) and apply it all:

lightestPaths exampleGraph 'C' weighter

It will give all the reacheable vertices from C and associated shortest path:

Paths $ M.fromList [
                     ('A', Path (fromList "AC") 1)
                   , ('B', Path (fromList "BAC") 3)
                   , ('C', Path (fromList "CAC") 1)
                   , ('D', Path (fromList "DC") 2)
                   , ('E', Path (fromList "EBAC") 3)
                   ]

lightestPaths :: forall v e a. (Ord v, Ord a) => Graph v e -> v -> Weighter v e a -> Paths v e a Source #

Explore all the reachable edges

findPath :: forall v e a. (Ord v, Ord a) => Graph v e -> v -> Weighter v e a -> v -> Maybe (Path v e a) Source #

Find the eventual path between two edges

dijkstraSteps :: forall v e a. (Ord v, Ord a) => Graph v e -> v -> Weighter v e a -> NonEmpty (Paths v e a) Source #

Details each step of the Dijkstra algorithm

data EdgeTo v e Source #

Edge to an arbitrary vertex and the associated input weight

Constructors

EdgeTo 

Fields

Instances
(Eq v, Eq e) => Eq (EdgeTo v e) Source # 
Instance details

Defined in Graph.DijkstraSimple

Methods

(==) :: EdgeTo v e -> EdgeTo v e -> Bool #

(/=) :: EdgeTo v e -> EdgeTo v e -> Bool #

(Show v, Show e) => Show (EdgeTo v e) Source # 
Instance details

Defined in Graph.DijkstraSimple

Methods

showsPrec :: Int -> EdgeTo v e -> ShowS #

show :: EdgeTo v e -> String #

showList :: [EdgeTo v e] -> ShowS #

newtype Graph v e Source #

All vertices and outgoing edges

Constructors

Graph 

Fields

Instances
(Eq v, Eq e) => Eq (Graph v e) Source # 
Instance details

Defined in Graph.DijkstraSimple

Methods

(==) :: Graph v e -> Graph v e -> Bool #

(/=) :: Graph v e -> Graph v e -> Bool #

(Show v, Show e) => Show (Graph v e) Source # 
Instance details

Defined in Graph.DijkstraSimple

Methods

showsPrec :: Int -> Graph v e -> ShowS #

show :: Graph v e -> String #

showList :: [Graph v e] -> ShowS #

data Weighter v e a Source #

Convert an input weight (edge-dependant) to an output weight (path-dependant) for the algorithm work.

Constructors

Weighter 

Fields

data Path v e a Source #

The lightest found path with reverse ordered list of traversed vertices and output weight.

Constructors

Path 

Fields

Instances
(Eq v, Eq a) => Eq (Path v e a) Source # 
Instance details

Defined in Graph.DijkstraSimple

Methods

(==) :: Path v e a -> Path v e a -> Bool #

(/=) :: Path v e a -> Path v e a -> Bool #

(Show v, Show a) => Show (Path v e a) Source # 
Instance details

Defined in Graph.DijkstraSimple

Methods

showsPrec :: Int -> Path v e a -> ShowS #

show :: Path v e a -> String #

showList :: [Path v e a] -> ShowS #

newtype Paths v e a Source #

Reachable vertices and associated lightest paths

Constructors

Paths 

Fields

Instances
(Eq v, Eq a) => Eq (Paths v e a) Source # 
Instance details

Defined in Graph.DijkstraSimple

Methods

(==) :: Paths v e a -> Paths v e a -> Bool #

(/=) :: Paths v e a -> Paths v e a -> Bool #

(Show v, Show a) => Show (Paths v e a) Source # 
Instance details

Defined in Graph.DijkstraSimple

Methods

showsPrec :: Int -> Paths v e a -> ShowS #

show :: Paths v e a -> String #

showList :: [Paths v e a] -> ShowS #