toysolver-0.7.0: Assorted decision procedures for SAT, SMT, Max-SAT, PB, MIP, etc
Copyright(c) Masahiro Sakai 2016-2017
LicenseBSD-style
Maintainermasahiro.sakai@gmail.com
Stabilityprovisional
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • ScopedTypeVariables
  • ExistentialQuantification
  • ExplicitForAll

ToySolver.Graph.ShortestPath

Description

This module provides functions for shotest path computation.

Reference:

Synopsis

Graph data types

type Graph cost label = IntMap [OutEdge cost label] Source #

Graph represented as a map from vertexes to their outgoing edges

type Edge cost label = (Vertex, Vertex, cost, label) Source #

Edge data type

type OutEdge cost label = (Vertex, cost, label) Source #

Outgoing edge data type (source vertex is implicit)

type InEdge cost label = (Vertex, cost, label) Source #

Incoming edge data type (target vertex is implicit)

Fold data type

data Fold cost label r Source #

Operations for folding edge information along with a path into a r value.

Fold cost label r consists of three operations

  • Vertex -> a corresponds to an empty path,
  • Edge cost label -> a corresponds to a single edge,
  • a -> a -> a corresponds to path concatenation,

and a -> r to finish the computation.

Constructors

forall a. Fold (Vertex -> a) (Edge cost label -> a) (a -> a -> a) (a -> r) 

Instances

Instances details
Functor (Fold cost label) Source # 
Instance details

Defined in ToySolver.Graph.ShortestPath

Methods

fmap :: (a -> b) -> Fold cost label a -> Fold cost label b #

(<$) :: a -> Fold cost label b -> Fold cost label a #

Applicative (Fold cost label) Source # 
Instance details

Defined in ToySolver.Graph.ShortestPath

Methods

pure :: a -> Fold cost label a #

(<*>) :: Fold cost label (a -> b) -> Fold cost label a -> Fold cost label b #

liftA2 :: (a -> b -> c) -> Fold cost label a -> Fold cost label b -> Fold cost label c #

(*>) :: Fold cost label a -> Fold cost label b -> Fold cost label b #

(<*) :: Fold cost label a -> Fold cost label b -> Fold cost label a #

monoid' :: Monoid m => (Edge cost label -> m) -> Fold cost label m Source #

Project Edge into a monoid value and fold using monoidal operation.

monoid :: Monoid m => Fold cost m m Source #

Similar to monoid' but a label is directly used as a monoid value.

unit :: Fold cost label () Source #

Ignore contents and return a unit value.

pair :: Fold cost label a -> Fold cost label b -> Fold cost label (a, b) Source #

Pairs two Fold into one that produce a tuple.

path :: Num cost => Fold cost label (Path cost label) Source #

Construct a Path value.

firstOutEdge :: Fold cost label (First (OutEdge cost label)) Source #

Get the first OutEdge of a path.

lastInEdge :: Fold cost label (Last (InEdge cost label)) Source #

Get the last InEdge of a path. This is useful for constructing a parent map of a spanning tree.

cost :: Num cost => Fold cost label cost Source #

Compute cost of a path.

Path data types

data Path cost label Source #

path data type.

Constructors

Empty Vertex

empty path

Singleton (Edge cost label)

path with single edge

Append (Path cost label) (Path cost label) !cost

concatenation of two paths

Instances

Instances details
(Eq cost, Eq label) => Eq (Path cost label) Source # 
Instance details

Defined in ToySolver.Graph.ShortestPath

Methods

(==) :: Path cost label -> Path cost label -> Bool #

(/=) :: Path cost label -> Path cost label -> Bool #

(Show cost, Show label) => Show (Path cost label) Source # 
Instance details

Defined in ToySolver.Graph.ShortestPath

Methods

showsPrec :: Int -> Path cost label -> ShowS #

show :: Path cost label -> String #

showList :: [Path cost label] -> ShowS #

pathFrom :: Path cost label -> Vertex Source #

Source vertex

pathTo :: Path cost label -> Vertex Source #

Target vertex

pathCost :: Num cost => Path cost label -> cost Source #

Cost of a path

pathEmpty :: Vertex -> Path cost label Source #

Empty path

pathAppend :: Num cost => Path cost label -> Path cost label -> Path cost label Source #

Concatenation of two paths

pathEdges :: Path cost label -> [Edge cost label] Source #

Edges of a path

pathEdgesBackward :: Path cost label -> [Edge cost label] Source #

Edges of a path, but in the reverse order

pathEdgesSeq :: Path cost label -> Seq (Edge cost label) Source #

Edges of a path, but as Seq

pathVertexes :: Path cost label -> [Vertex] Source #

Vertexes of a path

pathVertexesBackward :: Path cost label -> [Vertex] Source #

Vertexes of a path, but in the reverse order

pathVertexesSeq :: Path cost label -> Seq Vertex Source #

Vertex of a path, but as Seq

pathFold :: Fold cost label a -> Path cost label -> a Source #

Fold a path using a given Fold operation.

pathMin :: (Num cost, Ord cost) => Path cost label -> Path cost label -> Path cost label Source #

Shortest-path algorithms

bellmanFord Source #

Arguments

:: Real cost 
=> Fold cost label a

Operation used to fold shotest paths

-> Graph cost label 
-> [Vertex]

List of source vertexes vs

-> IntMap (cost, a) 

Bellman-Ford algorithm for finding shortest paths from source vertexes to all of the other vertices in a weighted graph with negative weight edges allowed.

It compute shortest-paths from given source vertexes, and folds edge information along shortest paths using a given Fold operation.

dijkstra Source #

Arguments

:: forall cost label a. Real cost 
=> Fold cost label a

Operation used to fold shotest paths

-> Graph cost label 
-> [Vertex]

List of source vertexes

-> IntMap (cost, a) 

Dijkstra's algorithm for finding shortest paths from source vertexes to all of the other vertices in a weighted graph with non-negative edge weight.

It compute shortest-paths from given source vertexes, and folds edge information along shortest paths using a given Fold operation.

floydWarshall Source #

Arguments

:: forall cost label a. Real cost 
=> Fold cost label a

Operation used to fold shotest paths

-> Graph cost label 
-> IntMap (IntMap (cost, a)) 

Floyd-Warshall algorithm for finding shortest paths in a weighted graph with positive or negative edge weights (but with no negative cycles).

It compute shortest-paths between each pair of vertexes, and folds edge information along shortest paths using a given Fold operation.

Utility functions

bellmanFordDetectNegativeCycle Source #

Arguments

:: forall cost label a. Real cost 
=> Fold cost label a

Operation used to fold a cycle

-> Graph cost label 
-> IntMap (cost, Last (InEdge cost label))

Result of bellmanFord lastInEdge vs

-> Maybe a 

Utility function for detecting a negative cycle.