digraph-0.1.0.0: Directed Graphs

CopyrightCopyright © 2018-2019 Kadena LLC.
LicenseMIT
MaintainerLars Kuhtz <lars@kadena.io>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.DiGraph

Contents

Description

Directed graphs in adjacency set representation. The implementation is based on Data.HashMap.Strict and Data.HashSet from the unordered-containers package

Undirected graphs are represented as symmetric, irreflexive directed graphs.

Synopsis

Documentation

data DiGraph a Source #

Adjacency set representation of directed graphs.

It is assumed that each target of an edge is also explicitly a vertex in the graph.

It is not generally required that graphs are irreflexive, but all concrete graphs that are defined in this module are irreflexive.

Undirected graphs are represented as symmetric directed graphs.

Instances
Eq a => Eq (DiGraph a) Source # 
Instance details

Defined in Data.DiGraph

Methods

(==) :: DiGraph a -> DiGraph a -> Bool #

(/=) :: DiGraph a -> DiGraph a -> Bool #

Ord a => Ord (DiGraph a) Source # 
Instance details

Defined in Data.DiGraph

Methods

compare :: DiGraph a -> DiGraph a -> Ordering #

(<) :: DiGraph a -> DiGraph a -> Bool #

(<=) :: DiGraph a -> DiGraph a -> Bool #

(>) :: DiGraph a -> DiGraph a -> Bool #

(>=) :: DiGraph a -> DiGraph a -> Bool #

max :: DiGraph a -> DiGraph a -> DiGraph a #

min :: DiGraph a -> DiGraph a -> DiGraph a #

Show a => Show (DiGraph a) Source # 
Instance details

Defined in Data.DiGraph

Methods

showsPrec :: Int -> DiGraph a -> ShowS #

show :: DiGraph a -> String #

showList :: [DiGraph a] -> ShowS #

Generic (DiGraph a) Source # 
Instance details

Defined in Data.DiGraph

Associated Types

type Rep (DiGraph a) :: Type -> Type #

Methods

from :: DiGraph a -> Rep (DiGraph a) x #

to :: Rep (DiGraph a) x -> DiGraph a #

(Hashable a, Eq a) => Semigroup (DiGraph a) Source # 
Instance details

Defined in Data.DiGraph

Methods

(<>) :: DiGraph a -> DiGraph a -> DiGraph a #

sconcat :: NonEmpty (DiGraph a) -> DiGraph a #

stimes :: Integral b => b -> DiGraph a -> DiGraph a #

(Hashable a, Eq a) => Monoid (DiGraph a) Source # 
Instance details

Defined in Data.DiGraph

Methods

mempty :: DiGraph a #

mappend :: DiGraph a -> DiGraph a -> DiGraph a #

mconcat :: [DiGraph a] -> DiGraph a #

NFData a => NFData (DiGraph a) Source # 
Instance details

Defined in Data.DiGraph

Methods

rnf :: DiGraph a -> () #

Hashable a => Hashable (DiGraph a) Source # 
Instance details

Defined in Data.DiGraph

Methods

hashWithSalt :: Int -> DiGraph a -> Int #

hash :: DiGraph a -> Int #

type Rep (DiGraph a) Source # 
Instance details

Defined in Data.DiGraph

type Rep (DiGraph a) = D1 (MetaData "DiGraph" "Data.DiGraph" "digraph-0.1.0.0-8w9BfID4Lt02wYn7iWxOIQ" True) (C1 (MetaCons "DiGraph" PrefixI True) (S1 (MetaSel (Just "unGraph") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap a (HashSet a)))))

type DiEdge a = (a, a) Source #

Directed Edge.

adjacencySets :: DiGraph a -> HashMap a (HashSet a) Source #

The adjacency sets of a graph.

vertices :: DiGraph a -> HashSet a Source #

The set of vertices of the graph.

edges :: Eq a => Hashable a => DiGraph a -> HashSet (DiEdge a) Source #

The set edges of the graph.

adjacents :: Eq a => Hashable a => a -> DiGraph a -> HashSet a Source #

The set of adjacent pairs of a graph.

incidents :: Eq a => Hashable a => a -> DiGraph a -> [(a, a)] Source #

The set of incident edges of a graph.

Construction and Modification of Graphs

insertEdge :: Eq a => Hashable a => DiEdge a -> DiGraph a -> DiGraph a Source #

Insert an edge. Returns the graph unmodified if the edge is already in the graph. Non-existing vertices are added.

fromEdges :: Eq a => Hashable a => Foldable f => f (a, a) -> DiGraph a Source #

Construct a graph from a foldable structure of edges.

insertVertex :: Eq a => Hashable a => a -> DiGraph a -> DiGraph a Source #

Insert a vertex. Returns the graph unmodified if the vertex is already in the graph.

mapVertices :: Eq b => Hashable b => (a -> b) -> DiGraph a -> DiGraph b Source #

Map a function over all vertices of a graph.

union :: Eq a => Hashable a => DiGraph a -> DiGraph a -> DiGraph a Source #

The union of two graphs.

transpose :: Eq a => Hashable a => DiGraph a -> DiGraph a Source #

Transpose a graph, i.e. reverse all edges of the graph.

symmetric :: Eq a => Hashable a => DiGraph a -> DiGraph a Source #

Symmetric closure of a graph.

fromList :: Eq a => Hashable a => [(a, [a])] -> DiGraph a Source #

Construct a graph from adjacency lists.

unsafeFromList :: Eq a => Hashable a => [(a, [a])] -> DiGraph a Source #

Unsafely construct a graph from adjacency lists.

This function assumes that the input includes a adjacency list of each vertex that appears in a adjacency list of another vertex. Generally, fromList should be preferred.

Predicates

isDiGraph :: Eq a => Hashable a => DiGraph a -> Bool Source #

A predicate that asserts that every target of an edge is also a vertex in the graph. Any graph that is constructed without using unsafe methods is guaranteed to satisfy this predicate.

isAdjacent :: Eq a => Hashable a => a -> a -> DiGraph a -> Bool Source #

Return whether two vertices are adjacent in a graph.

isRegular :: DiGraph a -> Bool Source #

Return whether a graph is regular, i.e. whether all vertices have the same out-degree. Note that the latter implies that all vertices also have the same in-degree.

isSymmetric :: Hashable a => Eq a => DiGraph a -> Bool Source #

Return whether a graph is symmetric, i.e. whether for each edge \((a,b)\) there is also the edge \((b,a)\) in the graph.

isIrreflexive :: Eq a => Hashable a => DiGraph a -> Bool Source #

Return whether a graph is irreflexive. A graph is irreflexive if for each edge \((a,b)\) it holds that \(a \neq b\), i.e there are no self-loops in the graph.

isEdge :: Eq a => Hashable a => DiEdge a -> DiGraph a -> Bool Source #

Return whether an edge is contained in a graph.

isVertex :: Eq a => Hashable a => a -> DiGraph a -> Bool Source #

Return whether a vertex is contained in a graph.

Properties

order :: DiGraph a -> Natural Source #

The order of a graph is the number of vertices.

size :: Eq a => Hashable a => DiGraph a -> Natural Source #

Directed Size. This the number of edges of the graph.

diSize :: Eq a => Hashable a => DiGraph a -> Natural Source #

Directed Size. This the number of edges of the graph.

symSize :: Eq a => Hashable a => DiGraph a -> Natural Source #

Undirected Size of a graph. This is the number of edges of the symmetric closure of the graph.

outDegree :: Eq a => Hashable a => DiGraph a -> a -> Natural Source #

The number of outgoing edges of vertex in a graph.

inDegree :: Eq a => Hashable a => DiGraph a -> a -> Natural Source #

The number of incoming edges of vertex in a graph.

maxOutDegree :: Eq a => Hashable a => DiGraph a -> Natural Source #

The maximum out-degree of the vertices of a graph.

maxInDegree :: Eq a => Hashable a => DiGraph a -> Natural Source #

The maximum in-degree of the vertices of a graph.

minOutDegree :: Eq a => Hashable a => DiGraph a -> Natural Source #

The minimum out-degree of the vertices of a graph.

minInDegree :: Eq a => Hashable a => DiGraph a -> Natural Source #

The minimum in-degree of the vertices of a graph.

Distances, Shortest Paths, and Diameter

data ShortestPathCache a Source #

The shortest path matrix of a graph.

The shortest path matrix of a graph can be used to efficiently query the distance and shortest path between any two vertices of the graph. It can also be used to efficiently compute the diameter of the graph.

Computing the shortest path matrix is expensive for larger graphs. The matrix is computed using the Floyd-Warshall algorithm. The space and time complexity is quadratic in the order of the graph. For sparse graphs there are more efficient algorithms for computing distances and shortest paths between the nodes of the graph.

Instances
Eq a => Eq (ShortestPathCache a) Source # 
Instance details

Defined in Data.DiGraph

Ord a => Ord (ShortestPathCache a) Source # 
Instance details

Defined in Data.DiGraph

Show a => Show (ShortestPathCache a) Source # 
Instance details

Defined in Data.DiGraph

Generic (ShortestPathCache a) Source # 
Instance details

Defined in Data.DiGraph

Associated Types

type Rep (ShortestPathCache a) :: Type -> Type #

NFData a => NFData (ShortestPathCache a) Source # 
Instance details

Defined in Data.DiGraph

Methods

rnf :: ShortestPathCache a -> () #

type Rep (ShortestPathCache a) Source # 
Instance details

Defined in Data.DiGraph

shortestPathCache :: Eq a => Hashable a => DiGraph a -> ShortestPathCache a Source #

Compute the shortest path matrix for a graph. The result can be used to efficiently query the distance and shortest path between any two vertices of the graph. It can also be used to efficiently compute the diameter of the graph.

shortestPath :: Eq a => Hashable a => a -> a -> DiGraph a -> Maybe [a] Source #

Compute the shortest path between two vertices of a graph.

| This is expensive for larger graphs. If more than one path is needed one should use shortestPathCache to cache the result of the search and use shortestPath_ to query paths from the cache.

The algorithm is optimized for dense graphs. For large sparse graphs a more efficient algorithm should be used.

shortestPath_ :: Eq a => Hashable a => a -> a -> ShortestPathCache a -> Maybe [a] Source #

Compute the shortest path between two vertices from the shortest path matrix of a graph.

The algorithm is optimized for dense graphs. For large sparse graphs a more efficient algorithm should be used.

distance :: Eq a => Hashable a => a -> a -> DiGraph a -> Maybe Natural Source #

Compute the distance between two vertices of a graph.

| This is expensive for larger graphs. If more than one distance is needed one should use shortestPathCache to cache the result of the search and use distance_ to query paths from the cache.

The algorithm is optimized for dense graphs. For large sparse graphs a more efficient algorithm should be used.

distance_ :: Eq a => Hashable a => a -> a -> ShortestPathCache a -> Maybe Natural Source #

Compute the distance between two vertices from the shortest path matrix of a graph.

The algorithm is optimized for dense graphs. For large sparse graphs a more efficient algorithm should be used.

diameter :: Eq a => Hashable a => DiGraph a -> Maybe Natural Source #

Compute the Diameter of a graph, i.e. the maximum length of a shortest path between two vertices in the graph.

This is expensive to compute for larger graphs. If also the shortest paths or distances are needed, one should use shortestPathCache to cache the result of the search and use the diameter_, shortestPath_, and distance_ to query the respective results from the cache.

The algorithm is optimized for dense graphs. For large sparse graphs a more efficient algorithm should be used.

diameter_ :: ShortestPathCache a -> Maybe Natural Source #

Compute the Diameter of a graph from a shortest path matrix. The diameter of a graph is the maximum length of a shortest path between two vertices in the graph.

Graphs

emptyGraph :: Natural -> DiGraph Int Source #

The empty graph on n nodes. This is the graph of order n and size 0.

singleton :: DiGraph Int Source #

The (irreflexive) singleton graph.

clique :: Natural -> DiGraph Int Source #

Undirected clique.

pair :: DiGraph Int Source #

Undirected pair.

triangle :: DiGraph Int Source #

Undirected triangle.

cycle :: Natural -> DiGraph Int Source #

Undirected cycle.

diCycle :: Natural -> DiGraph Int Source #

Directed cycle.

line :: Natural -> DiGraph Int Source #

Undirected line.

diLine :: Natural -> DiGraph Int Source #

Directed line.

petersonGraph :: DiGraph Int Source #

The Peterson graph.

twentyChainGraph :: DiGraph Int Source #

The "twenty chain" graph.

hoffmanSingleton :: DiGraph Int Source #

Hoffman-Singleton Graph.

The Hoffman-Singleton graph is a 7-regular graph with 50 vertices and 175 edges. It's the largest graph of max-degree 7 and diameter 2. Cf. [https:/en.wikipedia.orgwiki/Hoffman–Singleton_graph]()