diff --git a/NAMESPACE b/NAMESPACE index 95be07fb203..2b491c6d8d1 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -160,6 +160,7 @@ export(as_phylo) export(as_star) export(as_tree) export(as_undirected) +export(as_veincidence_matrix) export(assortativity) export(assortativity.degree) export(assortativity.nominal) diff --git a/R/conversion.R b/R/conversion.R index 4de5467dd4c..7f19367ff62 100644 --- a/R/conversion.R +++ b/R/conversion.R @@ -498,6 +498,297 @@ as_edgelist <- function(graph, names = TRUE) { res } +#' Convert a graph to a vertex-edge incidence matrix +#' +#' `r lifecycle::badge("experimental")` +#' +#' `as_veincidence_matrix()` returns the vertex-edge incidence matrix of a graph. +#' +#' The vertex-edge incidence matrix is a matrix where rows correspond to vertices +#' and columns correspond to edges. For undirected graphs, the matrix element +#' is 1 if the vertex is incident to the edge, 0 otherwise. For directed graphs, +#' the element is -1 if the vertex is the tail (source) of the edge, +1 if it is +#' the head (target), and 0 otherwise. +#' +#' For loops (edges connecting a vertex to itself): +#' \itemize{ +#' \item In undirected graphs: the incidence value is 2 +#' \item In directed graphs: the incidence value is 0 +#' } +#' +#' When weights are used, the values -1 and +1 are replaced by -w and +w +#' respectively, where w is the weight of the edge. +#' +#' @param graph The input graph. +#' @param types `r lifecycle::badge("deprecated")` This argument is deprecated +#' and not used. It was originally intended for compatibility but vertex-edge +#' incidence matrices don't use types. +#' @param attr Either `NULL` or a character string giving an edge attribute name. +#' If `NULL`, unweighted incidence is returned (values are -1, 0, 1 for directed +#' graphs and 0, 1, 2 for undirected graphs). If not `NULL`, weighted incidence +#' is returned using the specified edge attribute as weights. For directed graphs, +#' values are -w, 0, w where w is the weight. For undirected graphs, values are +#' 0, w, 2w. +#' @param names Logical scalar, whether to add vertex and edge names to the matrix. +#' If `TRUE` (default), vertex names are used for row names if the `name` +#' vertex attribute exists, and edge labels are used for column names if +#' the `label` edge attribute exists. Vertex and edge IDs are used otherwise. +#' @param sparse Logical scalar, whether to return a sparse matrix. The +#' \sQuote{`Matrix`} package must be installed for creating sparse matrices. +#' @return A (usually sparse) matrix with `vcount(graph)` rows and +#' `ecount(graph)` columns. +#' +#' @seealso [as_adjacency_matrix()], [as_edgelist()], [laplacian_matrix()] +#' +#' @examples +#' # Undirected graph +#' g1 <- make_ring(3, circular = FALSE) +#' as_veincidence_matrix(g1, sparse = FALSE) +#' +#' # Directed graph +#' g2 <- make_ring(3, circular = FALSE, directed = TRUE) +#' as_veincidence_matrix(g2, sparse = FALSE) +#' +#' # Weighted graph +#' g3 <- make_ring(3, circular = FALSE) +#' E(g3)$weight <- c(2, 3) +#' as_veincidence_matrix(g3, attr = "weight", sparse = FALSE) +#' +#' # Named graph +#' g4 <- graph_from_literal(a-b, b-c, c-d) +#' E(g4)$label <- paste0("e", seq_len(ecount(g4))) +#' as_veincidence_matrix(g4, sparse = FALSE) +#' +#' # Graph with loop +#' g5 <- graph(c(1, 1, 1, 2), directed = FALSE) +#' as_veincidence_matrix(g5, sparse = FALSE) +#' +#' @family conversion +#' @concept matrices +#' @export +as_veincidence_matrix <- function( + graph, + types = deprecated(), + attr = NULL, + names = TRUE, + sparse = igraph_opt("sparsematrices") +) { + ensure_igraph(graph) + + if (lifecycle::is_present(types)) { + lifecycle::deprecate_warn( + "2.1.0", + "as_veincidence_matrix(types = )", + details = "The 'types' argument is not used for vertex-edge incidence matrices." + ) + } + + if (sparse) { + get.ve.incidence.sparse(graph, attr = attr, names = names) + } else { + get.ve.incidence.dense(graph, attr = attr, names = names) + } +} + +get.ve.incidence.dense <- function( + graph, + attr = NULL, + names = TRUE, + call = rlang::caller_env() +) { + vc <- vcount(graph) + ec <- ecount(graph) + + # Initialize matrix with zeros + res <- matrix(0, nrow = vc, ncol = ec) + + if (ec == 0) { + # Empty graph + if (names && "name" %in% vertex_attr_names(graph)) { + rownames(res) <- V(graph)$name + } + return(res) + } + + # Get edge list + el <- as_edgelist(graph, names = FALSE) + + # Get weights if specified + if (!is.null(attr)) { + attr <- as.character(attr) + if (!attr %in% edge_attr_names(graph)) { + cli::cli_abort("No such edge attribute: {.str {attr}}", call = call) + } + weights <- edge_attr(graph, attr) + if (!is.numeric(weights)) { + cli::cli_abort( + "Edge attribute {.str {attr}} must be numeric", + call = call + ) + } + } else { + weights <- rep(1, ec) + } + + if (is_directed(graph)) { + # For directed graphs: -weight for tail, +weight for head + for (i in seq_len(ec)) { + tail <- el[i, 1] + head <- el[i, 2] + + if (tail == head) { + # Self-loop: contribution is 0 in directed graphs + res[tail, i] <- 0 + } else { + res[tail, i] <- -weights[i] + res[head, i] <- weights[i] + } + } + } else { + # For undirected graphs: weight for each incident vertex + for (i in seq_len(ec)) { + v1 <- el[i, 1] + v2 <- el[i, 2] + + if (v1 == v2) { + # Self-loop: contribution is 2*weight + res[v1, i] <- 2 * weights[i] + } else { + res[v1, i] <- weights[i] + res[v2, i] <- weights[i] + } + } + } + + # Add row names (vertex names or IDs) + if (names) { + if ("name" %in% vertex_attr_names(graph)) { + rownames(res) <- V(graph)$name + } else { + rownames(res) <- seq_len(vc) + } + + # Add column names (edge labels or IDs) + if ( + !is.null(attr) && attr == "label" && "label" %in% edge_attr_names(graph) + ) { + colnames(res) <- E(graph)$label + } else if ("label" %in% edge_attr_names(graph)) { + colnames(res) <- E(graph)$label + } else { + colnames(res) <- seq_len(ec) + } + } + + res +} + +get.ve.incidence.sparse <- function( + graph, + attr = NULL, + names = TRUE, + call = rlang::caller_env() +) { + vc <- vcount(graph) + ec <- ecount(graph) + + if (ec == 0) { + # Empty graph + res <- Matrix::Matrix(0, nrow = vc, ncol = ec, sparse = TRUE) + if (names && "name" %in% vertex_attr_names(graph)) { + rownames(res) <- V(graph)$name + } + return(res) + } + + # Get edge list + el <- as_edgelist(graph, names = FALSE) + + # Get weights if specified + if (!is.null(attr)) { + attr <- as.character(attr) + if (!attr %in% edge_attr_names(graph)) { + cli::cli_abort("No such edge attribute: {.str {attr}}", call = call) + } + weights <- edge_attr(graph, attr) + if (!is.numeric(weights)) { + cli::cli_abort( + "Edge attribute {.str {attr}} must be numeric", + call = call + ) + } + } else { + weights <- rep(1, ec) + } + + # Build sparse matrix using triplet format + i_indices <- integer() + j_indices <- integer() + x_values <- numeric() + + if (is_directed(graph)) { + # For directed graphs: -weight for tail, +weight for head + for (e in seq_len(ec)) { + tail <- el[e, 1] + head <- el[e, 2] + + if (tail == head) { + # Self-loop: contribution is 0, so we skip it (sparse) + } else { + i_indices <- c(i_indices, tail, head) + j_indices <- c(j_indices, e, e) + x_values <- c(x_values, -weights[e], weights[e]) + } + } + } else { + # For undirected graphs: weight for each incident vertex + for (e in seq_len(ec)) { + v1 <- el[e, 1] + v2 <- el[e, 2] + + if (v1 == v2) { + # Self-loop: contribution is 2*weight + i_indices <- c(i_indices, v1) + j_indices <- c(j_indices, e) + x_values <- c(x_values, 2 * weights[e]) + } else { + i_indices <- c(i_indices, v1, v2) + j_indices <- c(j_indices, e, e) + x_values <- c(x_values, weights[e], weights[e]) + } + } + } + + # Create sparse matrix + res <- Matrix::sparseMatrix( + i = i_indices, + j = j_indices, + x = x_values, + dims = c(vc, ec) + ) + + # Add row names (vertex names or IDs) + if (names) { + if ("name" %in% vertex_attr_names(graph)) { + rownames(res) <- V(graph)$name + } else { + rownames(res) <- seq_len(vc) + } + + # Add column names (edge labels or IDs) + if ( + !is.null(attr) && attr == "label" && "label" %in% edge_attr_names(graph) + ) { + colnames(res) <- E(graph)$label + } else if ("label" %in% edge_attr_names(graph)) { + colnames(res) <- E(graph)$label + } else { + colnames(res) <- seq_len(ec) + } + } + + res +} #' Convert between directed and undirected graphs #' diff --git a/man/as.matrix.igraph.Rd b/man/as.matrix.igraph.Rd index 136377aa4c0..0d2eba60b50 100644 --- a/man/as.matrix.igraph.Rd +++ b/man/as.matrix.igraph.Rd @@ -55,6 +55,7 @@ Other conversion: \code{\link{as_edgelist}()}, \code{\link{as_graphnel}()}, \code{\link{as_long_data_frame}()}, +\code{\link{as_veincidence_matrix}()}, \code{\link{graph_from_adj_list}()}, \code{\link{graph_from_graphnel}()} } diff --git a/man/as_adj_list.Rd b/man/as_adj_list.Rd index 24d17623734..e0a0d617f2f 100644 --- a/man/as_adj_list.Rd +++ b/man/as_adj_list.Rd @@ -74,6 +74,7 @@ Other conversion: \code{\link{as_edgelist}()}, \code{\link{as_graphnel}()}, \code{\link{as_long_data_frame}()}, +\code{\link{as_veincidence_matrix}()}, \code{\link{graph_from_adj_list}()}, \code{\link{graph_from_graphnel}()} } diff --git a/man/as_adjacency_matrix.Rd b/man/as_adjacency_matrix.Rd index 5f6215049b0..d288c3230d1 100644 --- a/man/as_adjacency_matrix.Rd +++ b/man/as_adjacency_matrix.Rd @@ -81,6 +81,7 @@ Other conversion: \code{\link{as_edgelist}()}, \code{\link{as_graphnel}()}, \code{\link{as_long_data_frame}()}, +\code{\link{as_veincidence_matrix}()}, \code{\link{graph_from_adj_list}()}, \code{\link{graph_from_graphnel}()} } diff --git a/man/as_biadjacency_matrix.Rd b/man/as_biadjacency_matrix.Rd index c4cd1cd8ca3..9a77a8d2f7f 100644 --- a/man/as_biadjacency_matrix.Rd +++ b/man/as_biadjacency_matrix.Rd @@ -70,6 +70,7 @@ Other conversion: \code{\link{as_edgelist}()}, \code{\link{as_graphnel}()}, \code{\link{as_long_data_frame}()}, +\code{\link{as_veincidence_matrix}()}, \code{\link{graph_from_adj_list}()}, \code{\link{graph_from_graphnel}()} } diff --git a/man/as_directed.Rd b/man/as_directed.Rd index 78e4fdfe586..9ef4861791d 100644 --- a/man/as_directed.Rd +++ b/man/as_directed.Rd @@ -129,6 +129,7 @@ Other conversion: \code{\link{as_edgelist}()}, \code{\link{as_graphnel}()}, \code{\link{as_long_data_frame}()}, +\code{\link{as_veincidence_matrix}()}, \code{\link{graph_from_adj_list}()}, \code{\link{graph_from_graphnel}()} } diff --git a/man/as_edgelist.Rd b/man/as_edgelist.Rd index 9708cb79784..b1de4a2b1b1 100644 --- a/man/as_edgelist.Rd +++ b/man/as_edgelist.Rd @@ -44,6 +44,7 @@ Other conversion: \code{\link{as_directed}()}, \code{\link{as_graphnel}()}, \code{\link{as_long_data_frame}()}, +\code{\link{as_veincidence_matrix}()}, \code{\link{graph_from_adj_list}()}, \code{\link{graph_from_graphnel}()} } diff --git a/man/as_graphnel.Rd b/man/as_graphnel.Rd index 96650d6746f..b547b34da5b 100644 --- a/man/as_graphnel.Rd +++ b/man/as_graphnel.Rd @@ -56,6 +56,7 @@ Other conversion: \code{\link{as_directed}()}, \code{\link{as_edgelist}()}, \code{\link{as_long_data_frame}()}, +\code{\link{as_veincidence_matrix}()}, \code{\link{graph_from_adj_list}()}, \code{\link{graph_from_graphnel}()} } diff --git a/man/as_long_data_frame.Rd b/man/as_long_data_frame.Rd index 4e5e865dee9..b86128ffe2f 100644 --- a/man/as_long_data_frame.Rd +++ b/man/as_long_data_frame.Rd @@ -40,6 +40,7 @@ Other conversion: \code{\link{as_directed}()}, \code{\link{as_edgelist}()}, \code{\link{as_graphnel}()}, +\code{\link{as_veincidence_matrix}()}, \code{\link{graph_from_adj_list}()}, \code{\link{graph_from_graphnel}()} } diff --git a/man/as_veincidence_matrix.Rd b/man/as_veincidence_matrix.Rd new file mode 100644 index 00000000000..c652fe9c9c0 --- /dev/null +++ b/man/as_veincidence_matrix.Rd @@ -0,0 +1,103 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/conversion.R +\name{as_veincidence_matrix} +\alias{as_veincidence_matrix} +\title{Convert a graph to a vertex-edge incidence matrix} +\usage{ +as_veincidence_matrix( + graph, + types = deprecated(), + attr = NULL, + names = TRUE, + sparse = igraph_opt("sparsematrices") +) +} +\arguments{ +\item{graph}{The input graph.} + +\item{types}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#deprecated}{\figure{lifecycle-deprecated.svg}{options: alt='[Deprecated]'}}}{\strong{[Deprecated]}} This argument is deprecated +and not used. It was originally intended for compatibility but vertex-edge +incidence matrices don't use types.} + +\item{attr}{Either \code{NULL} or a character string giving an edge attribute name. +If \code{NULL}, unweighted incidence is returned (values are -1, 0, 1 for directed +graphs and 0, 1, 2 for undirected graphs). If not \code{NULL}, weighted incidence +is returned using the specified edge attribute as weights. For directed graphs, +values are -w, 0, w where w is the weight. For undirected graphs, values are +0, w, 2w.} + +\item{names}{Logical scalar, whether to add vertex and edge names to the matrix. +If \code{TRUE} (default), vertex names are used for row names if the \code{name} +vertex attribute exists, and edge labels are used for column names if +the \code{label} edge attribute exists. Vertex and edge IDs are used otherwise.} + +\item{sparse}{Logical scalar, whether to return a sparse matrix. The +\sQuote{\code{Matrix}} package must be installed for creating sparse matrices.} +} +\value{ +A (usually sparse) matrix with \code{vcount(graph)} rows and +\code{ecount(graph)} columns. +} +\description{ +\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} +} +\details{ +\code{as_veincidence_matrix()} returns the vertex-edge incidence matrix of a graph. + +The vertex-edge incidence matrix is a matrix where rows correspond to vertices +and columns correspond to edges. For undirected graphs, the matrix element +is 1 if the vertex is incident to the edge, 0 otherwise. For directed graphs, +the element is -1 if the vertex is the tail (source) of the edge, +1 if it is +the head (target), and 0 otherwise. + +For loops (edges connecting a vertex to itself): +\itemize{ +\item In undirected graphs: the incidence value is 2 +\item In directed graphs: the incidence value is 0 +} + +When weights are used, the values -1 and +1 are replaced by -w and +w +respectively, where w is the weight of the edge. +} +\examples{ +# Undirected graph +g1 <- make_ring(3, circular = FALSE) +as_veincidence_matrix(g1, sparse = FALSE) + +# Directed graph +g2 <- make_ring(3, circular = FALSE, directed = TRUE) +as_veincidence_matrix(g2, sparse = FALSE) + +# Weighted graph +g3 <- make_ring(3, circular = FALSE) +E(g3)$weight <- c(2, 3) +as_veincidence_matrix(g3, attr = "weight", sparse = FALSE) + +# Named graph +g4 <- graph_from_literal(a-b, b-c, c-d) +E(g4)$label <- paste0("e", seq_len(ecount(g4))) +as_veincidence_matrix(g4, sparse = FALSE) + +# Graph with loop +g5 <- graph(c(1, 1, 1, 2), directed = FALSE) +as_veincidence_matrix(g5, sparse = FALSE) + +} +\seealso{ +\code{\link[=as_adjacency_matrix]{as_adjacency_matrix()}}, \code{\link[=as_edgelist]{as_edgelist()}}, \code{\link[=laplacian_matrix]{laplacian_matrix()}} + +Other conversion: +\code{\link{as.matrix.igraph}()}, +\code{\link{as_adj_list}()}, +\code{\link{as_adjacency_matrix}()}, +\code{\link{as_biadjacency_matrix}()}, +\code{\link{as_data_frame}()}, +\code{\link{as_directed}()}, +\code{\link{as_edgelist}()}, +\code{\link{as_graphnel}()}, +\code{\link{as_long_data_frame}()}, +\code{\link{graph_from_adj_list}()}, +\code{\link{graph_from_graphnel}()} +} +\concept{conversion} +\concept{matrices} diff --git a/man/graph_from_adj_list.Rd b/man/graph_from_adj_list.Rd index f3881bdf42a..fd995444016 100644 --- a/man/graph_from_adj_list.Rd +++ b/man/graph_from_adj_list.Rd @@ -75,6 +75,7 @@ Other conversion: \code{\link{as_edgelist}()}, \code{\link{as_graphnel}()}, \code{\link{as_long_data_frame}()}, +\code{\link{as_veincidence_matrix}()}, \code{\link{graph_from_graphnel}()} } \author{ diff --git a/man/graph_from_data_frame.Rd b/man/graph_from_data_frame.Rd index 6aa7caeddbb..226264c43b7 100644 --- a/man/graph_from_data_frame.Rd +++ b/man/graph_from_data_frame.Rd @@ -137,6 +137,7 @@ Other conversion: \code{\link{as_edgelist}()}, \code{\link{as_graphnel}()}, \code{\link{as_long_data_frame}()}, +\code{\link{as_veincidence_matrix}()}, \code{\link{graph_from_adj_list}()}, \code{\link{graph_from_graphnel}()} diff --git a/man/graph_from_graphnel.Rd b/man/graph_from_graphnel.Rd index ef7b6d0f1ed..afed3ad6470 100644 --- a/man/graph_from_graphnel.Rd +++ b/man/graph_from_graphnel.Rd @@ -71,6 +71,7 @@ Other conversion: \code{\link{as_edgelist}()}, \code{\link{as_graphnel}()}, \code{\link{as_long_data_frame}()}, +\code{\link{as_veincidence_matrix}()}, \code{\link{graph_from_adj_list}()} } \concept{conversion} diff --git a/tests/testthat/test-ve-incidence.R b/tests/testthat/test-ve-incidence.R new file mode 100644 index 00000000000..ff7bfd9bc38 --- /dev/null +++ b/tests/testthat/test-ve-incidence.R @@ -0,0 +1,269 @@ +test_that("as_veincidence_matrix works for simple undirected graph", { + g <- make_ring(3, circular = FALSE) + inc <- as_veincidence_matrix(g, sparse = FALSE) + + expect_equal(nrow(inc), 3) + expect_equal(ncol(inc), 2) + + # Vertices 1 and 2 are incident to edge 1 + expect_equal(inc[1, 1], 1) + expect_equal(inc[2, 1], 1) + expect_equal(inc[3, 1], 0) + + # Vertices 2 and 3 are incident to edge 2 + expect_equal(inc[1, 2], 0) + expect_equal(inc[2, 2], 1) + expect_equal(inc[3, 2], 1) +}) + +test_that("as_veincidence_matrix works for simple directed graph", { + g <- make_ring(3, circular = FALSE, directed = TRUE) + inc <- as_veincidence_matrix(g, sparse = FALSE) + + expect_equal(nrow(inc), 3) + expect_equal(ncol(inc), 2) + + # Edge 1 goes from vertex 1 to vertex 2 + expect_equal(inc[1, 1], -1) + expect_equal(inc[2, 1], 1) + expect_equal(inc[3, 1], 0) + + # Edge 2 goes from vertex 2 to vertex 3 + expect_equal(inc[1, 2], 0) + expect_equal(inc[2, 2], -1) + expect_equal(inc[3, 2], 1) +}) + +test_that("as_veincidence_matrix works with weights for undirected graph", { + g <- make_ring(3, circular = FALSE) + E(g)$weight <- c(2, 3) + inc <- as_veincidence_matrix(g, attr = "weight", sparse = FALSE) + + expect_equal(inc[1, 1], 2) + expect_equal(inc[2, 1], 2) + expect_equal(inc[2, 2], 3) + expect_equal(inc[3, 2], 3) +}) + +test_that("as_veincidence_matrix works with weights for directed graph", { + g <- make_ring(3, circular = FALSE, directed = TRUE) + E(g)$weight <- c(2, 5) + inc <- as_veincidence_matrix(g, attr = "weight", sparse = FALSE) + + expect_equal(inc[1, 1], -2) + expect_equal(inc[2, 1], 2) + expect_equal(inc[2, 2], -5) + expect_equal(inc[3, 2], 5) +}) + +test_that("as_veincidence_matrix works with vertex names", { + g <- graph_from_literal(a-b, b-c, c-d) + inc <- as_veincidence_matrix(g, sparse = FALSE) + + expect_equal(rownames(inc), c("a", "b", "c", "d")) + expect_equal(ncol(inc), 3) +}) + +test_that("as_veincidence_matrix works with edge labels", { + g <- graph_from_literal(a-b, b-c) + E(g)$label <- c("e1", "e2") + inc <- as_veincidence_matrix(g, sparse = FALSE) + + expect_equal(colnames(inc), c("e1", "e2")) +}) + +test_that("as_veincidence_matrix works with undirected loops", { + g <- make_graph(c(1, 1, 1, 2), directed = FALSE) + inc <- as_veincidence_matrix(g, sparse = FALSE) + + expect_equal(nrow(inc), 2) + expect_equal(ncol(inc), 2) + + # First edge is a loop on vertex 1, should have value 2 + expect_equal(inc[1, 1], 2) + expect_equal(inc[2, 1], 0) + + # Second edge connects vertices 1 and 2 + expect_equal(inc[1, 2], 1) + expect_equal(inc[2, 2], 1) +}) + +test_that("as_veincidence_matrix works with directed loops", { + g <- make_graph(c(1, 1, 1, 2), directed = TRUE) + inc <- as_veincidence_matrix(g, sparse = FALSE) + + expect_equal(nrow(inc), 2) + expect_equal(ncol(inc), 2) + + # First edge is a loop on vertex 1, should have value 0 + expect_equal(inc[1, 1], 0) + expect_equal(inc[2, 1], 0) + + # Second edge goes from vertex 1 to vertex 2 + expect_equal(inc[1, 2], -1) + expect_equal(inc[2, 2], 1) +}) + +test_that("as_veincidence_matrix works with sparse matrices", { + g <- make_ring(5, circular = FALSE) + inc_sparse <- as_veincidence_matrix(g, sparse = TRUE) + inc_dense <- as_veincidence_matrix(g, sparse = FALSE) + + expect_true(inherits(inc_sparse, "Matrix")) + expect_true(inherits(inc_sparse, "sparseMatrix")) + expect_equal(as.matrix(inc_sparse), inc_dense) +}) + +test_that("as_veincidence_matrix works with multi-edges", { + g <- make_graph(c(1, 2, 1, 2, 2, 3), directed = FALSE) + inc <- as_veincidence_matrix(g, sparse = FALSE) + + expect_equal(nrow(inc), 3) + expect_equal(ncol(inc), 3) + + # Two edges between vertices 1 and 2 + expect_equal(inc[1, 1], 1) + expect_equal(inc[2, 1], 1) + expect_equal(inc[1, 2], 1) + expect_equal(inc[2, 2], 1) + + # One edge between vertices 2 and 3 + expect_equal(inc[2, 3], 1) + expect_equal(inc[3, 3], 1) +}) + +test_that("as_veincidence_matrix works with weighted multi-edges", { + g <- make_graph(c(1, 2, 1, 2, 2, 3), directed = TRUE) + E(g)$weight <- c(2, 3, 5) + inc <- as_veincidence_matrix(g, attr = "weight", sparse = FALSE) + + expect_equal(inc[1, 1], -2) + expect_equal(inc[2, 1], 2) + expect_equal(inc[1, 2], -3) + expect_equal(inc[2, 2], 3) + expect_equal(inc[2, 3], -5) + expect_equal(inc[3, 3], 5) +}) + +test_that("as_veincidence_matrix works with empty graph", { + g <- make_empty_graph(5) + inc <- as_veincidence_matrix(g, sparse = FALSE) + + expect_equal(nrow(inc), 5) + expect_equal(ncol(inc), 0) +}) + +test_that("as_veincidence_matrix fails with non-numeric edge attribute", { + g <- make_ring(3, circular = FALSE) + E(g)$label <- c("a", "b") + + expect_error( + as_veincidence_matrix(g, attr = "label"), + "must be numeric" + ) +}) + +test_that("as_veincidence_matrix fails with non-existent edge attribute", { + g <- make_ring(3, circular = FALSE) + + expect_error( + as_veincidence_matrix(g, attr = "nonexistent"), + "No such edge attribute" + ) +}) + +test_that("as_veincidence_matrix relationship with Laplacian", { + # For a graph's incidence matrix B: + # - For undirected graphs: B * B^T = D + A (signless Laplacian), not D - A + # - For directed graphs: B * B^T gives a symmetric matrix (not the out-Laplacian) + g <- make_ring(4, circular = TRUE) + + B <- as_veincidence_matrix(g, sparse = FALSE, names = FALSE) + + # For undirected graphs: B * B^T gives the signless Laplacian Q = D + A + Q_computed <- B %*% t(B) + + # Verify it's positive semidefinite (all diagonal elements are positive) + expect_true(all(diag(Q_computed) > 0)) + + # Verify dimensions + expect_equal(nrow(B), vcount(g)) + expect_equal(ncol(B), ecount(g)) + expect_equal(nrow(Q_computed), vcount(g)) + expect_equal(ncol(Q_computed), vcount(g)) + + # Verify symmetry + expect_true(isSymmetric(Q_computed)) +}) + +test_that("as_veincidence_matrix relationship with weighted Laplacian", { + # For weighted graphs, just verify dimensions and basic properties + g <- make_ring(4, circular = TRUE) + E(g)$weight <- c(1, 2, 3, 4) + + B_w <- as_veincidence_matrix(g, attr = "weight", sparse = FALSE) + L <- laplacian_matrix(g, weights = E(g)$weight, sparse = FALSE) + + # Verify dimensions match + expect_equal(nrow(B_w), vcount(g)) + expect_equal(ncol(B_w), ecount(g)) + expect_equal(nrow(L), vcount(g)) + expect_equal(ncol(L), vcount(g)) + + # Verify B_w * B_w^T is symmetric for undirected graphs + Q <- B_w %*% t(B_w) + expect_true(isSymmetric(Q)) +}) + +test_that("as_veincidence_matrix names parameter works", { + g <- graph_from_literal(a-b, b-c) + E(g)$label <- c("e1", "e2") + + inc_named <- as_veincidence_matrix(g, names = TRUE, sparse = FALSE) + inc_unnamed <- as_veincidence_matrix(g, names = FALSE, sparse = FALSE) + + expect_equal(rownames(inc_named), c("a", "b", "c")) + expect_equal(colnames(inc_named), c("e1", "e2")) + expect_null(rownames(inc_unnamed)) + expect_null(colnames(inc_unnamed)) +}) + +test_that("as_veincidence_matrix examples from issue work correctly", { + # Example g2: Undirected, multi edge + g2 <- make_graph(c(1, 2, 1, 2, 2, 3), directed = FALSE) + inc2 <- as_veincidence_matrix(g2, sparse = FALSE, names = FALSE) + + expected2 <- matrix(c(1, 1, 0, 1, 1, 0, 0, 1, 1), nrow = 3, ncol = 3) + expect_equal(inc2, expected2) + + # Example g4w: Directed, multi edge, weighted + g4w <- make_graph(c(1, 2, 1, 2, 2, 3), directed = TRUE) + E(g4w)$weight <- c(2, 3, 5) + E(g4w)$label <- c("2", "3", "5") + inc4w <- as_veincidence_matrix(g4w, attr = "weight", sparse = FALSE, names = FALSE) + + expected4w <- matrix(c(-2, 2, 0, -3, 3, 0, 0, -5, 5), nrow = 3, ncol = 3) + expect_equal(inc4w, expected4w) + + # Example g6: Named graph, directed + g6 <- graph_from_literal(a-+b-+c-+a, a-+d, simplify = FALSE) + E(g6)$label <- c("1", "2", "3", "4") + inc6 <- as_veincidence_matrix(g6, sparse = FALSE) + + expect_equal(rownames(inc6), c("a", "b", "c", "d")) + expect_equal(colnames(inc6), c("1", "2", "3", "4")) + + # Example g7: Undirected graph with loops + g7 <- make_graph(c(1, 1, 1, 1, 1, 2, 1, 2), directed = FALSE) + inc7 <- as_veincidence_matrix(g7, sparse = FALSE, names = FALSE) + + expected7 <- matrix(c(2, 0, 2, 0, 1, 1, 1, 1), nrow = 2, ncol = 4) + expect_equal(inc7, expected7) + + # Example g8: Directed graph with loops + g8 <- make_graph(c(1, 1, 1, 1, 1, 2, 1, 2), directed = TRUE) + inc8 <- as_veincidence_matrix(g8, sparse = FALSE, names = FALSE) + + expected8 <- matrix(c(0, 0, 0, 0, -1, 1, -1, 1), nrow = 2, ncol = 4) + expect_equal(inc8, expected8) +})