graphite-0.0.2.0: Graphs and networks library

Safe HaskellSafe
LanguageHaskell2010

Data.Graph.Graph

Synopsis

Documentation

newtype Graph v e Source #

Undirected Graph of Vertices in v and Edges with attributes in e

Constructors

Graph 

Fields

Instances

(Eq e, Eq v) => Eq (Graph v e) Source # 

Methods

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

(/=) :: Graph v e -> Graph v e -> Bool #

(Show e, Show v) => Show (Graph v e) Source # 

Methods

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

show :: Graph v e -> String #

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

(Arbitrary v, Arbitrary e, Hashable v, Num v, Ord v) => Arbitrary (Graph v e) Source # 

Methods

arbitrary :: Gen (Graph v e) #

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

erdosRenyiIO :: Int -> Probability -> IO (Graph Int ()) Source #

Generate a random Graph of the Erdős–Rényi G(n, p) model

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

The Empty (order-zero) Graph with no vertices and no edges

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

O(log n) Insert a vertex into a Graph | If the graph already contains the vertex leave the graph untouched

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

O(n) Remove a vertex from a Graph if present | Every Edge incident to this vertex is also removed

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

O(m*log n) Insert a many vertices into a Graph | New vertices are inserted and already contained vertices are left untouched

insertEdge :: (Hashable v, Eq v) => Edge v e -> Graph v e -> Graph v e Source #

O(log n) Insert an undirected Edge into a Graph | The involved vertices are inserted if don't exist. If the graph already | contains the Edge, its attribute is updated

insertEdges :: (Hashable v, Eq v) => [Edge v e] -> Graph v e -> Graph v e Source #

O(m*log n) Insert many directed Edges into a Graph | Same rules as insertEdge are applied

removeEdge :: (Hashable v, Eq v) => Edge v e -> Graph v e -> Graph v e Source #

O(log n) Remove the undirected Edge from a Graph if present | The involved vertices are left untouched

removeEdge' :: (Hashable v, Eq v) => (v, v) -> Graph v e -> Graph v e Source #

Same as removeEdge but the edge is an unordered pair

removeEdgeAndVertices :: (Hashable v, Eq v) => Edge v e -> Graph v e -> Graph v e Source #

O(log n) Remove the undirected Edge from a Graph if present | The involved vertices are also removed

removeEdgeAndVertices' :: (Hashable v, Eq v) => (v, v) -> Graph v e -> Graph v e Source #

Same as removeEdgeAndVertices but the edge is an unordered pair

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

O(n) Retrieve the vertices of a Graph

order :: Graph v e -> Int Source #

O(n) Retrieve the order of a Graph | The order of a graph is its number of vertices

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

O(n*m) Retrieve the size of a Graph | The size of an undirected graph is its number of Edges

edges :: forall v e. (Hashable v, Eq v) => Graph v e -> [Edge v e] Source #

O(n*m) Retrieve the Edges of a Graph

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

Same as edges but the edges are unordered pairs, and their attributes | are discarded

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

O(log n) Tell if a vertex exists in the graph

containsEdge :: (Hashable v, Eq v) => Graph v e -> Edge v e -> Bool Source #

O(log n) Tell if an undirected Edge exists in the graph

containsEdge' :: (Hashable v, Eq v) => Graph v e -> (v, v) -> Bool Source #

Same as containsEdge but the edge is an unordered pair

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

Retrieve the adjacent vertices of a vertex

incidentEdges :: (Hashable v, Eq v) => Graph v e -> v -> [Edge v e] Source #

Retrieve the incident Edges of a Vertex

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

Degree of a vertex | The total number incident Edges of a vertex

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

Degrees of a all the vertices in a Graph

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

Maximum degree of a Graph

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

Minimum degree of a Graph

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

Tell if an Edge forms a loop | An Edge forms a loop with both of its ends point to the same vertex

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

Tell if a Graph is simple | A Graph is simple if it has no multiple edges nor loops

isRegular :: Graph v e -> Bool Source #

Tell if a Graph is regular | An Undirected Graph is regular when all of its vertices have the same | number of adjacent vertices

areIsomorphic :: Graph v e -> Graph v' e' -> Bool Source #

Tell if two Graphs are isomorphic

isomorphism :: Graph v e -> Graph v' e' -> v -> v' Source #

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

Generate a directed Graph of Int vertices from an adjacency | square matrix

toAdjacencyMatrix :: Graph v e -> [[Int]] Source #

Get the adjacency matrix representation of a directed Graph

degreeSequence :: [Int] -> DegreeSequence Source #

Construct a DegreeSequence from a list of degrees | Negative degree values are discarded

getDegreeSequence :: (Hashable v, Eq v) => Graph v e -> Maybe DegreeSequence Source #

Get the DegreeSequence of a simple Graph | If the graph is not simple (see isSimple) the result is Nothing

isGraphicalSequence :: DegreeSequence -> Bool Source #

Tell if a DegreeSequence is a Graphical Sequence | A Degree Sequence is a Graphical Sequence if a corresponding Graph for | it exists

fromGraphicalSequence :: DegreeSequence -> Maybe (Graph Int ()) Source #

Get the corresponding Graph of a DegreeSequence | If the DegreeSequence is not graphical (see isGraphicalSequence) the | result is Nothing