Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Data.Graph.Graph
- newtype Graph v e = Graph {}
- newtype Probability = P Float
- probability :: Float -> Probability
- erdosRenyiIO :: Int -> Probability -> IO (Graph Int ())
- randomMatIO :: Int -> IO [[Int]]
- empty :: Hashable v => Graph v e
- insertVertex :: (Hashable v, Eq v) => v -> Graph v e -> Graph v e
- removeVertex :: (Hashable v, Eq v) => v -> Graph v e -> Graph v e
- insertVertices :: (Hashable v, Eq v) => [v] -> Graph v e -> Graph v e
- insertEdge :: (Hashable v, Eq v) => Edge v e -> Graph v e -> Graph v e
- insertEdges :: (Hashable v, Eq v) => [Edge v e] -> Graph v e -> Graph v e
- removeEdge :: (Hashable v, Eq v) => Edge v e -> Graph v e -> Graph v e
- removeEdge' :: (Hashable v, Eq v) => (v, v) -> Graph v e -> Graph v e
- removeEdgeAndVertices :: (Hashable v, Eq v) => Edge v e -> Graph v e -> Graph v e
- removeEdgeAndVertices' :: (Hashable v, Eq v) => (v, v) -> Graph v e -> Graph v e
- vertices :: Graph v e -> [v]
- order :: Graph v e -> Int
- size :: (Hashable v, Eq v) => Graph v e -> Int
- edges :: forall v e. (Hashable v, Eq v) => Graph v e -> [Edge v e]
- edges' :: (Hashable v, Eq v) => Graph v e -> [(v, v)]
- containsVertex :: (Hashable v, Eq v) => Graph v e -> v -> Bool
- containsEdge :: (Hashable v, Eq v) => Graph v e -> Edge v e -> Bool
- containsEdge' :: (Hashable v, Eq v) => Graph v e -> (v, v) -> Bool
- adjacentVertices :: (Hashable v, Eq v) => Graph v e -> v -> [v]
- incidentEdges :: (Hashable v, Eq v) => Graph v e -> v -> [Edge v e]
- vertexDegree :: (Hashable v, Eq v) => Graph v e -> v -> Int
- degrees :: (Hashable v, Eq v) => Graph v e -> [Int]
- maxDegree :: (Hashable v, Eq v) => Graph v e -> Int
- minDegree :: (Hashable v, Eq v) => Graph v e -> Int
- isLoop :: Eq v => Edge v e -> Bool
- isSimple :: (Hashable v, Eq v) => Graph v e -> Bool
- isRegular :: Graph v e -> Bool
- areIsomorphic :: Graph v e -> Graph v' e' -> Bool
- isomorphism :: Graph v e -> Graph v' e' -> v -> v'
- fromAdjacencyMatrix :: [[Int]] -> Maybe (Graph Int ())
- toAdjacencyMatrix :: Graph v e -> [[Int]]
- newtype DegreeSequence = DegreeSequence {
- unDegreeSequence :: [Int]
- degreeSequence :: [Int] -> DegreeSequence
- getDegreeSequence :: (Hashable v, Eq v) => Graph v e -> Maybe DegreeSequence
- isGraphicalSequence :: DegreeSequence -> Bool
- fromGraphicalSequence :: DegreeSequence -> Maybe (Graph Int ())
Documentation
Undirected Graph of Vertices in v and Edges with attributes in e
probability :: Float -> Probability Source #
Construct a Probability
value
erdosRenyiIO :: Int -> Probability -> IO (Graph Int ()) Source #
Generate a random Graph
of the Erdős–Rényi G(n, p) model
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
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
insertEdges :: (Hashable v, Eq v) => [Edge v e] -> Graph v e -> Graph v e Source #
O(m*log n)
Insert many directed Edge
s into a Graph
| Same rules as insertEdge
are applied
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) => (v, v) -> Graph v e -> Graph v e Source #
Same as removeEdgeAndVertices
but the edge is an unordered pair
order :: Graph v e -> Int Source #
O(n)
Retrieve the order of a Graph
| The order
of a graph is its number of vertices
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 Edge
s of a Vertex
vertexDegree :: (Hashable v, Eq v) => Graph v e -> v -> Int Source #
Degree of a vertex
| The total number incident Edge
s of a vertex
degrees :: (Hashable v, Eq v) => Graph v e -> [Int] Source #
Degrees of a all the vertices in a Graph
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
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
newtype DegreeSequence Source #
The Degree Sequence of a simple Graph
is a list of degrees
Constructors
DegreeSequence | |
Fields
|
Instances
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