Nice to have: vertex_edge_incidence_matrix().
What is the feature or improvement you would like to see?
Nice to have: function to calculate the vertex-edge incidence matrix of a graph. 20240118 - Added argument weights = NULL 20240119 - Added example graph, directed, multiple, weighted. 20240123 - Added example graph with self-loop.
Description
The vertex-edge incidence matrix of a graph.
Usage
as_ve_incidence_matrix <- function( graph , mode = c("all", "out", "in") , loops , multiple , weights = NULL , names = FALSE , attr = "label" , sparse = igraph_opt("sparsematrices") )
Depending on personal taste, we can choose one of the following alternatives:
- as_vertex_edge_incidence_matrix()
- as_veincidence_matrix(), as in as_biadjacency_matrix().
- vertex_edge_incidence_matrix(), as in laplacian_matrix.
- ve_incidence_matrix(), shorter version.
- …
Arguments
graph
- simple or multi-edge
- directed, undirected
- weighted, unweighted
- named, unnamed
- with or without loops
- sparse, non-sparse
mode
- as in incident(), distances().
loops
- As in igraph Reference Manual.
- igraph_adjlist_init_empty — Initializes an empty adjacency list. p. 187.
multiple
- As in igraph Reference Manual.
weights
- as in distances(), cluster_leiden(). For example, Wikipedia, wiki/Incidence_matrix, chapter Weighted graphs.
names
- If NA, ignore names.
- If NULL, copy vertex name and edge label from graph if present, to dimnames.
- If matrix, then copy to dimnames.
attr
- name of the edge attr to be used for colnames of the matrix, default is "label".
sparse
- as in laplacian_matrix()
Details
This function calculates the vertex-edge incidence matrix B of graph g. If g is undirected, Bxe = 1 when vertex x is incident with edge e, 0 otherwise. If g is directed, Bxe = −1,1,0 when vertex x is the head of edge e, the tail of e, or not on e, respectively.
If weights are taken into account, then -1, 1 becomes -w, w, where w is the weight of edge e.
Value
A possibly sparse matrix B with rows indexed by the vertices and columns indexed by the edges.
See Also
The function laplacian_matrix() computes the out-degree Laplacian matrix. To allow the calculation of a symmetric Laplacian matrix, the function should be modified to support mode="all", in particular to ignore the orientation of edges. Currently, a workaround is to convert the graph to its undirected version.
The function as_adjacency_matrix() includes weights using attr = "weight".
See also Github/igraph/rigraph/issue #906, as_adjacency_matrix() should use weights instead of attr parameter.
See also Github/igraph/rigraph/issues #1125, Treat self-loops in igraph functions consistently.
Examples
library(igraph)
g1 <- make_ring(3, circular=FALSE) # Undirected, simple.
g2 <- graph(c(1,2,1,2,2,3), directed=FALSE ) # Undirected, multi edge.
g2w <- graph(c(1,2,2,3), directed=FALSE ) # Undirected
E(g2w)$weight <- c(2,1); E(g2w)$label <- E(g2w)$weight # Weighted.
g3 <- make_ring(3,circular=FALSE, directed=TRUE) # Directed, simple.
g4 <- graph(c(1,2,1,2,2,3) ) # Directed, multi edge.
g4w<- g4; # Directed, multi edge.
E(g4w)$weight<- c(2,3, 5); E(g4w)$label<- E(g4w)$weight # Weighted.
# Named graph, undirected. From wiki/Incidence_matrix.
g5 <- graph_from_literal(1-2, 1-3, 1-4, 3-4)
E(g5)$label <- paste0("e", seq_len(gsize(g5)) )
# Named graph, directed, From /wiki/Directed_graph (-B).
g6 <- graph_from_literal(a-+b-+c-+a, a-+d, simplify=FALSE)
g6$name <- "g6"; E(g6)$label <- c("1", "2", "3", "4")
# Undirected graph with loops, e.g. edge incident with a single vertex.
# An undirected loop adds two or one to the degree of its vertex (depending on parameters).
g7 <- graph(c(1,1,1,1,1,2,1,2), directed=FALSE)
# A directed loop adds 0 to the degree of its vertex.
g8 <- graph(c(1,1,1,1,1,2,1,2), directed=TRUE)
# Print incidence matrices.
for (g in list(g2, g4w, g6, g7, g8) )
{cat("\n");print(g); print(as_ve_incidence_matrix(g, weights=NULL))}
# Expected output.
# IGRAPH 3371287 U--- 3 3 --
# + edges from 3371287:
# [1] 1--2 1--2 2--3
# [,1] [,2] [,3]
# [1,] 1 1 0
# [2,] 1 1 1
# [3,] 0 0 1
#
# IGRAPH 337f2fd D-W- 3 3 --
# + attr: weight (e/n), label (e/n)
# + edges from 337f2fd:
# [1] 1->2 1->2 2->3
# [,1] [,2] [,3]
# [1,] -2 -3 0
# [2,] 2 3 -5
# [3,] 0 0 5
#
# IGRAPH 33949a0 DN-- 4 4 -- g6
# + attr: name (g/c), name (v/c), label (e/c)
# + edges from 33949a0 (vertex names):
# [1] a->b b->c c->a a->d
# 1 2 3 4
# a -1 0 1 -1
# b 1 -1 0 0
# c 0 1 -1 0
# d 0 0 0 1
#
# IGRAPH 33a118b U--- 2 4 --
# + edges from 33a118b:
# [1] 1--1 1--1 1--2 1--2
# [,1] [,2] [,3] [,4]
# [1,] 2 2 1 1
# [2,] 0 0 1 1
#
# IGRAPH 33a8e26 D--- 2 4 --
# + edges from 33a8e26:
# [1] 1->1 1->1 1->2 1->2
# [,1] [,2] [,3] [,4]
# [1,] 0 0 -1 -1
# [2,] 0 0 1 1
The following relationships apply: Let
- g be a graph without loops.
- L is the Laplacian matrix of graph g. Q is the signless Laplacian matrix.
- B is the unweighted vertex-edge incidence matrix.
- Bw is the (un)weighted matrix, depending on whether or not weights are taken into account.
- W is the diagonal matrix containing the edge weights, or ones if weights are not considered.
Then
- Bw = BW.
- Q = BwBT, when g is undirected.
- L = BwBT, when g is directed.
References
- igraph Reference Manual, https://igraph.org/c/pdf/latest/igraph-docs.pdf
- A. Brouwer, and W. Haemers, "Spectra of graphs", monograph, https://www.win.tue.nl/~aeb/2WF02/spectra.pdf, p11.
Thanks! Would you like to contribute a pull request?
@szhorvat: can you please comment on the naming and argument choices?
@krlmlr, I am not very familiar with Github. So I need some guidence.
I've been meaning to get back to this, and I hope to get to it next week. It should be implemented in C, but most of the work is collecting the kinds of information like in this issue, so this is very useful
For GitHub, https://happygitwithr.com/ is a great resource. Skip chapters 6-8 if you have installed Git. For a hands-on approach, try chapters 35 and 36.
Things are getting more complicated if we need to change the C core for that.
Please find below an application of the vertex_edge_incidence matrix.
Let g be an undirected graph without loops.
Then the vertex-edge incidence matrix C of a graph and the adjacency matrix L of its line graph are related by
L = t(C).C - 2I
See: https://mathworld.wolfram.com/LineGraph.html
# Rows indexed by the vertices, columns indexed by the edges.
# The degree of a loop, if present, is set to 2.
as_ve_incidence_matrix <- function(g) {
el <- as_edgelist(g, names=FALSE) # Edgelist, indexed from 1, consecutively.
X <- matrix(0, gorder(g), gsize(g) ) # Indexed by V x E, initialize with no edges.
X[cbind(el[,1], seq_len(nrow(el)) )] <- ifelse(is_directed(g), -1L, 1L) # Head of the edge.
X[cbind(el[,2], seq_len(nrow(el)) )] <- X[cbind(el[,2], seq_len(gsize(g)))] + 1L # Tail of the edge.
if (is_named(g) ) {
rownames(X) <- V(g)$name
colnames(X) <- E(g)$label
}
return(X)
}
# Graph is undirected without loops.
# Igraph Reference Manual, https://igraph.org/c/pdf/latest/igraph-docs.pdf
library(igraph)
g0 <- make_empty_graph(directed=FALSE); g0$name <- "Undirected Empty"
P2 <- graph(~ "a-b"); P2$name <- "Path graph P2"
Pn <- make_ring(4, circular=FALSE); Pn$name <- "Path graph Pn"
C4 <- make_ring(4); C4$name <- "Square graph C4"
K4 <- g <- make_full_graph(4); K4$name <- "K4"
S3 <- make_star(3, mode="undirected"); S3$name <- "S3"
S4 <- make_star(4, mode="undirected"); S4$name <- "Claw graph"
K32 <- make_full_bipartite_graph(3, 2); K32$name<- "K3,2"
nl <- make_graph("Nonline")
E2 <- graph(~a-b, a-b); E2$name = "Multigraph, 2 edges"
KB <- graph(~ a-b, a-b, b-c, b-c, a-d, b-d, c-d, simplify=FALSE); KB$name="Koningsberger bridges"
examples <- list(g0, P2, Pn, C4, K4, S3, S4, K32, nl, E2, KB)
# Undirected graphs.
for (g in examples ) {
Cve <- as_ve_incidence_matrix(g)
ALg <- t(Cve) %*% Cve - 2*diag(gsize(g))
Lg1 <- graph_from_adjacency_matrix(ALg, mode="undirected") # Definition.
Lg2 <- make_line_graph(g) # Igraph.
iso <- ifelse(isomorphic(Lg1, Lg2), " OK", "NOK") # Same.
cat(sprintf("%24s, %2d, %2d, %3d, %3s\n", g$name, gorder(g), gsize(g), gsize(Lg2), iso) )
}
# Validate incidence matrix ~ signless Laplace matrix.
for (g in examples ) {
Cve <- as_ve_incidence_matrix(g)
Q <- Cve %*% t(Cve) # Signless Laplace matrix
L <- laplacian_matrix(g, sparse=FALSE) # Laplace matrix
same <- all(-Q + diag(diag(Q), nrow(Q) )*2 == L) # compare with signless Laplace matrix
cat(sprintf("%24s, %2d, %2d, %3s\n", g$name, gorder(g), gsize(g), same) )
}
# Validate Laplace matrix L(g) == B.t(B).
# B is the directed incidence matrix of the directed graph
# obtained by orienting the edges of g in an arbitrary way.
# https://homepages.cwi.nl/~aeb/math/ipm/, p.11.
for (g in examples ) {
g.dir <- as.directed(g, mode="arbitrary") # Orientation is random.
Nve <- as_ve_incidence_matrix(g.dir) # The directed vertex-edge incidence matrix.
L1 <- Nve %*% t(Nve) # Laplace matrix via oriented incidence matrix.
L <- laplacian_matrix(g, sparse=FALSE) # Laplace matrix (g).
same <- all(L1 == L) # Verify L == B.t(B).
cat(sprintf("%24s, %2d, %2d, %3s\n", g$name, gorder(g), gsize(g), same) )
}
@clpippel: Copilot has hand-rolled an R implementation in #2426. Depending on the use case, it might already be sufficient for you. I asked Copilot to make use of vectorization, let's see if that PR improves even further. Either way, it's unlikely to land in this repo.
I was under the impression that we have a C function for this. For best efficiency, we'd implement there and merely expose here. (That's what the "expose" label is about, FYI.)