toysolver-0.6.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

ToySolver.Graph.ShortestPath

Contents

Description

This module provides functions for shotest path computation.

Reference:

Synopsis

Graph data types

type Graph vertex cost label = HashMap vertex [OutEdge vertex cost label] Source #

Graph represented as a map from vertexes to their outgoing edges

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

Edge data type

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

Outgoing edge data type (source vertex is implicit)

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

Incoming edge data type (target vertex is implicit)

Fold data type

data Fold vertex cost label r Source #

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

Fold vertex cost label r consists of three operations

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

and a -> r to finish the computation.

Constructors

Fold (vertex -> a) (Edge vertex cost label -> a) (a -> a -> a) (a -> r) 
Instances
Functor (Fold vertex cost label) Source # 
Instance details

Defined in ToySolver.Graph.ShortestPath

Methods

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

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

Applicative (Fold vertex cost label) Source # 
Instance details

Defined in ToySolver.Graph.ShortestPath

Methods

pure :: a -> Fold vertex cost label a #

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

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

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

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

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

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

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

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

unit :: Fold vertex cost label () Source #

Ignore contents and return a unit value.

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

Pairs two Fold into one that produce a tuple.

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

Construct a Path value.

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

Get the first OutEdge of a path.

lastInEdge :: Fold vertex cost label (Last (InEdge vertex 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 vertex cost label cost Source #

Compute cost of a path.

Path data types

data Path vertex cost label Source #

path data type.

Constructors

Empty vertex

empty path

Singleton (Edge vertex cost label)

path with single edge

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

concatenation of two paths

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

Defined in ToySolver.Graph.ShortestPath

Methods

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

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

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

Defined in ToySolver.Graph.ShortestPath

Methods

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

show :: Path vertex cost label -> String #

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

pathFrom :: Path vertex cost label -> vertex Source #

Source vertex

pathTo :: Path vertex cost label -> vertex Source #

Target vertex

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

Cost of a path

pathEmpty :: vertex -> Path vertex cost label Source #

Empty path

pathAppend :: (Eq vertex, Num cost) => Path vertex cost label -> Path vertex cost label -> Path vertex cost label Source #

Concatenation of two paths

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

Edges of a path

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

Edges of a path, but in the reverse order

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

Edges of a path, but as Seq

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

Vertexes of a path

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

Vertexes of a path, but in the reverse order

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

Vertex of a path, but as Seq

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

Fold a path using a given Fold operation.

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

Shortest-path algorithms

bellmanFord Source #

Arguments

:: (Eq vertex, Hashable vertex, Real cost) 
=> Fold vertex cost label a

Operation used to fold shotest paths

-> Graph vertex cost label 
-> [vertex]

List of source vertexes vs

-> HashMap vertex (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

:: (Eq vertex, Hashable vertex, Real cost) 
=> Fold vertex cost label a

Operation used to fold shotest paths

-> Graph vertex cost label 
-> [vertex]

List of source vertexes

-> HashMap vertex (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

:: (Eq vertex, Hashable vertex, Real cost) 
=> Fold vertex cost label a

Operation used to fold shotest paths

-> Graph vertex cost label 
-> HashMap vertex (HashMap vertex (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

:: (Eq vertex, Hashable vertex, Real cost) 
=> Fold vertex cost label a

Operation used to fold a cycle

-> Graph vertex cost label 
-> HashMap vertex (cost, Last (InEdge vertex cost label))

Result of bellmanFord lastInEdge vs

-> Maybe a 

Utility function for detecting a negative cycle.