graphite-0.0.2.0: Graphs and networks library

Safe HaskellSafe
LanguageHaskell2010

Data.Graph.DGraph

Synopsis

Documentation

newtype DGraph v e Source #

Directed Graph of Vertices in v and Arcs with attributes in e

Constructors

DGraph 

Fields

Instances

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

Methods

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

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

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

Methods

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

show :: DGraph v e -> String #

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

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

Methods

arbitrary :: Gen (DGraph v e) #

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

type DegreeSequence = [(Int, Int)] Source #

The Degree Sequence of a DGraph is a list of pairs (Indegree, Outdegree)

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

The Empty (order-zero) DGraph with no vertices and no arcs

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

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

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

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

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

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

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

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

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

O(m*log n) Insert many directed Arcs into a DGraph | Same rules as insertArc are applied

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

O(log n) Remove the directed Arc from a DGraph if present | The involved vertices are left untouched

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

Same as removeArc but the arc is an ordered pair

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

O(log n) Remove the directed Arc from a DGraph if present | The involved vertices are also removed

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

Same as removeArcAndVertices but the arc is an ordered pair

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

O(n) Retrieve the vertices of a DGraph

order :: DGraph v e -> Int Source #

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

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

O(n*m) Retrieve the size of a DGraph | The size of a directed graph is its number of Arcs

arcs :: forall v e. (Hashable v, Eq v) => DGraph v e -> [Arc v e] Source #

O(n*m) Retrieve the Arcs of a DGraph

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

Same as arcs but the arcs are ordered pairs, and their attributes are | discarded

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

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

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

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

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

Same as containsArc but the arc is an ordered pair

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

Retrieve the inbounding Arcs of a Vertex

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

Retrieve the outbounding Arcs of a Vertex

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

Retrieve the incident Arcs of a Vertex | Both inbounding and outbounding arcs

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

Retrieve the adjacent vertices of a vertex

isSymmetric :: DGraph v e -> Bool Source #

Tell if a DGraph is symmetric | All of its Arcs are bidirected

isOriented :: DGraph v e -> Bool Source #

Tell if a DGraph is oriented | There are none bidirected Arcs | Note: This is not the opposite of isSymmetric

isIsolated :: DGraph v e -> Bool Source #

Tell if a DGraph is isolated | A graph is isolated if it has no edges, that is, it has a degree of 0 | TODO: What if it has a loop?

vertexDegree :: DGraph v e -> v -> Int Source #

Degree of a vertex | The total number of inbounding and outbounding Arcs of a vertex

vertexIndegree :: DGraph v e -> v -> Int Source #

Indegree of a vertex | The number of inbounding Arcs to a vertex

vertexOutdegree :: DGraph v e -> v -> Int Source #

Outdegree of a vertex | The number of outbounding Arcs from a vertex

indegrees :: DGraph v e -> [Int] Source #

Indegrees of all the vertices in a DGraph

outdegrees :: DGraph v e -> [Int] Source #

Outdegree of all the vertices in a DGraph

isBalanced :: DGraph v e -> Bool Source #

Tell if a DGraph is balanced | A Directed Graph is balanced when its indegree = outdegree

isRegular :: DGraph v e -> Bool Source #

Tell if a DGraph is regular | A Directed Graph is regular when all of its vertices have the same number | of adjacent vertices AND when the indegree and outdegree of each vertex | are equal to each toher.

isSource :: DGraph v e -> v -> Bool Source #

Tell if a vertex is a source | A vertex is a source when its indegree = 0

isSink :: DGraph v e -> v -> Bool Source #

Tell if a vertex is a sink | A vertex is a sink when its outdegree = 0

isInternal :: DGraph v e -> v -> Bool Source #

Tell if a vertex is internal | A vertex is a internal when its neither a source nor a sink

isDirectedGraphic :: DegreeSequence -> Bool Source #

Tell if a DegreeSequence is a Directed Graphic | A Directed Graphic is a Degree Sequence for wich a DGraph exists TODO: Kleitman–Wang | Fulkerson–Chen–Anstee theorem algorithms