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
20 changes: 16 additions & 4 deletions R/basic.R
Original file line number Diff line number Diff line change
Expand Up @@ -77,13 +77,19 @@ get.edge <- function(graph, id) {
#'
#' @param graph The input graph.
#' @param es The edges to query.
#' @return A vertex sequence with the head(s) of the edge(s).
#' @return A vertex sequence with the head(s) of the edge(s) if
#' the `return.vs.es` igraph option is true (the default), or a numeric
#' vector of vertex IDs otherwise.
#'
#' @family structural queries
#'
#' @export
head_of <- function(graph, es) {
create_vs(graph, ends(graph, es, names = FALSE)[, 2])
res <- ends(graph, es, names = FALSE)[, 2]
if (igraph_opt("return.vs.es")) {
res <- create_vs(graph, res)
}
res
}

#' Tails of the edge(s) in a graph
Expand All @@ -94,11 +100,17 @@ head_of <- function(graph, es) {
#'
#' @param graph The input graph.
#' @param es The edges to query.
#' @return A vertex sequence with the tail(s) of the edge(s).
#' @return A vertex sequence with the tail(s) of the edge(s) if
#' the `return.vs.es` igraph option is true (the default), or a numeric
#' vector of vertex IDs otherwise.
#'
#' @family structural queries
#'
#' @export
tail_of <- function(graph, es) {
create_vs(graph, ends(graph, es, names = FALSE)[, 1])
res <- ends(graph, es, names = FALSE)[, 1]
if (igraph_opt("return.vs.es")) {
res <- create_vs(graph, res)
}
res
}
13 changes: 10 additions & 3 deletions R/conversion.R
Original file line number Diff line number Diff line change
Expand Up @@ -651,7 +651,9 @@ as_undirected <- function(
#'
#' `as_adj_edge_list()` returns a list of numeric vectors, which include the
#' ids of adjacent edges (according to the `mode` argument) of all
#' vertices.
#' vertices. The return type depends on the `return.vs.es` option: if true
#' (default), a list of `igraph.es` is returned; if false, a list of numeric
#' vectors is returned.
#'
#' @param graph The input graph.
#' @param mode Character scalar, it gives what kind of adjacent edges/vertices
Expand All @@ -663,7 +665,8 @@ as_undirected <- function(
#' is not allowed for directed graphs and will be replaced with `"once"`.
#' @param multiple Logical scalar, set to `FALSE` to use only one representative
#' of each set of parallel edges.
#' @return A list of `igraph.vs` or a list of numeric vectors depending on
#' @return A list of `igraph.vs` (for `as_adj_list()`) or `igraph.es`
#' (for `as_adj_edge_list()`), or a list of numeric vectors depending on
#' the value of `igraph_opt("return.vs.es")`, see details for performance
#' characteristics.
#' @details If `igraph_opt("return.vs.es")` is true (default), the numeric
Expand Down Expand Up @@ -730,7 +733,11 @@ as_adj_edge_list <- function(

on.exit(.Call(R_igraph_finalizer))
res <- .Call(R_igraph_get_adjedgelist, graph, mode, loops)
res <- lapply(res, function(.x) E(graph)[.x + 1])
if (igraph_opt("return.vs.es")) {
res <- lapply(res, function(.x) E(graph)[.x + 1])
} else {
res <- lapply(res, `+`, 1)
}
if (is_named(graph)) {
names(res) <- V(graph)$name
}
Expand Down
32 changes: 25 additions & 7 deletions R/topology.R
Original file line number Diff line number Diff line change
Expand Up @@ -192,7 +192,12 @@ graph.get.isomorphisms.vf2 <- function(
edge.color2
)

lapply(res, function(.x) V(graph2)[.x + 1])
if (igraph_opt("return.vs.es")) {
res <- lapply(res, function(.x) V(graph2)[.x + 1])
} else {
res <- lapply(res, `+`, 1)
}
res
}

#' @export
Expand Down Expand Up @@ -260,7 +265,12 @@ graph.get.subisomorphisms.vf2 <- function(
edge.color2
)

lapply(res, function(.x) V(graph1)[.x + 1])
if (igraph_opt("return.vs.es")) {
res <- lapply(res, function(.x) V(graph1)[.x + 1])
} else {
res <- lapply(res, `+`, 1)
}
res
}

#' @export
Expand Down Expand Up @@ -330,7 +340,11 @@ graph.subisomorphic.lad <- function(
}
}
if (all.maps) {
res$maps <- lapply(res$maps, function(.x) V(target)[.x + 1])
if (igraph_opt("return.vs.es")) {
res$maps <- lapply(res$maps, function(.x) V(target)[.x + 1])
} else {
res$maps <- lapply(res$maps, `+`, 1)
}
}

res
Expand Down Expand Up @@ -854,8 +868,10 @@ graph.count.subisomorphisms.vf2 <- function(
#' @param method Currently only \sQuote{vf2} is supported, see
#' [isomorphic()] for details about it and extra arguments.
#' @param ... Extra arguments, passed to the various methods.
#' @return A list of vertex sequences, corresponding to all
#' mappings from the first graph to the second.
#' @return A list of vertex sequences (if the `return.vs.es` igraph option is
#' true, the default), or a list of numeric vectors of vertex IDs (if
#' `return.vs.es` is false), corresponding to all mappings from the first
#' graph to the second.
#'
#' @aliases graph.get.isomorphisms.vf2
#'
Expand Down Expand Up @@ -920,8 +936,10 @@ isomorphisms <- function(graph1, graph2, method = "vf2", ...) {
#' @param method The method to use. Possible values: \sQuote{auto},
#' \sQuote{lad}, \sQuote{vf2}. See their details below.
#' @param ... Additional arguments, passed to the various methods.
#' @return A list of vertex sequences, corresponding to all
#' mappings from the first graph to the second.
#' @return A list of vertex sequences (if the `return.vs.es` igraph option is
#' true, the default), or a list of numeric vectors of vertex IDs (if
#' `return.vs.es` is false), corresponding to all mappings from the first
#' graph to the second.
#'
#' @aliases graph.get.subisomorphisms.vf2
#'
Expand Down
7 changes: 5 additions & 2 deletions man/as_adj_list.Rd

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

4 changes: 3 additions & 1 deletion man/head_of.Rd

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

6 changes: 4 additions & 2 deletions man/isomorphisms.Rd

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

6 changes: 4 additions & 2 deletions man/subgraph_isomorphisms.Rd

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

4 changes: 3 additions & 1 deletion man/tail_of.Rd

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

18 changes: 18 additions & 0 deletions tests/testthat/test-conversion.R
Original file line number Diff line number Diff line change
Expand Up @@ -444,6 +444,24 @@ test_that("as_adj_list works when return.vs.es is FALSE", {
}
})

test_that("as_adj_edge_list respects return.vs.es option", {
g <- make_tree(6, children = 2)
V(g)$name <- paste0("V", 1:6)

# Test with return.vs.es = TRUE (default)
local_igraph_options(return.vs.es = TRUE)
adj_el_list <- as_adj_edge_list(g)
expect_s3_class(adj_el_list[[1]], "igraph.es")
expect_length(adj_el_list[[1]], 2)

# Test with return.vs.es = FALSE
local_igraph_options(return.vs.es = FALSE)
adj_el_list <- as_adj_edge_list(g)
expect_type(adj_el_list[[1]], "integer")
expect_length(adj_el_list[[1]], 2)
expect_equal(as.numeric(adj_el_list[[1]]), c(1, 2))
})

test_that("as_edgelist works", {
g <- sample_gnp(100, 3 / 100)
el <- as_edgelist(g)
Expand Down
36 changes: 36 additions & 0 deletions tests/testthat/test-interface.R
Original file line number Diff line number Diff line change
Expand Up @@ -222,3 +222,39 @@ test_that("get_edge_id() errors correctly for wrong matrices", {
mat <- matrix(c(1, 2, 1, 3, 1, 4), nrow = 2, ncol = 3)
lifecycle::expect_deprecated(get_edge_ids(g, mat))
})

test_that("head_of respects return.vs.es option", {
g <- make_tree(6, children = 2)
V(g)$name <- paste0("V", 1:6)

# Test with return.vs.es = TRUE (default)
local_igraph_options(return.vs.es = TRUE)
result <- head_of(g, E(g)[c(1, 4)])
expect_s3_class(result, "igraph.vs")
expect_length(result, 2)

# Test with return.vs.es = FALSE
local_igraph_options(return.vs.es = FALSE)
result <- head_of(g, E(g)[c(1, 4)])
expect_type(result, "integer")
expect_length(result, 2)
expect_equal(as.numeric(result), c(2, 5))
})

test_that("tail_of respects return.vs.es option", {
g <- make_tree(6, children = 2)
V(g)$name <- paste0("V", 1:6)

# Test with return.vs.es = TRUE (default)
local_igraph_options(return.vs.es = TRUE)
result <- tail_of(g, E(g)[c(1, 4)])
expect_s3_class(result, "igraph.vs")
expect_length(result, 2)

# Test with return.vs.es = FALSE
local_igraph_options(return.vs.es = FALSE)
result <- tail_of(g, E(g)[c(1, 4)])
expect_type(result, "integer")
expect_length(result, 2)
expect_equal(as.numeric(result), c(1, 2))
})
49 changes: 49 additions & 0 deletions tests/testthat/test-topology.R
Original file line number Diff line number Diff line change
Expand Up @@ -361,3 +361,52 @@ test_that("subgraph_isomorphisms, vf2", {
g3 <- graph_from_literal(X - Y - Z - X)
expect_equal(subgraph_isomorphisms(g3, g1, method = "vf2"), list())
})

test_that("graph.get.isomorphisms.vf2 respects return.vs.es option", {
g <- make_tree(6, children = 2)
V(g)$name <- paste0("V", 1:6)

# Test with return.vs.es = TRUE (default)
local_igraph_options(return.vs.es = TRUE)
result <- graph.get.isomorphisms.vf2(g, g)
expect_s3_class(result[[1]], "igraph.vs")
expect_length(result[[1]], 6)

# Test with return.vs.es = FALSE
local_igraph_options(return.vs.es = FALSE)
result <- graph.get.isomorphisms.vf2(g, g)
expect_type(result[[1]], "integer")
expect_length(result[[1]], 6)
})

test_that("graph.get.subisomorphisms.vf2 respects return.vs.es option", {
g <- make_tree(6, children = 2)

# Test with return.vs.es = TRUE (default)
local_igraph_options(return.vs.es = TRUE)
result <- graph.get.subisomorphisms.vf2(g, g)
expect_s3_class(result[[1]], "igraph.vs")
expect_length(result[[1]], 6)

# Test with return.vs.es = FALSE
local_igraph_options(return.vs.es = FALSE)
result <- graph.get.subisomorphisms.vf2(g, g)
expect_type(result[[1]], "integer")
expect_length(result[[1]], 6)
})

test_that("graph.subisomorphic.lad respects return.vs.es option", {
g <- make_tree(6, children = 2)

# Test with return.vs.es = TRUE (default)
local_igraph_options(return.vs.es = TRUE)
result <- graph.subisomorphic.lad(g, g, all.maps = TRUE)
expect_s3_class(result$maps[[1]], "igraph.vs")
expect_length(result$maps[[1]], 6)

# Test with return.vs.es = FALSE
local_igraph_options(return.vs.es = FALSE)
result <- graph.subisomorphic.lad(g, g, all.maps = TRUE)
expect_type(result$maps[[1]], "integer")
expect_length(result$maps[[1]], 6)
})