graphite-0.2.1.0: Graphs and networks library

Safe HaskellSafe
LanguageHaskell2010

Data.Graph.UGraph

Synopsis

Documentation

newtype UGraph v e Source #

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

Constructors

UGraph 

Fields

Instances

Graph UGraph Source # 

Methods

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

order :: UGraph v e -> Int Source #

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

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

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

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

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

density :: (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 #

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

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

removeEdgePair :: (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 #

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

isRegular :: UGraph v e -> Bool Source #

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

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

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

Methods

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

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

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

Methods

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

show :: UGraph v e -> String #

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

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

Methods

arbitrary :: Gen (UGraph v e) #

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

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

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

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

O(log n) Insert an undirected Edge into a UGraph | 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] -> UGraph v e -> UGraph v e Source #

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

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

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

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

Same as removeEdge but the edge is an unordered pair

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

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

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

Same as removeEdgeAndVertices but the edge is an unordered pair

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

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

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

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

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

Same as containsEdge but the edge is an unordered pair

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

Retrieve the incident Edges of a Vertex

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

Tell if two UGraph are isomorphic

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

degreeSequence :: [Int] -> DegreeSequence Source #

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

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

Get the DegreeSequence of a simple UGraph | 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 UGraph for | it exists

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

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