graphite-0.10.0.1: Graphs and networks library

Safe HaskellSafe
LanguageHaskell2010

Data.Graph.Types

Contents

Synopsis

Main Graph type class

class Graph g where Source #

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

Methods

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
Graph UGraph Source # 
Instance details

Defined in Data.Graph.UGraph

Methods

empty :: Hashable v => UGraph v e Source #

order :: UGraph v e -> Int Source #

size :: (Hashable v, Eq v) => UGraph v e -> Int Source #

density :: (Hashable v, Eq v) => UGraph v e -> Double Source #

vertices :: UGraph v e -> [v] Source #

edgeTriples :: (Hashable v, Eq v) => UGraph v e -> [(v, v, e)] Source #

edgePairs :: (Hashable v, Eq v) => UGraph v e -> [(v, v)] Source #

containsVertex :: (Hashable v, Eq v) => UGraph v e -> v -> Bool Source #

areAdjacent :: (Hashable v, Eq v) => UGraph v e -> v -> v -> Bool Source #

adjacentVertices :: (Hashable v, Eq v) => UGraph v e -> v -> [v] Source #

adjacentVertices' :: (Hashable v, Eq v) => UGraph v e -> v -> [(v, v, e)] Source #

reachableAdjacentVertices :: (Hashable v, Eq v) => UGraph v e -> v -> [v] Source #

reachableAdjacentVertices' :: (Hashable v, Eq v) => UGraph v e -> v -> [(v, v, e)] Source #

vertexDegree :: (Hashable v, Eq v) => UGraph v e -> v -> Int Source #

degrees :: (Hashable v, Eq v) => UGraph v e -> [Int] Source #

maxDegree :: (Hashable v, Eq v) => UGraph v e -> Int Source #

minDegree :: (Hashable v, Eq v) => UGraph v e -> Int Source #

avgDegree :: (Hashable v, Eq v) => UGraph v e -> Double Source #

insertVertex :: (Hashable v, Eq v) => v -> UGraph v e -> UGraph v e Source #

insertVertices :: (Hashable v, Eq v) => [v] -> UGraph v e -> UGraph v e Source #

containsEdgePair :: (Hashable v, Eq v) => UGraph v e -> (v, v) -> Bool Source #

incidentEdgeTriples :: (Hashable v, Eq v) => UGraph v e -> v -> [(v, v, e)] Source #

incidentEdgePairs :: (Hashable v, Eq v) => UGraph v e -> v -> [(v, v)] Source #

edgeTriple :: (Hashable v, Eq v) => UGraph v e -> v -> v -> Maybe (v, v, e) Source #

insertEdgeTriple :: (Hashable v, Eq v) => (v, v, e) -> UGraph v e -> UGraph v e Source #

insertEdgeTriples :: (Hashable v, Eq v) => [(v, v, e)] -> UGraph v e -> UGraph v e Source #

insertEdgePair :: (Hashable v, Eq v) => (v, v) -> UGraph v () -> UGraph v () Source #

insertEdgePairs :: (Hashable v, Eq v) => [(v, v)] -> UGraph v () -> UGraph v () Source #

removeVertex :: (Hashable v, Eq v) => v -> UGraph v e -> UGraph v e Source #

removeVertices :: (Hashable v, Eq v) => [v] -> UGraph v e -> UGraph v e Source #

removeEdgePair :: (Hashable v, Eq v) => (v, v) -> UGraph v e -> UGraph v e Source #

removeEdgePairs :: (Hashable v, Eq v) => [(v, v)] -> UGraph v e -> UGraph v e Source #

removeEdgePairAndVertices :: (Hashable v, Eq v) => (v, v) -> UGraph v e -> UGraph v e Source #

isolatedVertices :: (Hashable v, Eq v) => UGraph v e -> [v] Source #

isSimple :: (Hashable v, Eq v) => UGraph v e -> Bool Source #

union :: (Hashable v, Eq v) => UGraph v e -> UGraph v e -> UGraph v e Source #

intersection :: (Hashable v, Eq v, Eq e) => UGraph v e -> UGraph v e -> UGraph v e Source #

toList :: (Hashable v, Eq v) => UGraph v e -> [(v, [(v, e)])] Source #

fromList :: (Hashable v, Eq v) => [(v, [(v, e)])] -> UGraph v e Source #

fromAdjacencyMatrix :: [[Int]] -> Maybe (UGraph Int ()) Source #

Graph DGraph Source # 
Instance details

Defined in Data.Graph.DGraph

Methods

empty :: Hashable v => DGraph v e Source #

order :: DGraph v e -> Int Source #

size :: (Hashable v, Eq v) => DGraph v e -> Int Source #

density :: (Hashable v, Eq v) => DGraph v e -> Double Source #

vertices :: DGraph v e -> [v] Source #

edgeTriples :: (Hashable v, Eq v) => DGraph v e -> [(v, v, e)] Source #

edgePairs :: (Hashable v, Eq v) => DGraph v e -> [(v, v)] Source #

containsVertex :: (Hashable v, Eq v) => DGraph v e -> v -> Bool Source #

areAdjacent :: (Hashable v, Eq v) => DGraph v e -> v -> v -> Bool Source #

adjacentVertices :: (Hashable v, Eq v) => DGraph v e -> v -> [v] Source #

adjacentVertices' :: (Hashable v, Eq v) => DGraph v e -> v -> [(v, v, e)] Source #

reachableAdjacentVertices :: (Hashable v, Eq v) => DGraph v e -> v -> [v] Source #

reachableAdjacentVertices' :: (Hashable v, Eq v) => DGraph v e -> v -> [(v, v, e)] Source #

vertexDegree :: (Hashable v, Eq v) => DGraph v e -> v -> Int Source #

degrees :: (Hashable v, Eq v) => DGraph v e -> [Int] Source #

maxDegree :: (Hashable v, Eq v) => DGraph v e -> Int Source #

minDegree :: (Hashable v, Eq v) => DGraph v e -> Int Source #

avgDegree :: (Hashable v, Eq v) => DGraph v e -> Double Source #

insertVertex :: (Hashable v, Eq v) => v -> DGraph v e -> DGraph v e Source #

insertVertices :: (Hashable v, Eq v) => [v] -> DGraph v e -> DGraph v e Source #

containsEdgePair :: (Hashable v, Eq v) => DGraph v e -> (v, v) -> Bool Source #

incidentEdgeTriples :: (Hashable v, Eq v) => DGraph v e -> v -> [(v, v, e)] Source #

incidentEdgePairs :: (Hashable v, Eq v) => DGraph v e -> v -> [(v, v)] Source #

edgeTriple :: (Hashable v, Eq v) => DGraph v e -> v -> v -> Maybe (v, v, e) Source #

insertEdgeTriple :: (Hashable v, Eq v) => (v, v, e) -> DGraph v e -> DGraph v e Source #

insertEdgeTriples :: (Hashable v, Eq v) => [(v, v, e)] -> DGraph v e -> DGraph v e Source #

insertEdgePair :: (Hashable v, Eq v) => (v, v) -> DGraph v () -> DGraph v () Source #

insertEdgePairs :: (Hashable v, Eq v) => [(v, v)] -> DGraph v () -> DGraph v () Source #

removeVertex :: (Hashable v, Eq v) => v -> DGraph v e -> DGraph v e Source #

removeVertices :: (Hashable v, Eq v) => [v] -> DGraph v e -> DGraph v e Source #

removeEdgePair :: (Hashable v, Eq v) => (v, v) -> DGraph v e -> DGraph v e Source #

removeEdgePairs :: (Hashable v, Eq v) => [(v, v)] -> DGraph v e -> DGraph v e Source #

removeEdgePairAndVertices :: (Hashable v, Eq v) => (v, v) -> DGraph v e -> DGraph v e Source #

isolatedVertices :: (Hashable v, Eq v) => DGraph v e -> [v] Source #

isSimple :: (Hashable v, Eq v) => DGraph v e -> Bool Source #

union :: (Hashable v, Eq v) => DGraph v e -> DGraph v e -> DGraph v e Source #

intersection :: (Hashable v, Eq v, Eq e) => DGraph v e -> DGraph v e -> DGraph v e Source #

toList :: (Hashable v, Eq v) => DGraph v e -> [(v, [(v, e)])] Source #

fromList :: (Hashable v, Eq v) => [(v, [(v, e)])] -> DGraph v e Source #

fromAdjacencyMatrix :: [[Int]] -> Maybe (DGraph Int ()) Source #

Edges type class

class IsEdge e where Source #

Types that represent edges

The main IsEdge instances are Edge for undirected edges and Arc for directed edges.

Methods

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 # 
Instance details

Defined in Data.Graph.Types

Methods

originVertex :: Arc v a -> v Source #

destinationVertex :: Arc v a -> v Source #

attribute :: Arc v a -> a Source #

toPair :: Arc v a -> (v, v) Source #

fromPair :: (v, v) -> Arc v () Source #

toTriple :: Arc v a -> (v, v, a) Source #

fromTriple :: (v, v, a) -> Arc v a Source #

isLoop :: Eq v => Arc v a -> Bool Source #

IsEdge Edge Source # 
Instance details

Defined in Data.Graph.Types

Methods

originVertex :: Edge v a -> v Source #

destinationVertex :: Edge v a -> v Source #

attribute :: Edge v a -> a Source #

toPair :: Edge v a -> (v, v) Source #

fromPair :: (v, v) -> Edge v () Source #

toTriple :: Edge v a -> (v, v, a) Source #

fromTriple :: (v, v, a) -> Edge v a Source #

isLoop :: Eq v => Edge v a -> Bool Source #

Main IsEdge instances

data Edge v e Source #

Undirected Edge with attribute of type e between to Vertices of type v

Constructors

Edge v v e 
Instances
IsEdge Edge Source # 
Instance details

Defined in Data.Graph.Types

Methods

originVertex :: Edge v a -> v Source #

destinationVertex :: Edge v a -> v Source #

attribute :: Edge v a -> a Source #

toPair :: Edge v a -> (v, v) Source #

fromPair :: (v, v) -> Edge v () Source #

toTriple :: Edge v a -> (v, v, a) Source #

fromTriple :: (v, v, a) -> Edge v a Source #

isLoop :: Eq v => Edge v a -> Bool Source #

Functor (Edge v) Source # 
Instance details

Defined in Data.Graph.Types

Methods

fmap :: (a -> b) -> Edge v a -> Edge v b #

(<$) :: a -> Edge v b -> Edge v a #

(Eq v, Eq a) => Eq (Edge v a) Source #

Two Edges are equal if they point to the same vertices, regardless of the direction

Instance details

Defined in Data.Graph.Types

Methods

(==) :: Edge v a -> Edge v a -> Bool #

(/=) :: Edge v a -> Edge v a -> Bool #

(Ord v, Ord e) => Ord (Edge v e) Source # 
Instance details

Defined in Data.Graph.Types

Methods

compare :: Edge v e -> Edge v e -> Ordering #

(<) :: Edge v e -> Edge v e -> Bool #

(<=) :: Edge v e -> Edge v e -> Bool #

(>) :: Edge v e -> Edge v e -> Bool #

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

max :: Edge v e -> Edge v e -> Edge v e #

min :: Edge v e -> Edge v e -> Edge v e #

(Read v, Read e) => Read (Edge v e) Source # 
Instance details

Defined in Data.Graph.Types

Methods

readsPrec :: Int -> ReadS (Edge v e) #

readList :: ReadS [Edge v e] #

readPrec :: ReadPrec (Edge v e) #

readListPrec :: ReadPrec [Edge v e] #

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

Defined in Data.Graph.Types

Methods

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

show :: Edge v e -> String #

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

Generic (Edge v e) Source # 
Instance details

Defined in Data.Graph.Types

Associated Types

type Rep (Edge v e) :: Type -> Type #

Methods

from :: Edge v e -> Rep (Edge v e) x #

to :: Rep (Edge v e) x -> Edge v e #

(Arbitrary v, Arbitrary e, Num v, Ord v) => Arbitrary (Edge v e) Source # 
Instance details

Defined in Data.Graph.Types

Methods

arbitrary :: Gen (Edge v e) #

shrink :: Edge v e -> [Edge v e] #

(NFData v, NFData e) => NFData (Edge v e) Source # 
Instance details

Defined in Data.Graph.Types

Methods

rnf :: Edge v e -> () #

type Rep (Edge v e) Source # 
Instance details

Defined in Data.Graph.Types

data Arc v e Source #

Directed Arc with attribute of type e between to Vertices of type v

Constructors

Arc v v e 
Instances
IsEdge Arc Source # 
Instance details

Defined in Data.Graph.Types

Methods

originVertex :: Arc v a -> v Source #

destinationVertex :: Arc v a -> v Source #

attribute :: Arc v a -> a Source #

toPair :: Arc v a -> (v, v) Source #

fromPair :: (v, v) -> Arc v () Source #

toTriple :: Arc v a -> (v, v, a) Source #

fromTriple :: (v, v, a) -> Arc v a Source #

isLoop :: Eq v => Arc v a -> Bool Source #

Functor (Arc v) Source # 
Instance details

Defined in Data.Graph.Types

Methods

fmap :: (a -> b) -> Arc v a -> Arc v b #

(<$) :: a -> Arc v b -> Arc v a #

(Eq v, Eq a) => Eq (Arc v a) Source #

Two Arcs are equal if they point to the same vertices, and the directions are the same

Instance details

Defined in Data.Graph.Types

Methods

(==) :: Arc v a -> Arc v a -> Bool #

(/=) :: Arc v a -> Arc v a -> Bool #

(Ord v, Ord e) => Ord (Arc v e) Source # 
Instance details

Defined in Data.Graph.Types

Methods

compare :: Arc v e -> Arc v e -> Ordering #

(<) :: Arc v e -> Arc v e -> Bool #

(<=) :: Arc v e -> Arc v e -> Bool #

(>) :: Arc v e -> Arc v e -> Bool #

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

max :: Arc v e -> Arc v e -> Arc v e #

min :: Arc v e -> Arc v e -> Arc v e #

(Read v, Read e) => Read (Arc v e) Source # 
Instance details

Defined in Data.Graph.Types

Methods

readsPrec :: Int -> ReadS (Arc v e) #

readList :: ReadS [Arc v e] #

readPrec :: ReadPrec (Arc v e) #

readListPrec :: ReadPrec [Arc v e] #

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

Defined in Data.Graph.Types

Methods

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

show :: Arc v e -> String #

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

Generic (Arc v e) Source # 
Instance details

Defined in Data.Graph.Types

Associated Types

type Rep (Arc v e) :: Type -> Type #

Methods

from :: Arc v e -> Rep (Arc v e) x #

to :: Rep (Arc v e) x -> Arc v e #

(Arbitrary v, Arbitrary e, Num v, Ord v) => Arbitrary (Arc v e) Source # 
Instance details

Defined in Data.Graph.Types

Methods

arbitrary :: Gen (Arc v e) #

shrink :: Arc v e -> [Arc v e] #

(NFData v, NFData e) => NFData (Arc v e) Source # 
Instance details

Defined in Data.Graph.Types

Methods

rnf :: Arc v e -> () #

type Rep (Arc v e) Source # 
Instance details

Defined in Data.Graph.Types

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

Methods

weight :: e -> Double Source #

Instances
Weighted Double Source # 
Instance details

Defined in Data.Graph.Types

Methods

weight :: Double -> Double Source #

Weighted Float Source # 
Instance details

Defined in Data.Graph.Types

Methods

weight :: Float -> Double Source #

Weighted Int Source # 
Instance details

Defined in Data.Graph.Types

Methods

weight :: Int -> Double Source #

Weighted (Double, String) Source # 
Instance details

Defined in Data.Graph.Types

Methods

weight :: (Double, String) -> Double Source #

class Labeled e where Source #

Edge attributes that represent labels

Methods

label :: e -> String Source #

Instances
Labeled String Source # 
Instance details

Defined in Data.Graph.Types

Methods

label :: String -> String Source #

Labeled (Double, String) Source # 
Instance details

Defined in Data.Graph.Types

Methods

label :: (Double, String) -> String Source #

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