Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- class Graph g where
- empty :: Hashable v => g v e
- order :: g v e -> Int
- size :: (Hashable v, Eq v) => g v e -> Int
- density :: (Hashable v, Eq v) => g v e -> Double
- vertices :: g v e -> [v]
- edgeTriples :: (Hashable v, Eq v) => g v e -> [(v, v, e)]
- edgePairs :: (Hashable v, Eq v) => g v e -> [(v, v)]
- containsVertex :: (Hashable v, Eq v) => g v e -> v -> Bool
- areAdjacent :: (Hashable v, Eq v) => g v e -> v -> v -> Bool
- adjacentVertices :: (Hashable v, Eq v) => g v e -> v -> [v]
- adjacentVertices' :: (Hashable v, Eq v) => g v e -> v -> [(v, v, e)]
- reachableAdjacentVertices :: (Hashable v, Eq v) => g v e -> v -> [v]
- reachableAdjacentVertices' :: (Hashable v, Eq v) => g v e -> v -> [(v, v, e)]
- vertexDegree :: (Hashable v, Eq v) => g v e -> v -> Int
- degrees :: (Hashable v, Eq v) => g v e -> [Int]
- maxDegree :: (Hashable v, Eq v) => g v e -> Int
- minDegree :: (Hashable v, Eq v) => g v e -> Int
- avgDegree :: (Hashable v, Eq v) => g v e -> Double
- insertVertex :: (Hashable v, Eq v) => v -> g v e -> g v e
- insertVertices :: (Hashable v, Eq v) => [v] -> g v e -> g v e
- containsEdgePair :: (Hashable v, Eq v) => g v e -> (v, v) -> Bool
- incidentEdgeTriples :: (Hashable v, Eq v) => g v e -> v -> [(v, v, e)]
- incidentEdgePairs :: (Hashable v, Eq v) => g v e -> v -> [(v, v)]
- edgeTriple :: (Hashable v, Eq v) => g v e -> v -> v -> Maybe (v, v, e)
- insertEdgeTriple :: (Hashable v, Eq v) => (v, v, e) -> g v e -> g v e
- insertEdgeTriples :: (Hashable v, Eq v) => [(v, v, e)] -> g v e -> g v e
- insertEdgePair :: (Hashable v, Eq v) => (v, v) -> g v () -> g v ()
- insertEdgePairs :: (Hashable v, Eq v) => [(v, v)] -> g v () -> g v ()
- removeVertex :: (Hashable v, Eq v) => v -> g v e -> g v e
- removeVertices :: (Hashable v, Eq v) => [v] -> g v e -> g v e
- removeEdgePair :: (Hashable v, Eq v) => (v, v) -> g v e -> g v e
- removeEdgePairs :: (Hashable v, Eq v) => [(v, v)] -> g v e -> g v e
- removeEdgePairAndVertices :: (Hashable v, Eq v) => (v, v) -> g v e -> g v e
- isolatedVertices :: (Hashable v, Eq v) => g v e -> [v]
- isSimple :: (Hashable v, Eq v) => g v e -> Bool
- union :: (Hashable v, Eq v) => g v e -> g v e -> g v e
- intersection :: (Hashable v, Eq v, Eq e) => g v e -> g v e -> g v e
- toList :: (Hashable v, Eq v) => g v e -> [(v, [(v, e)])]
- fromList :: (Hashable v, Eq v) => [(v, [(v, e)])] -> g v e
- fromAdjacencyMatrix :: [[Int]] -> Maybe (g Int ())
- class IsEdge e where
- originVertex :: e v a -> v
- destinationVertex :: e v a -> v
- attribute :: e v a -> a
- toPair :: e v a -> (v, v)
- fromPair :: (v, v) -> e v ()
- toTriple :: e v a -> (v, v, a)
- fromTriple :: (v, v, a) -> e v a
- isLoop :: Eq v => e v a -> Bool
- data Edge v e = Edge v v e
- data Arc v e = Arc v v e
- (<->) :: Hashable v => v -> v -> Edge v ()
- (-->) :: Hashable v => v -> v -> Arc v ()
- class Weighted e where
- class Labeled e where
- tripleToPair :: (a, b, c) -> (a, b)
- pairToTriple :: (a, b) -> (a, b, ())
- tripleOriginVertex :: (v, v, e) -> v
- tripleDestVertex :: (v, v, e) -> v
- tripleAttribute :: (v, v, e) -> e
Main Graph type class
Types that behave like graphs
The main Graph
instances are UGraph
and DGraph
. The functions in this
class should be used for algorithms that are graph-directionality agnostic,
otherwise use the more specific ones in UGraph
and DGraph
empty, order, vertices, edgeTriples, containsVertex, adjacentVertices', reachableAdjacentVertices', vertexDegree, insertVertex, containsEdgePair, incidentEdgeTriples, edgeTriple, insertEdgeTriple, removeVertex, removeEdgePair, isSimple, union, intersection, toList, fromAdjacencyMatrix
empty :: Hashable v => g v e Source #
The Empty (order-zero) graph with no vertices and no edges
order :: g v e -> Int Source #
Retrieve the order of a graph
The order
of a graph is its number of vertices
size :: (Hashable v, Eq v) => g v e -> Int Source #
Retrieve the size of a graph
The size
of a graph is its number of edges
density :: (Hashable v, Eq v) => g v e -> Double Source #
Density of a graph
The density
of a graph is the ratio of the number of existing edges to
the number of posible edges
vertices :: g v e -> [v] Source #
Retrieve all the vertices of a graph
edgeTriples :: (Hashable v, Eq v) => g v e -> [(v, v, e)] Source #
Retrieve the edges of a graph
edgePairs :: (Hashable v, Eq v) => g v e -> [(v, v)] Source #
Retrieve the edges of a graph, ignoring its attributes
containsVertex :: (Hashable v, Eq v) => g v e -> v -> Bool Source #
Tell if a vertex exists in the graph
areAdjacent :: (Hashable v, Eq v) => g v e -> v -> v -> Bool Source #
Tell if two vertices are adjacent
adjacentVertices :: (Hashable v, Eq v) => g v e -> v -> [v] Source #
Retrieve the adjacent vertices of a vertex
adjacentVertices' :: (Hashable v, Eq v) => g v e -> v -> [(v, v, e)] Source #
Same as adjacentVertices
but gives back the connecting edges
reachableAdjacentVertices :: (Hashable v, Eq v) => g v e -> v -> [v] Source #
Same as adjacentVertices
but gives back only those vertices for which
the connecting edge allows the vertex to be reached.
For an undirected graph this is equivalent to adjacentVertices
, but
for the case of a directed graph, the directed arcs will constrain the
reachability of the adjacent vertices.
reachableAdjacentVertices' :: (Hashable v, Eq v) => g v e -> v -> [(v, v, e)] Source #
Same as reachableAdjacentVertices
but gives back the connecting edges
vertexDegree :: (Hashable v, Eq v) => g v e -> v -> Int Source #
Total number of incident edges of a vertex
degrees :: (Hashable v, Eq v) => g v e -> [Int] Source #
Degrees of a all the vertices in a graph
maxDegree :: (Hashable v, Eq v) => g v e -> Int Source #
Maximum degree of a graph
minDegree :: (Hashable v, Eq v) => g v e -> Int Source #
Minimum degree of a graph
avgDegree :: (Hashable v, Eq v) => g v e -> Double Source #
Average degree of a graph
insertVertex :: (Hashable v, Eq v) => v -> g v e -> g v e Source #
Insert a vertex into a graph. If the graph already contains the vertex leave it untouched
insertVertices :: (Hashable v, Eq v) => [v] -> g v e -> g v e Source #
Insert many vertices into a graph. New vertices are inserted and already contained vertices are left untouched
containsEdgePair :: (Hashable v, Eq v) => g v e -> (v, v) -> Bool Source #
Tell if an edge exists in the graph
incidentEdgeTriples :: (Hashable v, Eq v) => g v e -> v -> [(v, v, e)] Source #
Retrieve the incident edges of a vertex
incidentEdgePairs :: (Hashable v, Eq v) => g v e -> v -> [(v, v)] Source #
Retrieve the incident edges of a vertex, ignoring its attributes
edgeTriple :: (Hashable v, Eq v) => g v e -> v -> v -> Maybe (v, v, e) Source #
Get the edge between to vertices if it exists
insertEdgeTriple :: (Hashable v, Eq v) => (v, v, e) -> g v e -> g v e Source #
Insert an edge into a graph. The involved vertices are inserted if don't exist. If the graph already contains the edge, its attribute gets updated
insertEdgeTriples :: (Hashable v, Eq v) => [(v, v, e)] -> g v e -> g v e Source #
Same as insertEdgeTriple
but for multiple edges
insertEdgePair :: (Hashable v, Eq v) => (v, v) -> g v () -> g v () Source #
Same as insertEdgeTriple
but insert edge pairs in graphs with
attribute less edges
insertEdgePairs :: (Hashable v, Eq v) => [(v, v)] -> g v () -> g v () Source #
Same as insertEdgePair
for multiple edges
removeVertex :: (Hashable v, Eq v) => v -> g v e -> g v e Source #
Remove a vertex from a graph if present. Every edge incident to this vertex also gets removed
removeVertices :: (Hashable v, Eq v) => [v] -> g v e -> g v e Source #
Same as removeVertex
but for multiple vertices
removeEdgePair :: (Hashable v, Eq v) => (v, v) -> g v e -> g v e Source #
Remove an edge from a graph if present. The involved vertices are left untouched
removeEdgePairs :: (Hashable v, Eq v) => [(v, v)] -> g v e -> g v e Source #
Same as removeEdgePair
but for multiple edges
removeEdgePairAndVertices :: (Hashable v, Eq v) => (v, v) -> g v e -> g v e Source #
Remove the edge from a graph if present. The involved vertices also get removed
isolatedVertices :: (Hashable v, Eq v) => g v e -> [v] Source #
Retrieve the isolated vertices of a graph, if any
isSimple :: (Hashable v, Eq v) => g v e -> Bool Source #
Tell if a graph is simple
A graph is simple
if it has no loops
union :: (Hashable v, Eq v) => g v e -> g v e -> g v e Source #
Union of two graphs
intersection :: (Hashable v, Eq v, Eq e) => g v e -> g v e -> g v e Source #
Intersection of two graphs
toList :: (Hashable v, Eq v) => g v e -> [(v, [(v, e)])] Source #
Convert a graph to an adjacency list with vertices in type v and edge attributes in e
fromList :: (Hashable v, Eq v) => [(v, [(v, e)])] -> g v e Source #
Construct a graph from an adjacency list with vertices in type /v and edge attributes in e
fromAdjacencyMatrix :: [[Int]] -> Maybe (g Int ()) Source #
Get the adjacency binary matrix representation of a graph toAdjacencyMatrix :: g v e -> [[Int]]
Generate a graph of Int vertices from an adjacency square binary matrix
Instances
Edges type class
Types that represent edges
The main IsEdge
instances are Edge
for undirected edges and Arc
for
directed edges.
originVertex :: e v a -> v Source #
Retrieve the origin vertex of the edge
destinationVertex :: e v a -> v Source #
Retrieve the destination vertex of the edge
attribute :: e v a -> a Source #
Retrieve the attribute of the edge
toPair :: e v a -> (v, v) Source #
Convert an edge to a pair discarding its attribute
fromPair :: (v, v) -> e v () Source #
Convert a pair to an edge, where it's attribute is unit
toTriple :: e v a -> (v, v, a) Source #
Convert an edge to a triple, where the 3rd element it's the edge attribute
fromTriple :: (v, v, a) -> e v a Source #
Convert a triple to an edge
isLoop :: Eq v => e v a -> Bool Source #
Tell if an edge is a loop
An edge forms a loop
if both of its ends point to the same vertex
Instances
IsEdge Arc Source # | |
Defined in Data.Graph.Types | |
IsEdge Edge Source # | |
Defined in Data.Graph.Types |
Main IsEdge instances
Undirected Edge with attribute of type e between to Vertices of type v
Edge v v e |
Instances
Directed Arc with attribute of type e between to Vertices of type v
Arc v v e |
Instances
Edges and Arcs constructors
(<->) :: Hashable v => v -> v -> Edge v () Source #
Construct an attribute less undirected Edge
between two vertices
(-->) :: Hashable v => v -> v -> Arc v () Source #
Construct an attribute less directed Arc
between two vertices
Edge attributes type clases
class Weighted e where Source #
Edge attributes that represent weights
Triple-Edges convenience functions
tripleToPair :: (a, b, c) -> (a, b) Source #
Convert a triple to a pair by ignoring the third element
pairToTriple :: (a, b) -> (a, b, ()) Source #
Convert a pair to a triple where the 3rd element is unit
tripleOriginVertex :: (v, v, e) -> v Source #
Get the origin vertex from an edge triple
tripleDestVertex :: (v, v, e) -> v Source #
Get the destination vertex from an edge triple
tripleAttribute :: (v, v, e) -> e Source #
Get the attribute from an edge triple