Skip to content
Draft
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
42 changes: 35 additions & 7 deletions R/conversion.R
Original file line number Diff line number Diff line change
Expand Up @@ -473,8 +473,15 @@ as_adj <- function(
#' @param names Whether to return a character matrix containing vertex
#' names (i.e. the `name` vertex attribute) if they exist or numeric
#' vertex ids.
#' @return A `ecount(graph)` by 2 numeric matrix.
#' @seealso [graph_from_adjacency_matrix()], [read_graph()]
#' @param as.vector Logical scalar, whether to return the edge list as a vector
#' instead of a matrix.
#' When `TRUE`, the result is a vector in the format `c(from1, to1, from2, to2, ...)`
#' which is suitable for passing to [make_graph()].
#' When `FALSE` (the default), the result is an `ecount(graph)` by 2 matrix.
#' @return If `as.vector` is `FALSE` (the default), an `ecount(graph)` by 2 numeric matrix.
#' If `as.vector` is `TRUE`, a vector of length `2 * ecount(graph)` with edges
#' in the format `c(from1, to1, from2, to2, ...)`.
#' @seealso [graph_from_adjacency_matrix()], [read_graph()], [make_graph()]
#' @keywords graphs
#' @examples
#'
Expand All @@ -484,15 +491,36 @@ as_adj <- function(
#' V(g)$name <- LETTERS[seq_len(gorder(g))]
#' as_edgelist(g)
#'
#' # Get edges as a vector suitable for make_graph()
#' g2 <- make_graph(c(1, 2, 2, 3, 3, 4))
#' edges <- as_edgelist(g2, names = FALSE, as.vector = TRUE)
#' g3 <- make_graph(edges)
#' identical_graphs(g2, g3)
#'
#' @family conversion
#' @export
as_edgelist <- function(graph, names = TRUE) {
as_edgelist <- function(graph, names = TRUE, as.vector = FALSE) {
ensure_igraph(graph)
on.exit(.Call(R_igraph_finalizer))
res <- matrix(.Call(R_igraph_get_edgelist, graph, TRUE), ncol = 2)
res <- res + 1
if (names && "name" %in% vertex_attr_names(graph)) {
res <- matrix(V(graph)$name[res], ncol = 2)

if (as.vector) {
# Return as a flat vector suitable for make_graph()
# The FALSE parameter tells R_igraph_get_edgelist to return edges in column-major order,
# which produces the format: c(from1, to1, from2, to2, ...)
res <- .Call(R_igraph_get_edgelist, graph, FALSE)
res <- res + 1
if (names && "name" %in% vertex_attr_names(graph)) {
res <- V(graph)$name[res]
}
} else {
# Return as a matrix (original behavior)
# The TRUE parameter tells R_igraph_get_edgelist to return edges in row-major order,
# which can be directly converted to a matrix with edges as rows
res <- matrix(.Call(R_igraph_get_edgelist, graph, TRUE), ncol = 2)
res <- res + 1
if (names && "name" %in% vertex_attr_names(graph)) {
res <- matrix(V(graph)$name[res], ncol = 2)
}
}

res
Expand Down
20 changes: 17 additions & 3 deletions man/as_edgelist.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

34 changes: 34 additions & 0 deletions tests/testthat/test-conversion.R
Original file line number Diff line number Diff line change
Expand Up @@ -451,6 +451,40 @@ test_that("as_edgelist works", {
expect_isomorphic(g, g2)
})

test_that("as_edgelist with as.vector = TRUE works", {
# Test basic functionality with numeric vertices
g <- make_graph(c(1, 2, 2, 3, 3, 4, 4, 5))
edges_vec <- as_edgelist(g, names = FALSE, as.vector = TRUE)
expect_equal(edges_vec, c(1, 2, 2, 3, 3, 4, 4, 5))
expect_type(edges_vec, "double")

# Test that we can recreate the graph
g2 <- make_graph(edges_vec)
expect_identical_graphs(g, g2)

# Test with named vertices
V(g)$name <- letters[1:5]
edges_vec_named <- as_edgelist(g, names = TRUE, as.vector = TRUE)
expect_equal(edges_vec_named, c("a", "b", "b", "c", "c", "d", "d", "e"))
expect_type(edges_vec_named, "character")

# Test with empty graph
g_empty <- make_graph(c(), n = 3)
edges_empty <- as_edgelist(g_empty, names = FALSE, as.vector = TRUE)
expect_equal(edges_empty, numeric(0))

# Test default behavior unchanged (as.vector = FALSE)
el_matrix <- as_edgelist(g, names = FALSE)
expect_true(is.matrix(el_matrix))
expect_equal(ncol(el_matrix), 2)

# Test that as.vector = TRUE is more efficient than t()
g_large <- sample_gnp(100, 3 / 100)
edges_direct <- as_edgelist(g_large, names = FALSE, as.vector = TRUE)
edges_transpose <- as.vector(t(as_edgelist(g_large, names = FALSE)))
expect_equal(edges_direct, edges_transpose)
})

test_that("as_biadjacency_matrix() works -- dense", {
biadj_mat <- matrix(sample(0:1, 35, replace = TRUE, prob = c(3, 1)), ncol = 5)
g <- graph_from_biadjacency_matrix(biadj_mat)
Expand Down