Skip to content

Commit c7ae980

Browse files
Copilotkrlmlr
andauthored
feat: add count_reachable() function to R (#2412)
Co-authored-by: copilot-swe-agent[bot] <[email protected]> Co-authored-by: krlmlr <[email protected]> Co-authored-by: Kirill Müller <[email protected]>
1 parent d04948d commit c7ae980

File tree

9 files changed

+170
-0
lines changed

9 files changed

+170
-0
lines changed

NAMESPACE

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -275,6 +275,7 @@ export(count_isomorphisms)
275275
export(count_max_cliques)
276276
export(count_motifs)
277277
export(count_multiple)
278+
export(count_reachable)
278279
export(count_subgraph_isomorphisms)
279280
export(count_triangles)
280281
export(create.communities)

R/structural-properties.R

Lines changed: 51 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3161,6 +3161,57 @@ count_components <- function(graph, mode = c("weak", "strong")) {
31613161
.Call(Rx_igraph_no_components, graph, mode)
31623162
}
31633163

3164+
#' Count reachable vertices
3165+
#'
3166+
#' `r lifecycle::badge("experimental")`
3167+
#'
3168+
#' Counts the number of vertices reachable from each vertex in the graph.
3169+
#'
3170+
#' For each vertex in the graph, this function counts how many vertices
3171+
#' are reachable from it, including the vertex itself.
3172+
#' A vertex is reachable from another if there is a directed path between them.
3173+
#' For undirected graphs, two vertices are reachable from each other if they
3174+
#' are in the same connected component.
3175+
#'
3176+
#' @param graph The input graph.
3177+
#' @param mode Character constant, defines how edge directions are considered
3178+
#' in directed graphs.
3179+
#' `"out"` counts vertices reachable via outgoing edges,
3180+
#' `"in"` counts vertices from which the current vertex is reachable via
3181+
#' incoming edges,
3182+
#' `"all"` or `"total"` ignores edge directions.
3183+
#' This parameter is ignored for undirected graphs.
3184+
#' @return An integer vector of length `vcount(graph)`.
3185+
#' The i-th element is the number of vertices reachable from vertex i
3186+
#' (including vertex i itself).
3187+
#' @author Gabor Csardi \email{csardi.gabor@@gmail.com}
3188+
#' @seealso [components()], [subcomponent()], [is_connected()]
3189+
#' @family components
3190+
#' @export
3191+
#' @keywords graphs
3192+
#' @examples
3193+
#'
3194+
#' # In a directed path graph, the reachability depends on direction
3195+
#' g <- make_graph(~ 1 -+ 2 -+ 3 -+ 4 -+ 5)
3196+
#' count_reachable(g, mode = "out")
3197+
#' count_reachable(g, mode = "in")
3198+
#'
3199+
#' # In an undirected graph, reachability is the same in all directions
3200+
#' g2 <- make_graph(~ 1 - 2 - 3 - 4 - 5)
3201+
#' count_reachable(g2, mode = "out")
3202+
#'
3203+
#' # A graph with multiple components
3204+
#' g3 <- make_graph(~ 1 - 2 - 3, 4 - 5, 6)
3205+
#' count_reachable(g3, mode = "all")
3206+
#'
3207+
#' @cdocs igraph_count_reachable
3208+
count_reachable <- function(graph, mode = c("out", "in", "all", "total")) {
3209+
count_reachable_impl(
3210+
graph = graph,
3211+
mode = mode
3212+
)
3213+
}
3214+
31643215
#' Convert a general graph into a forest
31653216
#'
31663217
#' Perform a breadth-first search on a graph and convert it into a tree or

man/articulation_points.Rd

Lines changed: 1 addition & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/biconnected_components.Rd

Lines changed: 1 addition & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/components.Rd

Lines changed: 1 addition & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/count_reachable.Rd

Lines changed: 69 additions & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/decompose.Rd

Lines changed: 1 addition & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/is_biconnected.Rd

Lines changed: 1 addition & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

tests/testthat/test-structural-properties.R

Lines changed: 44 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -730,6 +730,50 @@ test_that("a null graph has zero components", {
730730
expect_equal(count_components(g), 0L)
731731
})
732732

733+
test_that("count_reachable() works for directed graphs", {
734+
# Directed path graph: 1 -> 2 -> 3 -> 4 -> 5
735+
g <- make_graph(~ 1 -+ 2 -+ 3 -+ 4 -+ 5)
736+
737+
# Out mode: count vertices reachable via outgoing edges
738+
out_counts <- count_reachable(g, mode = "out")
739+
expect_equal(out_counts, c(5, 4, 3, 2, 1))
740+
741+
# In mode: count vertices from which current vertex is reachable
742+
in_counts <- count_reachable(g, mode = "in")
743+
expect_equal(in_counts, c(1, 2, 3, 4, 5))
744+
745+
# All mode: treat as undirected
746+
all_counts <- count_reachable(g, mode = "all")
747+
expect_equal(all_counts, rep(5, 5))
748+
})
749+
750+
test_that("count_reachable() works for undirected graphs", {
751+
# Undirected path graph
752+
g <- make_graph(~ 1 - 2 - 3 - 4 - 5)
753+
754+
# All vertices are reachable from each other in an undirected path
755+
counts <- count_reachable(g, mode = "out")
756+
expect_equal(counts, rep(5, 5))
757+
})
758+
759+
test_that("count_reachable() works for graphs with multiple components", {
760+
# Graph with three components: 1-2-3, 4-5, 6
761+
g <- make_graph(~ 1 - 2 - 3, 4 - 5, 6)
762+
763+
counts <- count_reachable(g, mode = "all")
764+
expect_equal(counts, c(3, 3, 3, 2, 2, 1))
765+
})
766+
767+
test_that("count_reachable() works for empty and single-vertex graphs", {
768+
# Empty graph
769+
g0 <- make_empty_graph(0)
770+
expect_equal(count_reachable(g0, mode = "out"), integer(0))
771+
772+
# Single vertex
773+
g1 <- make_empty_graph(1)
774+
expect_equal(count_reachable(g1, mode = "out"), 1L)
775+
})
776+
733777
test_that("girth() works", {
734778
## No circle in a tree
735779
g <- make_tree(1000, 3)

0 commit comments

Comments
 (0)