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
15 changes: 15 additions & 0 deletions R/operators.R
Original file line number Diff line number Diff line change
Expand Up @@ -1161,6 +1161,14 @@ path <- function(...) {
e2[named]
)

# Abort if adding named vertices to a non-empty unnamed graph
# Empty graphs have zero vertices
if (!is.null(nn) && !is_named(e1) && vcount(e1) > 0) {
cli::cli_abort(
"Cannot add named vertices to a non-empty unnamed graph. Existing vertices will have {.code NA} names."
)
}

# When adding vertices via +, all unnamed arguments are interpreted as vertex names of the new vertices.
res <- add_vertices(e1, nv = vctrs::vec_size_common(!!!e2), attr = e2)
} else if ("igraph.path" %in% class(e2)) {
Expand Down Expand Up @@ -1188,6 +1196,13 @@ path <- function(...) {
res <- add_vertices(e1, e2)
} else if (is.character(e2)) {
## Adding named vertices
# Abort if adding named vertices to a non-empty unnamed graph
# Empty graphs have zero vertices
if (!is_named(e1) && vcount(e1) > 0) {
cli::cli_abort(
"Cannot add named vertices to a non-empty unnamed graph. Existing vertices will have {.code NA} names."
)
}
res <- add_vertices(e1, length(e2), name = e2)
} else {
cli::cli_abort("Cannot add {.obj_type_friendly {type}} to igraph graph.")
Expand Down
28 changes: 28 additions & 0 deletions tests/testthat/_snaps/operators.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,10 @@

Can't recycle `name` (size 2) to match `foo` (size 3).

---

Cannot add named vertices to a non-empty unnamed graph. Existing vertices will have `NA` names.

# vertices() errors on duplicate attribute names

Duplicate attribute name in `vertices()`: "name".
Expand All @@ -18,3 +22,27 @@

Duplicate attribute names in `vertices()`: "foo" and "bar".

# adding named vertices to non-empty unnamed graphs errors

Cannot add named vertices to a non-empty unnamed graph. Existing vertices will have `NA` names.

---

Cannot add named vertices to a non-empty unnamed graph. Existing vertices will have `NA` names.

---

Cannot add named vertices to a non-empty unnamed graph. Existing vertices will have `NA` names.

---

Cannot add named vertices to a non-empty unnamed graph. Existing vertices will have `NA` names.

---

Cannot add named vertices to a non-empty unnamed graph. Existing vertices will have `NA` names.

---

Cannot add named vertices to a non-empty unnamed graph. Existing vertices will have `NA` names.

76 changes: 63 additions & 13 deletions tests/testthat/test-operators.R
Original file line number Diff line number Diff line change
Expand Up @@ -214,27 +214,28 @@ test_that("t() is aliased to edge reversal for graphs", {
})

test_that("vertices() works", {
g_all_unnamed <- make_empty_graph(1) + vertices("a", "b")
# Test adding named vertices to empty graph (0 vertices)
g_all_unnamed <- make_empty_graph() + vertices("a", "b")
expect_s3_class(V(g_all_unnamed), "igraph.vs")
expect_identical(V(g_all_unnamed)$name, c(NA, "a", "b"))
expect_identical(V(g_all_unnamed)$name, c("a", "b"))

g_mix_named_unnamed <- make_empty_graph(1) + vertices("a", "b", foo = 5)
g_mix_named_unnamed <- make_empty_graph() + vertices("a", "b", foo = 5)
expect_s3_class(V(g_mix_named_unnamed), "igraph.vs")
expect_true(is.na(V(g_mix_named_unnamed)$name[1]))
expect_identical(V(g_mix_named_unnamed)$name[-1], c("a", "b"))
expect_equal(V(g_mix_named_unnamed)$foo, c(NA, 5, 5))
expect_identical(V(g_mix_named_unnamed)$name, c("a", "b"))
expect_equal(V(g_mix_named_unnamed)$foo, c(5, 5))

g_mix_bigger_attribute <- make_empty_graph(1) +
g_mix_bigger_attribute <- make_empty_graph() +
vertices("a", "b", "c", foo = 5:7, bar = 8)
expect_s3_class(V(g_mix_bigger_attribute), "igraph.vs")
expect_identical(V(g_mix_bigger_attribute)$name, c(NA, "a", "b", "c"))
expect_equal(V(g_mix_bigger_attribute)$foo, c(NA, 5, 6, 7))
expect_equal(V(g_mix_bigger_attribute)$bar, c(NA, 8, 8, 8))
expect_identical(V(g_mix_bigger_attribute)$name, c("a", "b", "c"))
expect_equal(V(g_mix_bigger_attribute)$foo, c(5, 6, 7))
expect_equal(V(g_mix_bigger_attribute)$bar, c(8, 8, 8))

g_one_unnamed <- make_empty_graph(1) + vertices(letters)
g_one_unnamed <- make_empty_graph() + vertices(letters)
expect_s3_class(V(g_one_unnamed), "igraph.vs")
expect_identical(V(g_one_unnamed)$name, c(NA, letters))
expect_identical(V(g_one_unnamed)$name, letters)

# Test adding unnamed vertices (attributes only) - should work with any graph
g_all_named <- make_empty_graph(1) + vertices(foo = 5:7)
expect_s3_class(V(g_all_named), "igraph.vs")
expect_null(V(g_all_named)$name)
Expand All @@ -249,7 +250,15 @@ test_that("vertices() works", {
expect_s3_class(V(g_none), "igraph.vs")
expect_null(V(g_none)$name)

expect_snapshot_error(make_empty_graph(1) + vertices("a", "b", foo = 5:7))
# Test that adding named vertices to non-empty graph with mismatched attributes errors
expect_snapshot_error(
make_empty_graph() + vertices("a", "b", foo = 5:7)
)

# Test that adding named vertices to non-empty unnamed graph errors
expect_snapshot_error(
make_empty_graph(1) + vertices("a", "b")
)
})

test_that("vertices() errors on duplicate attribute names", {
Expand All @@ -274,6 +283,47 @@ test_that("vertices() errors on duplicate attribute names", {
)
})

test_that("adding named vertices to non-empty unnamed graphs errors", {
# Test with vertex() function
expect_snapshot_error(
make_ring(10) + vertex(1)
)

expect_snapshot_error(
make_ring(10) + vertex("a")
)

expect_snapshot_error(
make_ring(10) + vertices("a", "b")
)

# Test with character vector
expect_snapshot_error(
make_ring(10) + c("a", "b")
)

# No error when adding to named graph
g <- make_ring(10)
V(g)$name <- letters[1:10]
expect_no_error(g + vertex("k"))
expect_no_error(g + c("x", "y"))

# No error when adding unnamed vertices
expect_no_error(make_ring(10) + vertex(foo = 5))
expect_no_error(make_ring(10) + vertices(foo = 1:3))
expect_no_error(make_ring(10) + 5)

# No error when adding to empty graph (0 vertices)
expect_no_error(make_empty_graph() + vertex("a"))
expect_no_error(make_empty_graph() + c("a", "b"))
expect_no_error(make_empty_graph() + vertices("a", "b"))

# Error when adding to non-empty unnamed graph (even with 1 vertex)
expect_snapshot_error(make_empty_graph(1) + vertex("a"))
expect_snapshot_error(make_empty_graph(1) + c("a", "b"))
})


test_that("infix operators work", {
g <- make_ring(10)
V(g)$name <- letters[1:10]
Expand Down