graphite-0.10.0.1: Graphs and networks library

Safe HaskellSafe
LanguageHaskell2010

Data.Graph.DGraph

Contents

Synopsis

DGraph data type

data DGraph v e Source #

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

Instances
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 #

(Hashable v, Eq v) => Functor (DGraph v) Source # 
Instance details

Defined in Data.Graph.DGraph

Methods

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

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

(Hashable v, Eq v) => Foldable (DGraph v) Source # 
Instance details

Defined in Data.Graph.DGraph

Methods

fold :: Monoid m => DGraph v m -> m #

foldMap :: Monoid m => (a -> m) -> DGraph v a -> m #

foldr :: (a -> b -> b) -> b -> DGraph v a -> b #

foldr' :: (a -> b -> b) -> b -> DGraph v a -> b #

foldl :: (b -> a -> b) -> b -> DGraph v a -> b #

foldl' :: (b -> a -> b) -> b -> DGraph v a -> b #

foldr1 :: (a -> a -> a) -> DGraph v a -> a #

foldl1 :: (a -> a -> a) -> DGraph v a -> a #

toList :: DGraph v a -> [a] #

null :: DGraph v a -> Bool #

length :: DGraph v a -> Int #

elem :: Eq a => a -> DGraph v a -> Bool #

maximum :: Ord a => DGraph v a -> a #

minimum :: Ord a => DGraph v a -> a #

sum :: Num a => DGraph v a -> a #

product :: Num a => DGraph v a -> a #

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

Defined in Data.Graph.DGraph

Methods

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

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

(Hashable v, Eq v, Read v, Read e) => Read (DGraph v e) Source # 
Instance details

Defined in Data.Graph.DGraph

(Hashable v, Eq v, Show v, Show e) => Show (DGraph v e) Source # 
Instance details

Defined in Data.Graph.DGraph

Methods

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

show :: DGraph v e -> String #

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

Generic (DGraph v e) Source # 
Instance details

Defined in Data.Graph.DGraph

Associated Types

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

Methods

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

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

(Hashable v, Eq v) => Semigroup (DGraph v e) Source # 
Instance details

Defined in Data.Graph.DGraph

Methods

(<>) :: DGraph v e -> DGraph v e -> DGraph v e #

sconcat :: NonEmpty (DGraph v e) -> DGraph v e #

stimes :: Integral b => b -> DGraph v e -> DGraph v e #

(Hashable v, Eq v) => Monoid (DGraph v e) Source # 
Instance details

Defined in Data.Graph.DGraph

Methods

mempty :: DGraph v e #

mappend :: DGraph v e -> DGraph v e -> DGraph v e #

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

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

Defined in Data.Graph.DGraph

Methods

arbitrary :: Gen (DGraph v e) #

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

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

Defined in Data.Graph.DGraph

Methods

rnf :: DGraph v e -> () #

type Rep (DGraph v e) Source # 
Instance details

Defined in Data.Graph.DGraph

type Rep (DGraph v e)

Functions on DGraph

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

Insert a directed Arc into a DGraph

The involved vertices are inserted if they don't exist. If the graph already contains the Arc, its attribute gets updated

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

Same as insertArc but for a list of Arcs

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

Remove the directed Arc from a DGraph if present. The involved vertices are left untouched

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

Same as removeArc but for a list of Arcs

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

Remove the directed Arc from a DGraph if present. The involved vertices also get removed

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

Retrieve the Arcs of a DGraph

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

Tell if a directed Arc exists in the graph

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

The incident arcs of a vertex are all the inbounding and outbounding arcs of the vertex

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

Indegree of a vertex

The indegree of a vertex is the number of inbounding Arcs to a vertex

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

Outdegree of a vertex

The outdegree of a vertex is the number of outbounding Arcs from a vertex

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

Indegrees of all the vertices in a DGraph

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

Outdegree of all the vertices in a DGraph

Query graph properties and characteristics

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

Tell if a DGraph is balanced

A directed graph is balanced when its indegree = outdegree

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

Tell if a vertex is a source

A vertex is a source when its indegree = 0

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

Tell if a vertex is a sink

A vertex is a sink when its outdegree = 0

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

Tell if a vertex is internal

A vertex is internal when its neither a source nor a sink

Transformations

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

Get the transpose of a DGraph

The transpose of a directed graph is another directed graph where all of its arcs are reversed

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

List conversions

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

Convert a DGraph to a list of Arcs discarding isolated vertices

Note that because toArcsList discards isolated vertices:

fromArcsList . toArcsList /= id

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

Construct a DGraph from a list of Arcs

Pretty printing

prettyPrint :: (Hashable v, Eq v, Show v, Show e) => DGraph v e -> String Source #

Pretty print a DGraph