Skip to content

Commit

Permalink
feat: is_biconnected()
Browse files Browse the repository at this point in the history
  • Loading branch information
szhorvat committed Feb 5, 2024
1 parent 2f785a2 commit 5f6af72
Show file tree
Hide file tree
Showing 10 changed files with 169 additions and 6 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -70,5 +70,5 @@ Config/testthat/start-first: vs-es, scan, vs-operators, weakref,
watts.strogatz.game
Encoding: UTF-8
Roxygen: list(markdown = TRUE)
RoxygenNote: 7.3.0.9000
RoxygenNote: 7.3.1
SystemRequirements: gmp, libxml2, glpk (>= 4.57)
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -536,6 +536,7 @@ export(is.separator)
export(is.simple)
export(is.weighted)
export(is_acyclic)
export(is_biconnected)
export(is_bipartite)
export(is_chordal)
export(is_connected)
Expand Down
26 changes: 26 additions & 0 deletions R/aaa-auto.R
Original file line number Diff line number Diff line change
Expand Up @@ -215,6 +215,21 @@ realize_degree_sequence_impl <- function(out.deg, in.deg=NULL, allowed.edge.type
res
}

realize_bipartite_degree_sequence_impl <- function(degrees1, degrees2, allowed.edge.types=c("simple", "loops", "multi", "all"), method=c("smallest", "largest", "index")) {
# Argument checks
degrees1 <- as.numeric(degrees1)
degrees2 <- as.numeric(degrees2)
allowed.edge.types <- switch(igraph.match.arg(allowed.edge.types),
"simple"=0L, "loop"=1L, "loops"=1L, "multi"=6L, "multiple"=6L, "all"=7L)
method <- switch(igraph.match.arg(method), "smallest"=0L, "largest"=1L, "index"=2L)

on.exit( .Call(R_igraph_finalizer) )
# Function call
res <- .Call(R_igraph_realize_bipartite_degree_sequence, degrees1, degrees2, allowed.edge.types, method)

res
}

circulant_impl <- function(n, shifts, directed=FALSE) {
# Argument checks
n <- as.numeric(n)
Expand Down Expand Up @@ -2257,6 +2272,17 @@ bridges_impl <- function(graph) {
res
}

is_biconnected_impl <- function(graph) {
# Argument checks
ensure_igraph(graph)

on.exit( .Call(R_igraph_finalizer) )
# Function call
res <- .Call(R_igraph_is_biconnected, graph)

res
}

cliques_impl <- function(graph, min=0, max=0) {
# Argument checks
ensure_igraph(graph)
Expand Down
26 changes: 26 additions & 0 deletions R/components.R
Original file line number Diff line number Diff line change
Expand Up @@ -274,6 +274,32 @@ bridges <- bridges_impl
biconnected_components <- biconnected_components_impl


#' Check biconnectedness
#'
#' Tests whether a graph is biconnected.
#'
#' A graph is biconnected if the removal of any single vertex (and its adjacent
#' edges) does not disconnect it.
#'
#' igraph does not consider single-vertex graphs biconnected.
#'
#' Note that some authors do not consider the graph consisting of
#' two connected vertices as biconnected, however, igraph does.
#'
#' @param graph The input graph. Edge directions are ignored.
#' @return Logical, `TRUE` if the graph is biconnected.
#' @seealso [articulation_points()], [biconnected_components()],
#' [is_connected()], [vertex_connectivity()]
#' @keywords graphs
#' @examples
#'
#' is_biconnected(make_graph("bull"))
#' is_biconnected(make_graph("dodecahedron"))
#' @family components
#' @export
is_biconnected <- is_biconnected_impl


#' @rdname components
#' @export
largest_component <- function(graph, mode = c("weak", "strong")) {
Expand Down
6 changes: 4 additions & 2 deletions man/articulation_points.Rd

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

3 changes: 2 additions & 1 deletion man/biconnected_components.Rd

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

3 changes: 2 additions & 1 deletion man/components.Rd

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

3 changes: 2 additions & 1 deletion man/decompose.Rd

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

43 changes: 43 additions & 0 deletions man/is_biconnected.Rd

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

62 changes: 62 additions & 0 deletions src/rinterface.c
Original file line number Diff line number Diff line change
Expand Up @@ -788,6 +788,44 @@ SEXP R_igraph_realize_degree_sequence(SEXP out_deg, SEXP in_deg, SEXP allowed_ed
return(r_result);
}

/*-------------------------------------------/
/ igraph_realize_bipartite_degree_sequence /
/-------------------------------------------*/
SEXP R_igraph_realize_bipartite_degree_sequence(SEXP degrees1, SEXP degrees2, SEXP allowed_edge_types, SEXP method) {
/* Declarations */
igraph_t c_graph;
igraph_vector_int_t c_degrees1;
igraph_vector_int_t c_degrees2;
igraph_edge_type_sw_t c_allowed_edge_types;
igraph_realize_degseq_t c_method;
SEXP graph;

SEXP r_result;
/* Convert input */
R_SEXP_to_vector_int_copy(degrees1, &c_degrees1);
IGRAPH_FINALLY(igraph_vector_int_destroy, &c_degrees1);
R_SEXP_to_vector_int_copy(degrees2, &c_degrees2);
IGRAPH_FINALLY(igraph_vector_int_destroy, &c_degrees2);
c_allowed_edge_types = (igraph_edge_type_sw_t) Rf_asInteger(allowed_edge_types);
c_method = (igraph_realize_degseq_t) Rf_asInteger(method);
/* Call igraph */
IGRAPH_R_CHECK(igraph_realize_bipartite_degree_sequence(&c_graph, &c_degrees1, &c_degrees2, c_allowed_edge_types, c_method));

/* Convert output */
IGRAPH_FINALLY(igraph_destroy, &c_graph);
PROTECT(graph=R_igraph_to_SEXP(&c_graph));
IGRAPH_I_DESTROY(&c_graph);
IGRAPH_FINALLY_CLEAN(1);
igraph_vector_int_destroy(&c_degrees1);
IGRAPH_FINALLY_CLEAN(1);
igraph_vector_int_destroy(&c_degrees2);
IGRAPH_FINALLY_CLEAN(1);
r_result = graph;

UNPROTECT(1);
return(r_result);
}

/*-------------------------------------------/
/ igraph_circulant /
/-------------------------------------------*/
Expand Down Expand Up @@ -6222,6 +6260,30 @@ SEXP R_igraph_bridges(SEXP graph) {
return(r_result);
}

/*-------------------------------------------/
/ igraph_is_biconnected /
/-------------------------------------------*/
SEXP R_igraph_is_biconnected(SEXP graph) {
/* Declarations */
igraph_t c_graph;
igraph_bool_t c_res;
SEXP res;

SEXP r_result;
/* Convert input */
R_SEXP_to_igraph(graph, &c_graph);
/* Call igraph */
IGRAPH_R_CHECK(igraph_is_biconnected(&c_graph, &c_res));

/* Convert output */
PROTECT(res=NEW_LOGICAL(1));
LOGICAL(res)[0]=c_res;
r_result = res;

UNPROTECT(1);
return(r_result);
}

/*-------------------------------------------/
/ igraph_cliques /
/-------------------------------------------*/
Expand Down

0 comments on commit 5f6af72

Please sign in to comment.