graphite-0.3.0.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

Graph DGraph Source # 

Methods

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

order :: DGraph v e -> Int Source #

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

vertices :: DGraph v e -> [v] 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 #

directlyReachableVertices :: (Hashable v, Eq v) => DGraph v e -> v -> [v] 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 #

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

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

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

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

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

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

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

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

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

isRegular :: DGraph v e -> Bool Source #

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

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

(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)

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

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) => DGraph v e -> Arc 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) => DGraph v e -> (v, v) -> DGraph v e Source #

Same as removeArc but the arc is an ordered pair

removeArcAndVertices :: (Hashable v, Eq v) => DGraph v e -> Arc 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) => DGraph v e -> (v, v) -> DGraph v e Source #

Same as removeArcAndVertices but the arc is an ordered pair

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

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

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

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

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

Convert a directed DGraph to an undirected UGraph by converting all of | its Arcs into Edges

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