igraph-0.1.1: Bindings to the igraph C library.

Safe HaskellNone

Data.IGraph

Contents

Description

Haskell bindings to the igraph C library.

Function descriptions have been copied from http://igraph.sourceforge.net/doc/html/index.html from the specified sections.

Synopsis

Basic types

data Graph d a whereSource

The internal graph representation wrapped into a GADT to carry around the E d a class constraint.

Constructors

G :: E d a => G d a -> Graph d a 

Instances

Eq (Edge d a) => Eq (Graph (Weighted d) a) 
Eq (Graph D a) 
Eq (Graph U a) 
Show (Edge d a) => Show (Graph (Weighted d) a) 
Show a => Show (Graph D a) 
Show a => Show (Graph U a) 

data D Source

Directed graph

Instances

IsDirected D 
IsUnweighted D 
(Eq a, Hashable a) => E D a 
IsDirected (Weighted D) 
Eq a => Eq (Edge D a) 
Eq (Graph D a) 
Ord a => Ord (Edge D a) 
Show a => Show (Edge D a) 
Show a => Show (Graph D a) 
Hashable a => Hashable (Edge D a) 

data U Source

Undirected graph

Instances

IsUndirected U 
IsUnweighted U 
(Eq a, Hashable a) => E U a 
IsUndirected (Weighted U) 
Eq a => Eq (Edge U a) 
Eq (Graph U a) 
Ord a => Ord (Edge U a) 
Show a => Show (Edge U a) 
Show a => Show (Graph U a) 
Hashable a => Hashable (Edge U a) 

class (Eq a, Hashable a, Eq (Edge d a), Hashable (Edge d a)) => E d a whereSource

Class for graph edges, particularly for undirected edges Edge U a and directed edges Edge D a and weighted edges.

Associated Types

data Edge d a Source

Methods

isDirected :: Graph d a -> BoolSource

isWeighted :: Graph d a -> BoolSource

toEdge :: a -> a -> Edge d aSource

edgeFrom :: Edge d a -> aSource

edgeTo :: Edge d a -> aSource

edgeWeight :: Edge d a -> Maybe IntSource

Instances

(Eq a, Hashable a) => E D a 
(Eq a, Hashable a) => E U a 
(E d a, IsUnweighted d) => E (Weighted d) a 

data Weighted d Source

Weighted graphs, weight defaults to 0

Instances

IsUndirected (Weighted U) 
IsDirected (Weighted D) 
(E d a, IsUnweighted d) => E (Weighted d) a 
E d a => Eq (Edge (Weighted d) a) 
Eq (Edge d a) => Eq (Graph (Weighted d) a) 
(E d a, Ord (Edge d a)) => Ord (Edge (Weighted d) a) 
Show (Edge d a) => Show (Edge (Weighted d) a) 
Show (Edge d a) => Show (Graph (Weighted d) a) 
E d a => Hashable (Edge (Weighted d) a) 

toEdgeWeighted :: E d a => a -> a -> Int -> Edge (Weighted d) aSource

class IsUndirected u Source

Associated Types

type ToDirected u Source

class IsDirected d Source

Associated Types

type ToUndirected d Source

Pure Haskell functions

These functions do not depend on the C library and perform no FFI calls.

Construction / modification

emptyGraph :: E d a => Graph d aSource

fromList :: E d a => [(a, a)] -> Graph d aSource

fromListWeighted :: (E d a, IsUnweighted d) => [(a, a, Int)] -> Graph (Weighted d) aSource

insertEdge :: Edge d a -> Graph d a -> Graph d aSource

deleteEdge :: Edge d a -> Graph d a -> Graph d aSource

deleteNode :: a -> Graph d a -> Graph d aSource

reverseGraphDirection :: Graph d a -> Graph d aSource

Reverse graph direction. This simply changes the associated igraph_neimode_t of the graph (IGRAPH_OUT to IGRAPH_IN, IGRAPH_IN to IGRAPH_OUT, other to IGRAPH_OUT). O(1)

Query

member :: a -> Graph d a -> BoolSource

nodes :: Graph d a -> [a]Source

edges :: Graph d a -> [Edge d a]Source

neighbours :: a -> Graph d a -> [a]Source

Chapter 11. Vertex and Edge Selectors and Sequences, Iterators

11.2 Vertex selector constructors

data VertexSelector a Source

Constructors

VsAll 
VsNone 
Vs1 a 
VsList [a] 
VsAdj a 
VsNonAdj a 

11.3 Generic vertex selector operations

vsSize :: Graph d a -> VertexSelector a -> IntSource

3.4. igraph_vs_size — Returns the size of the vertex selector.

11.6 Edge selector constructors

data EdgeSelector d a Source

Constructors

EsAll 
EsNone 
EsIncident a 
EsSeq a a 
EsFromTo (VertexSelector a) (VertexSelector a) 
Es1 (Edge d a) 
EsList [Edge d a] 

11.8 Generic edge selector operations

esSize :: Graph d a -> EdgeSelector d a -> IntSource

8.4. igraph_es_size — Returns the size of the edge selector.

Chapter 13. Structural Properties of Graphs

13.1 Basic properties

areConnected :: Graph d a -> a -> a -> BoolSource

1.1. igraph_are_connected — Decides whether two vertices are connected

13.2 Shortest Path Related Functions

shortestPaths :: (Ord a, Hashable a) => Graph d a -> VertexSelector a -> VertexSelector a -> Map (a, a) (Maybe Int)Source

2.1. igraph_shortest_paths — The length of the shortest paths between vertices.

shortestPathsDijkstra :: (Ord a, Hashable a) => Graph (Weighted d) a -> VertexSelector a -> VertexSelector a -> Map (a, a) (Maybe Int)Source

2.2. igraph_shortest_paths_dijkstra — Weighted shortest paths from some sources.

This function is Dijkstra's algorithm to find the weighted shortest paths to all vertices from a single source. (It is run independently for the given sources.) It uses a binary heap for efficient implementation.

shortestPathsBellmanFord :: (Ord a, Hashable a) => Graph (Weighted d) a -> VertexSelector a -> VertexSelector a -> Map (a, a) (Maybe Int)Source

2.3. igraph_shortest_paths_bellman_ford — Weighted shortest paths from some sources allowing negative weights.

This function is the Bellman-Ford algorithm to find the weighted shortest paths to all vertices from a single source. (It is run independently for the given sources.). If there are no negative weights, you are better off with igraph_shortest_paths_dijkstra() .

shortestPathsJohnson :: (Ord a, Hashable a) => Graph (Weighted d) a -> VertexSelector a -> VertexSelector a -> Map (a, a) (Maybe Int)Source

2.4. igraph_shortest_paths_johnson — Calculate shortest paths from some sources using Johnson's algorithm.

See Wikipedia at http:en.wikipedia.orgwikiJohnson's_algorithm for Johnson's algorithm. This algorithm works even if the graph contains negative edge weights, and it is worth using it if we calculate the shortest paths from many sources.

If no edge weights are supplied, then the unweighted version, igraph_shortest_paths() is called.

If all the supplied edge weights are non-negative, then Dijkstra's algorithm is used by calling igraph_shortest_paths_dijkstra().

getShortestPathsSource

Arguments

:: Graph d a 
-> a

from

-> VertexSelector a

to

-> [([a], [Edge d a])]

list of (vertices, edges)

2.5. igraph_get_shortest_paths — Calculates the shortest paths from/to one vertex.

If there is more than one geodesic between two vertices, this function gives only one of them.

getShortestPathsDijkstraSource

Arguments

:: Graph (Weighted d) a 
-> a

from

-> VertexSelector a

to

-> [([a], [Edge (Weighted d) a])]

list of (vertices, edges)

2.7. igraph_get_shortest_paths_dijkstra — Calculates the weighted shortest paths from/to one vertex.

If there is more than one path with the smallest weight between two vertices, this function gives only one of them.

getShortestPath :: Graph d a -> a -> a -> ([a], [Edge d a])Source

2.6. igraph_get_shortest_path — Shortest path from one vertex to another one.

Calculates and returns a single unweighted shortest path from a given vertex to another one. If there are more than one shortest paths between the two vertices, then an arbitrary one is returned.

This function is a wrapper to igraph_get_shortest_paths(), for the special case when only one target vertex is considered.

getShortestPathDijkstra :: Graph (Weighted d) a -> a -> a -> ([a], [Edge (Weighted d) a])Source

2.8. igraph_get_shortest_path_dijkstra — Weighted shortest path from one vertex to another one.

Calculates a single (positively) weighted shortest path from a single vertex to another one, using Dijkstra's algorithm.

This function is a special case (and a wrapper) to igraph_get_shortest_paths_dijkstra().

getAllShortestPathsSource

Arguments

:: Graph d a 
-> a

from

-> VertexSelector a

to

-> [[a]]

list of vertices along the shortest path from from to each other (reachable) vertex

2.9. igraph_get_all_shortest_paths — Finds all shortest paths (geodesics) from a vertex to all other vertices.

getAllShortestPathsDijkstraSource

Arguments

:: Graph (Weighted d) a 
-> a

from

-> VertexSelector a

to

-> [[a]]

list of vertices along the shortest path from from to each other (reachable) vertex

2.10. igraph_get_all_shortest_paths_dijkstra — Finds all shortest paths (geodesics) from a vertex to all other vertices.

averagePathLengthSource

Arguments

:: Graph d a 
-> Bool

Boolean, whether to consider directed paths. Ignored for undirected graphs.

-> Bool

What to do if the graph is not connected. If TRUE the average of the geodesics within the components will be returned, otherwise the number of vertices is used for the length of non-existing geodesics. (The rationale behind this is that this is always longer than the longest possible geodesic in a graph.)

-> Double 

2.11. igraph_average_path_length — Calculates the average geodesic length in a graph.

pathLengthHistSource

Arguments

:: Graph d a 
-> Bool

Whether to consider directed paths in a directed graph (if not zero). This argument is ignored for undirected graphs.

-> ([Double], Double) 

2.12. igraph_path_length_hist — Create a histogram of all shortest path lengths.

This function calculates a histogram, by calculating the shortest path length between each pair of vertices. For directed graphs both directions might be considered and then every pair of vertices appears twice in the histogram.

diameterSource

Arguments

:: Graph d a 
-> Bool 
-> Bool 
-> (Int, (a, a), [a])

the diameter of the graph, the starting/end vertices and the longest path

2.13. igraph_diameter — Calculates the diameter of a graph (longest geodesic).

diameterDijkstraSource

Arguments

:: Graph d a 
-> (Double, a, a, [a])

(diameter, source vertex, target vertex, path)

2.14. igraph_diameter_dijkstra — Weighted diameter using Dijkstra's algorithm, non-negative weights only.

The diameter of a graph is its longest geodesic. I.e. the (weighted) shortest path is calculated for all pairs of vertices and the longest one is the diameter.

girthSource

Arguments

:: Graph d a 
-> (Int, [a])

girth with the shortest circle

2.15. igraph_girth — The girth of a graph is the length of the shortest circle in it.

The current implementation works for undirected graphs only, directed graphs are treated as undirected graphs. Loop edges and multiple edges are ignored.

If the graph is a forest (ie. acyclic), then zero is returned.

This implementation is based on Alon Itai and Michael Rodeh: Finding a minimum circuit in a graph Proceedings of the ninth annual ACM symposium on Theory of computing , 1-10, 1977. The first implementation of this function was done by Keith Briggs, thanks Keith.

eccentricity :: Graph d a -> VertexSelector a -> [(a, Int)]Source

2.16. igraph_eccentricity — Eccentricity of some vertices

The eccentricity of a vertex is calculated by measuring the shortest distance from (or to) the vertex, to (or from) all vertices in the graph, and taking the maximum.

This implementation ignores vertex pairs that are in different components. Isolated vertices have eccentricity zero.

radius :: Graph d a -> IntSource

2.17. igraph_radius — Radius of a graph

The radius of a graph is the defined as the minimum eccentricity of its vertices, see igraph_eccentricity().

13.4 Graph Components

Note that there currently is an issue with GHCi and shared libraries on x86_64 linux systems which will cause an error in those functions that return graphs (e.g. inducedSubgraph). See GHC Ticket #781 (http://hackage.haskell.org/trac/ghc/ticket/781). Statically compiling your program or installing this module (and all it's dependencies) with -fPIC should fix this issue.

subcomponent :: Graph d a -> a -> [a]Source

4.1. igraph_subcomponent — The vertices in the same component as a given vertex.

inducedSubgraph :: Graph d a -> VertexSelector a -> SubgraphImplementation -> Graph d aSource

4.2. igraph_induced_subgraph — Creates a subgraph induced by the specified vertices.

This function collects the specified vertices and all edges between them to a new graph. As the vertex ids in a graph always start with zero, this function very likely needs to reassign ids to the vertices.

subgraphEdges :: Graph d a -> EdgeSelector d a -> Graph d aSource

4.3. igraph_subgraph_edges — Creates a subgraph with the specified edges and their endpoints.

This function collects the specified edges and their endpoints to a new graph. As the vertex ids in a graph always start with zero, this function very likely needs to reassign ids to the vertices.

clustersSource

Arguments

:: Graph d a 
-> Connectedness 
-> (Int, [Int])

(number of clusters, list of size of all clusters)

4.5. igraph_clusters — Calculates the (weakly or strongly) connected components in a graph.

isConnected :: Graph d a -> Connectedness -> BoolSource

4.6. igraph_is_connected — Decides whether the graph is (weakly or strongly) connected.

A graph with zero vertices (i.e. the null graph) is connected by definition.

decompose :: Graph d a -> Connectedness -> Int -> Int -> [Graph d a]Source

4.7. igraph_decompose — Decompose a graph into connected components.

Create separate graph for each component of a graph. Note that the vertex ids in the new graphs will be different than in the original graph. (Except if there is only one component in the original graph.)

biconnectedComponentsSource

Arguments

:: Graph d a 
-> (Int, [[Edge d a]], [[Edge d a]], [[a]], [a])

(number of biconnected components, edges of spanning trees, edges of biconnected components, vertices of biconnected components, articulation points of the graph)

4.9. igraph_biconnected_components — Calculate biconnected components

A graph is biconnected if the removal of any single vertex (and its incident edges) does not disconnect it.

A biconnected component of a graph is a maximal biconnected subgraph of it. The biconnected components of a graph can be given by the partition of its edges: every edge is a member of exactly one biconnected component. Note that this is not true for vertices: the same vertex can be part of many biconnected components.

articulationPoints :: Graph d a -> [a]Source

4.10. igraph_articulation_points — Find the articulation points in a graph.

A vertex is an articulation point if its removal increases the number of connected components in the graph.

13.5 Centrality Measures

closeness :: Ord a => Graph d a -> VertexSelector a -> Map a DoubleSource

5.1. igraph_closeness — Closeness centrality calculations for some vertices.

The closeness centrality of a vertex measures how easily other vertices can be reached from it (or the other way: how easily it can be reached from the other vertices). It is defined as the number of the number of vertices minus one divided by the sum of the lengths of all geodesics from/to the given vertex.

If the graph is not connected, and there is no path between two vertices, the number of vertices is used instead the length of the geodesic. This is always longer than the longest possible geodesic.

betweenness :: Ord a => Graph d a -> VertexSelector a -> Map a DoubleSource

5.2. igraph_betweenness — Betweenness centrality of some vertices.

The betweenness centrality of a vertex is the number of geodesics going through it. If there are more than one geodesic between two vertices, the value of these geodesics are weighted by one over the number of geodesics.

edgeBetweenness :: Ord (Edge d a) => Graph d a -> Map (Edge d a) DoubleSource

5.3. igraph_edge_betweenness — Betweenness centrality of the edges.

The betweenness centrality of an edge is the number of geodesics going through it. If there are more than one geodesics between two vertices, the value of these geodesics are weighted by one over the number of geodesics.

pagerankSource

Arguments

:: Graph d a 
-> VertexSelector a 
-> Double

The damping factor (d in the original paper)

-> (Double, [(a, Double)]) 

5.4. igraph_pagerank — Calculates the Google PageRank for the specified vertices.

personalizedPagerankSource

Arguments

:: Graph d a 
-> VertexSelector a 
-> Double

The damping factor (d in the original paper)

-> (Double, [(a, Double)]) 

5.6. igraph_personalized_pagerank — Calculates the personalized Google PageRank for the specified vertices.

personalizedPagerankVsSource

Arguments

:: Graph d a 
-> VertexSelector a 
-> Double

The damping factor (d in the original paper)

-> VertexSelector a

IDs of the vertices used when resetting the random walk.

-> (Double, [(a, Double)]) 

5.7. igraph_personalized_pagerank_vs — Calculates the personalized Google PageRank for the specified vertices.

constraint :: Ord a => Graph d a -> VertexSelector a -> Map a DoubleSource

5.8. igraph_constraint — Burt's constraint scores.

This function calculates Burt's constraint scores for the given vertices, also known as structural holes.

Burt's constraint is higher if ego has less, or mutually stronger related (i.e. more redundant) contacts. Burt's measure of constraint, C[i], of vertex i's ego network V[i], is defined for directed and valued graphs,

C[i] = sum( sum( (p[i,q] p[q,j])^2, q in V[i], q != i,j ), j in V[], j != i)

for a graph of order (ie. number of vertices) N, where proportional tie strengths are defined as

p[i,j]=(a[i,j]+a[j,i]) / sum(a[i,k]+a[k,i], k in V[i], k != i),

a[i,j] are elements of A and the latter being the graph adjacency matrix. For isolated vertices, constraint is undefined.

Burt, R.S. (2004). Structural holes and good ideas. American Journal of Sociology 110, 349-399.

The first R version of this function was contributed by Jeroen Bruggeman.

maxdegreeSource

Arguments

:: Graph d a 
-> VertexSelector a 
-> Bool

count self-loops?

-> Int 

5.9. igraph_maxdegree — Calculate the maximum degree in a graph (or set of vertices).

The largest in-, out- or total degree of the specified vertices is calculated.

strengthSource

Arguments

:: Ord a 
=> Graph d a 
-> VertexSelector a 
-> Bool

count self-loops?

-> Map a Int 

5.10. igraph_strength — Strength of the vertices, weighted vertex degree in other words.

In a weighted network the strength of a vertex is the sum of the weights of all incident edges. In a non-weighted network this is exactly the vertex degree.

eigenvectorCentralitySource

Arguments

:: Graph d a 
-> Bool

If True the result will be scaled such that the absolute value of the maximum centrality is one.

-> (Double, [(a, Double)]) 

5.11. igraph_eigenvector_centrality — Eigenvector centrality of the vertices

hubScoreSource

Arguments

:: Graph d a 
-> Bool

If True then the result will be scaled such that the absolute value of the maximum centrality is one.

-> (Double, [(a, Double)]) 

5.12. igraph_hub_score — Kleinberg's hub scores

authorityScoreSource

Arguments

:: Graph d a 
-> Bool

If True then the result will be scaled such that the absolute value of the maximum centrality is one.

-> (Double, [(a, Double)]) 

5.13. igraph_authority_score — Kleinerg's authority scores

13.6 Estimating Centrality Measures

closenessEstimateSource

Arguments

:: Ord a 
=> Graph d a 
-> VertexSelector a 
-> Int

cutoff

-> Map a Double 

6.1. igraph_closeness_estimate — Closeness centrality estimations for some vertices.

The closeness centrality of a vertex measures how easily other vertices can be reached from it (or the other way: how easily it can be reached from the other vertices). It is defined as the number of the number of vertices minus one divided by the sum of the lengths of all geodesics from/to the given vertex. When estimating closeness centrality, igraph considers paths having a length less than or equal to a prescribed cutoff value.

If the graph is not connected, and there is no such path between two vertices, the number of vertices is used instead the length of the geodesic. This is always longer than the longest possible geodesic.

Since the estimation considers vertex pairs with a distance greater than the given value as disconnected, the resulting estimation will always be lower than the actual closeness centrality.

betweennessEstimateSource

Arguments

:: Ord a 
=> Graph d a 
-> VertexSelector a 
-> Int

cutoff

-> Map a Double 

6.2. igraph_betweenness_estimate — Estimated betweenness centrality of some vertices.

The betweenness centrality of a vertex is the number of geodesics going through it. If there are more than one geodesic between two vertices, the value of these geodesics are weighted by one over the number of geodesics. When estimating betweenness centrality, igraph takes into consideration only those paths that are shorter than or equal to a prescribed length. Note that the estimated centrality will always be less than the real one.

edgeBetweennessEstimateSource

Arguments

:: Ord (Edge d a) 
=> Graph d a 
-> Int

cutoff

-> Map (Edge d a) Double 

6.3. igraph_edge_betweenness_estimate — Estimated betweenness centrality of the edges.

The betweenness centrality of an edge is the number of geodesics going through it. If there are more than one geodesics between two vertices, the value of these geodesics are weighted by one over the number of geodesics. When estimating betweenness centrality, igraph takes into consideration only those paths that are shorter than or equal to a prescribed length. Note that

13.7 Centralization

centralizationDegreeSource

Arguments

:: Ord a 
=> Graph d a 
-> Bool

consider loop edges?

-> Bool

normalize centralization score?

-> (Map a Double, Double, Double)

(node-level degree scores, centralization scores, theoretical max)

7.2. igraph_centralization_degree — Calculate vertex degree and graph centralization

This function calculates the degree of the vertices by passing its arguments to igraph_degree(); and it calculates the graph level centralization index based on the results by calling igraph_centralization().

centralizationBetweennessSource

Arguments

:: Ord a 
=> Graph d a 
-> Bool

normalize centralization score?

-> (Map a Double, Double, Double)

(node-level degree scores, centralization scores, theoretical max)

7.3. igraph_centralization_betweenness — Calculate vertex betweenness and graph centralization

This function calculates the betweenness centrality of the vertices by passing its arguments to igraph_betweenness(); and it calculates the graph level centralization index based on the results by calling igraph_centralization().

centralizationClosenessSource

Arguments

:: Ord a 
=> Graph d a 
-> Bool

normalize centralization score?

-> (Map a Double, Double, Double)

(node-level degree scores, centralization scores, theoretical max)

7.4. igraph_centralization_closeness — Calculate vertex closeness and graph centralization

This function calculates the closeness centrality of the vertices by passing its arguments to igraph_closeness(); and it calculates the graph level centralization index based on the results by calling igraph_centralization().

centralizationEigenvectorCentralitySource

Arguments

:: Graph d a 
-> Bool

If True then the result will be scaled, such that the absolute value of the maximum centrality is one.

-> Bool

Boolean, whether to calculate a normalized centralization score. See igraph_centralization() for how the normalization is done.

-> (Double, Double, Double)

(leading eigen-value, centralization score, theoretical max)

7.5. igraph_centralization_eigenvector_centrality — Calculate eigenvector centrality scores and graph centralization

This function calculates the eigenvector centrality of the vertices by passing its arguments to igraph_eigenvector_centrality); and it calculates the graph level centralization index based on the results by calling igraph_centralization().

centralizationDegreeTMaxSource

Arguments

:: Either (Graph d a) Int

either graph or number of nodes

-> Bool

consider loop edges?

-> Double 

7.6. igraph_centralization_degree_tmax — Theoretical maximum for graph centralization based on degree

This function returns the theoretical maximum graph centrality based on vertex degree.

There are two ways to call this function, the first is to supply a graph as the graph argument, and then the number of vertices is taken from this object, and its directedness is considered as well. The nodes argument is ignored in this case. The mode argument is also ignored if the supplied graph is undirected.

The other way is to supply a null pointer as the graph argument. In this case the nodes and mode arguments are considered.

The most centralized structure is the star. More specifically, for undirected graphs it is the star, for directed graphs it is the in-star or the out-star.

centralizationBetweennessTMax :: Either (Graph d a) Int -> DoubleSource

7.7. igraph_centralization_betweenness_tmax — Theoretical maximum for graph centralization based on betweenness

This function returns the theoretical maximum graph centrality based on vertex betweenness.

There are two ways to call this function, the first is to supply a graph as the graph argument, and then the number of vertices is taken from this object, and its directedness is considered as well. The nodes argument is ignored in this case. The directed argument is also ignored if the supplied graph is undirected.

The other way is to supply a null pointer as the graph argument. In this case the nodes and directed arguments are considered.

The most centralized structure is the star.

centralizationClosenessTMax :: Either (Graph d a) Int -> DoubleSource

7.8. igraph_centralization_closeness_tmax — Theoretical maximum for graph centralization based on closeness

This function returns the theoretical maximum graph centrality based on vertex closeness.

There are two ways to call this function, the first is to supply a graph as the graph argument, and then the number of vertices is taken from this object, and its directedness is considered as well. The nodes argument is ignored in this case. The mode argument is also ignored if the supplied graph is undirected.

The other way is to supply a null pointer as the graph argument. In this case the nodes and mode arguments are considered.

The most centralized structure is the star.

centralizationEigenvectorCentralityTMaxSource

Arguments

:: Either (Graph d a) Int 
-> Bool

Whether to consider edge directions. This argument is ignored if graph is not a null pointer and it is undirected

-> Bool

Whether to rescale the node-level centrality scores to have a maximum of one

-> Double 

7.9. igraph_centralization_eigenvector_centrality_tmax — Theoretical maximum centralization for eigenvector centrality

This function returns the theoretical maximum graph centrality based on vertex eigenvector centrality.

There are two ways to call this function, the first is to supply a graph as the graph argument, and then the number of vertices is taken from this object, and its directedness is considered as well. The nodes argument is ignored in this case. The directed argument is also ignored if the supplied graph is undirected.

The other way is to supply a null pointer as the graph argument. In this case the nodes and directed arguments are considered.

The most centralized directed structure is the in-star. The most centralized undirected structure is the graph with a single edge.

13.8 Similarity Measures

bibCoupling :: Graph d a -> VertexSelector a -> [(a, [(a, Int)])]Source

8.1. igraph_bibcoupling — Bibliographic coupling.

The bibliographic coupling of two vertices is the number of other vertices they both cite, `igraph_bibcoupling()` calculates this. The bibliographic coupling score for each given vertex and all other vertices in the graph will be calculated.

cocitation :: Graph d a -> VertexSelector a -> [(a, [(a, Int)])]Source

8.2. igraph_cocitation — Cocitation coupling.

Two vertices are cocited if there is another vertex citing both of them. `igraph_cocitation()` simply counts how many times two vertices are cocited. The cocitation score for each given vertex and all other vertices in the graph will be calculated.

similarityJaccardSource

Arguments

:: Graph d a 
-> VertexSelector a 
-> Bool

Whether to include the vertices themselves in the neighbor sets

-> [(a, [(a, Double)])] 

8.3. igraph_similarity_jaccard — Jaccard similarity coefficient for the given vertices.

The Jaccard similarity coefficient of two vertices is the number of common neighbors divided by the number of vertices that are neighbors of at least one of the two vertices being considered. This function calculates the pairwise Jaccard similarities for some (or all) of the vertices.

similarityJaccardPairsSource

Arguments

:: Graph d a 
-> [Edge d a] 
-> Bool

Whether to include the vertices themselves in the neighbor sets

-> [(Edge d a, Double)] 

8.4. igraph_similarity_jaccard_pairs — Jaccard similarity coefficient for given vertex pairs.

The Jaccard similarity coefficient of two vertices is the number of common neighbors divided by the number of vertices that are neighbors of at least one of the two vertices being considered. This function calculates the pairwise Jaccard similarities for a list of vertex pairs.

similarityJaccardEsSource

Arguments

:: Graph d a 
-> EdgeSelector d a 
-> Bool

Whether to include the vertices themselves in the neighbor sets

-> [(Edge d a, Double)] 

8.5. igraph_similarity_jaccard_es — Jaccard similarity coefficient for a given edge selector.

The Jaccard similarity coefficient of two vertices is the number of common neighbors divided by the number of vertices that are neighbors of at least one of the two vertices being considered. This function calculates the pairwise Jaccard similarities for the endpoints of edges in a given edge selector.

similarityDiceSource

Arguments

:: Graph d a 
-> VertexSelector a 
-> Bool

Whether to include the vertices themselves as their own neighbors

-> [(a, [(a, Double)])] 

8.6. igraph_similarity_dice — Dice similarity coefficient.

The Dice similarity coefficient of two vertices is twice the number of common neighbors divided by the sum of the degrees of the vertices. This function calculates the pairwise Dice similarities for some (or all) of the vertices.

similarityDicePairsSource

Arguments

:: Graph d a 
-> [Edge d a] 
-> Bool

Whether to include the vertices themselves as their own neighbors

-> [(Edge d a, Double)] 

8.7. igraph_similarity_dice_pairs — Dice similarity coefficient for given vertex pairs.

The Dice similarity coefficient of two vertices is twice the number of common neighbors divided by the sum of the degrees of the vertices. This function calculates the pairwise Dice similarities for a list of vertex pairs.

similarityDiceEsSource

Arguments

:: Graph d a 
-> EdgeSelector d a 
-> Bool

Whether to include the vertices themselves as their own neighbors

-> [(Edge d a, Double)] 

8.8. igraph_similarity_dice_es — Dice similarity coefficient for a given edge selector.

The Dice similarity coefficient of two vertices is twice the number of common neighbors divided by the sum of the degrees of the vertices. This function calculates the pairwise Dice similarities for the endpoints of edges in a given edge selector.

similarityInverseLogWeighted :: Graph d a -> VertexSelector a -> [(a, [(a, Double)])]Source

8.9. igraph_similarity_inverse_log_weighted — Vertex similarity based on the inverse logarithm of vertex degrees.

The inverse log-weighted similarity of two vertices is the number of their common neighbors, weighted by the inverse logarithm of their degrees. It is based on the assumption that two vertices should be considered more similar if they share a low-degree common neighbor, since high-degree common neighbors are more likely to appear even by pure chance.

Isolated vertices will have zero similarity to any other vertex. Self-similarities are not calculated.

See the following paper for more details: Lada A. Adamic and Eytan Adar: Friends and neighbors on the Web. Social Networks, 25(3):211-230, 2003.

13.9 Spanning Tress

minimumSpanningTree :: Graph d a -> [Edge d a]Source

9.1. igraph_minimum_spanning_tree — Calculates one minimum spanning tree of a graph.

If the graph has more minimum spanning trees (this is always the case, except if it is a forest) this implementation returns only the same one.

Directed graphs are considered as undirected for this computation.

If the graph is not connected then its minimum spanning forest is returned. This is the set of the minimum spanning trees of each component.

minimumSpanningTreeUnweighted :: IsUnweighted d => Graph d a -> Graph d aSource

9.2. igraph_minimum_spanning_tree_unweighted — Calculates one minimum spanning tree of an unweighted graph.

minimumSpanningTreePrim :: IsUnweighted d => Graph (Weighted d) a -> Graph (Weighted d) aSource

9.3. igraph_minimum_spanning_tree_prim — Calculates one minimum spanning tree of a weighted graph.

13.10 Transitivity or Clustering Coefficient

transitivityUndirected :: Graph d a -> DoubleSource

10.1. igraph_transitivity_undirected — Calculates the transitivity (clustering coefficient) of a graph.

The transitivity measures the probability that two neighbors of a vertex are connected. More precisely, this is the ratio of the triangles and connected triples in the graph, the result is a single real number. Directed graphs are considered as undirected ones.

Note that this measure is different from the local transitivity measure (see `igraph_transitivity_local_undirected()` ) as it calculates a single value for the whole graph. See the following reference for more details:

S. Wasserman and K. Faust: Social Network Analysis: Methods and Applications. Cambridge: Cambridge University Press, 1994.

Clustering coefficient is an alternative name for transitivity.

transitivityLocalUndirected :: Graph d a -> VertexSelector a -> [(a, Double)]Source

10.2. igraph_transitivity_local_undirected — Calculates the local transitivity (clustering coefficient) of a graph.

The transitivity measures the probability that two neighbors of a vertex are connected. In case of the local transitivity, this probability is calculated separately for each vertex.

Note that this measure is different from the global transitivity measure (see igraph_transitivity_undirected() ) as it calculates a transitivity value for each vertex individually. See the following reference for more details:

D. J. Watts and S. Strogatz: Collective dynamics of small-world networks. Nature 393(6684):440-442 (1998).

Clustering coefficient is an alternative name for transitivity.

transitivityAvglocalUndirected :: Graph d a -> DoubleSource

10.3. igraph_transitivity_avglocal_undirected — Average local transitivity (clustering coefficient).

The transitivity measures the probability that two neighbors of a vertex are connected. In case of the average local transitivity, this probability is calculated for each vertex and then the average is taken. Vertices with less than two neighbors require special treatment, they will either be left out from the calculation or they will be considered as having zero transitivity, depending on the mode argument.

Note that this measure is different from the global transitivity measure (see `igraph_transitivity_undirected()` ) as it simply takes the average local transitivity across the whole network. See the following reference for more details:

D. J. Watts and S. Strogatz: Collective dynamics of small-world networks. Nature 393(6684):440-442 (1998).

Clustering coefficient is an alternative name for transitivity.

transitivityBarrat :: Graph d a -> VertexSelector a -> [(a, Double)]Source

10.4. igraph_transitivity_barrat — Weighted transitivity, as defined by A. Barrat.

This is a local transitivity, i.e. a vertex-level index. For a given vertex i, from all triangles in which it participates we consider the weight of the edges incident on i. The transitivity is the sum of these weights divided by twice the strength of the vertex (see `igraph_strength()`) and the degree of the vertex minus one. See Alain Barrat, Marc Barthelemy, Romualdo Pastor-Satorras, Alessandro Vespignani: The architecture of complex weighted networks, Proc. Natl. Acad. Sci. USA 101, 3747 (2004) at http:arxiv.orgabscond-mat/0311416 for the exact formula.

13.12 Spectral properties

laplacianSource

Arguments

:: Graph d a 
-> Bool

Whether to create a normalized Laplacian matrix

-> [[Double]] 

12.1. igraph_laplacian — Returns the Laplacian matrix of a graph

The graph Laplacian matrix is similar to an adjacency matrix but contains -1's instead of 1's and the vertex degrees are included in the diagonal. So the result for edge i--j is -1 if i!=j and is equal to the degree of vertex i if i==j. igraph_laplacian will work on a directed graph; in this case, the diagonal will contain the out-degrees. Loop edges will be ignored.

The normalized version of the Laplacian matrix has 1 in the diagonal and -1/sqrt(d[i]d[j]) if there is an edge from i to j.

The first version of this function was written by Vincent Matossian.

13.14 Mixing patterns

assortativityNominalSource

Arguments

:: Eq vertexType 
=> Graph d (vertexType, a) 
-> Bool

whether to consider edge directions in a directed graph. It is ignored for undirected graphs

-> Double 

14.1. igraph_assortativity_nominal — Assortativity of a graph based on vertex categories

Assuming the vertices of the input graph belong to different categories, this function calculates the assortativity coefficient of the graph. The assortativity coefficient is between minus one and one and it is one if all connections stay within categories, it is minus one, if the network is perfectly disassortative. For a randomly connected network it is (asymptotically) zero.

See equation (2) in M. E. J. Newman: Mixing patterns in networks, Phys. Rev. E 67, 026126 (2003) (http:arxiv.orgabscond-mat/0209450) for the proper definition.

assortativitySource

Arguments

:: (Eq vertexTypeIncoming, Eq vertexTypeOutgoing) 
=> Graph d (vertexTypeIncoming, vertexTypeOutgoing, a) 
-> Bool

whether to consider edge directions for directed graphs. It is ignored for undirected graphs

-> Double 

14.2. igraph_assortativity — Assortativity based on numeric properties of vertices

This function calculates the assortativity coefficient of the input graph. This coefficient is basically the correlation between the actual connectivity patterns of the vertices and the pattern expected from the distribution of the vertex types.

See equation (21) in M. E. J. Newman: Mixing patterns in networks, Phys. Rev. E 67, 026126 (2003) (http:arxiv.orgabscond-mat/0209450) for the proper definition. The actual calculation is performed using equation (26) in the same paper for directed graphs, and equation (4) in M. E. J. Newman: Assortative mixing in networks, Phys. Rev. Lett. 89, 208701 (2002) (http:arxiv.orgabscond-mat0205405) for undirected graphs.

assortativityDegreeSource

Arguments

:: Graph d a 
-> Bool

whether to consider edge directions for directed graphs. This argument is ignored for undirected graphs. Supply True here to do the natural thing, i.e. use directed version of the measure for directed graphs and the undirected version for undirected graphs.

-> Double 

14.3. igraph_assortativity_degree — Assortativity of a graph based on vertex degree

Assortativity based on vertex degree, please see the discussion at the documentation of igraph_assortativity() for details.

13.15 K-Cores

coreness :: Graph d a -> [(Double, a)]Source

15.1. igraph_coreness — Finding the coreness of the vertices in a network.

The k-core of a graph is a maximal subgraph in which each vertex has at least degree k. (Degree here means the degree in the subgraph of course.). The coreness of a vertex is the highest order of a k-core containing the vertex.

This function implements the algorithm presented in Vladimir Batagelj, Matjaz Zaversnik: An O(m) Algorithm for Cores Decomposition of Networks.

13.16 Topological sorting, directed acyclic graphs

isDAG :: Graph d a -> BoolSource

16.1. igraph_is_dag — Checks whether a graph is a directed acyclic graph (DAG) or not.

A directed acyclic graph (DAG) is a directed graph with no cycles.

topologicalSorting :: Graph d a -> [a]Source

16.2. igraph_topological_sorting — Calculate a possible topological sorting of the graph.

A topological sorting of a directed acyclic graph is a linear ordering of its nodes where each node comes before all nodes to which it has edges. Every DAG has at least one topological sort, and may have many. This function returns a possible topological sort among them. If the graph is not acyclic (it has at least one cycle), a partial topological sort is returned and a warning is issued.

feedbackArcSet :: Graph d a -> FASAlgorithm -> [a]Source

16.3. igraph_feedback_arc_set — Calculates a feedback arc set of the graph using different

A feedback arc set is a set of edges whose removal makes the graph acyclic. We are usually interested in minimum feedback arc sets, i.e. sets of edges whose total weight is minimal among all the feedback arc sets.

For undirected graphs, the problem is simple: one has to find a maximum weight spanning tree and then remove all the edges not in the spanning tree. For directed graphs, this is an NP-hard problem, and various heuristics are usually used to find an approximate solution to the problem. This function implements a few of these heuristics.

13.17 Maximum cardinality search, graph decomposition, chordal graphs

maximumCardinalitySearch :: Graph d a -> [(Int, a)]Source

17.1. igraph_maximum_cardinality_search — Maximum cardinality search

This function implements the maximum cardinality search algorithm discussed in Robert E Tarjan and Mihalis Yannakakis: Simple linear-time algorithms to test chordality of graphs, test acyclicity of hypergraphs, and selectively reduce acyclic hypergraphs. SIAM Journal of Computation 13, 566--579, 1984.

isChordalSource

Arguments

:: Graph d a 
-> (Bool, [Edge d a])

returns a list of fill-in edges to make the graph chordal

17.2. igraph_is_chordal — Decides whether a graph is chordal

A graph is chordal if each of its cycles of four or more nodes has a chord, which is an edge joining two nodes that are not adjacent in the cycle. An equivalent definition is that any chordless cycles have at most three nodes.