Skip to content

Commit

Permalink
chore: Update vendored sources to igraph/igraph@a6441e7
Browse files Browse the repository at this point in the history
chore: trim trailing whitespace in interface file
interface: add missing interface for igraph_get_isomorphisms_vf2_callback()
interface: mark all callback extra parameters and some callback functions as optional
interface: add default parameter values for fundamental_cycles() and minimum_cycle_basis()
interface: even more missing OPTIONAL markers
interface: add more missing OPTIONAL markers
fix: some weights parameters were incorrectly marked as OPTIONAL in functions.yaml
fix: mark some optional weight parameters as OPTIONAL in functions.yaml
fix: type -> types in is_bipartite interface
fix: some BIPARTITE_TYPES parameters were incorrectly marked as optional
refactor: use OPTIONAL instead of =NULL in interfaces
feat: functionality for listing all simple cycles
interface: default OUT mode for igraph_find_cycle()
refactor: better error reporting for igraph_find_cycle()
chore: some copyright header cleanup in public headers
refactor: minor readability improvements
fix: add some missing IGRAPH_CHECKs
  • Loading branch information
szhorvat authored and krlmlr committed Nov 7, 2024
1 parent 4fb3aa5 commit a8469f6
Show file tree
Hide file tree
Showing 20 changed files with 1,018 additions and 57 deletions.
90 changes: 87 additions & 3 deletions R/aaa-auto.R
Original file line number Diff line number Diff line change
Expand Up @@ -3098,6 +3098,58 @@ isomorphic_vf2_impl <- function(graph1, graph2, vertex.color1=NULL, vertex.color
res
}

get_isomorphisms_vf2_callback_impl <- function(graph1, graph2, vertex.color1=NULL, vertex.color2=NULL, edge.color1=NULL, edge.color2=NULL, ishohandler.fn) {
# Argument checks
ensure_igraph(graph1)
ensure_igraph(graph2)
if (missing(vertex.color1)) {
if ("color" %in% vertex_attr_names(graph1)) {
vertex.color1 <- V(graph1)$color
} else {
vertex.color1 <- NULL
}
}
if (!is.null(vertex.color1)) {
vertex.color1 <- as.numeric(vertex.color1)-1
}
if (missing(vertex.color2)) {
if ("color" %in% vertex_attr_names(graph2)) {
vertex.color2 <- V(graph2)$color
} else {
vertex.color2 <- NULL
}
}
if (!is.null(vertex.color2)) {
vertex.color2 <- as.numeric(vertex.color2)-1
}
if (missing(edge.color1)) {
if ("color" %in% edge_attr_names(graph1)) {
edge.color1 <- E(graph1)$color
} else {
edge.color1 <- NULL
}
}
if (!is.null(edge.color1)) {
edge.color1 <- as.numeric(edge.color1)-1
}
if (missing(edge.color2)) {
if ("color" %in% edge_attr_names(graph2)) {
edge.color2 <- E(graph2)$color
} else {
edge.color2 <- NULL
}
}
if (!is.null(edge.color2)) {
edge.color2 <- as.numeric(edge.color2)-1
}

on.exit( .Call(R_igraph_finalizer) )
# Function call
res <- .Call(R_igraph_get_isomorphisms_vf2_callback, graph1, graph2, vertex.color1, vertex.color2, edge.color1, edge.color2, ishohandler.fn)

res
}

count_isomorphisms_vf2_impl <- function(graph1, graph2, vertex.color1=NULL, vertex.color2=NULL, edge.color1=NULL, edge.color2=NULL) {
# Argument checks
ensure_igraph(graph1)
Expand Down Expand Up @@ -3511,7 +3563,7 @@ solve_lsap_impl <- function(c, n) {
res
}

find_cycle_impl <- function(graph, mode) {
find_cycle_impl <- function(graph, mode=c("out", "in", "all", "total")) {
# Argument checks
ensure_igraph(graph)
mode <- switch(igraph.match.arg(mode), "out"=1L, "in"=2L, "all"=3L, "total"=3L)
Expand All @@ -3528,6 +3580,38 @@ find_cycle_impl <- function(graph, mode) {
res
}

simple_cycles_impl <- function(graph, mode=c("out", "in", "all", "total"), max.cycle.length=-1) {
# Argument checks
ensure_igraph(graph)
mode <- switch(igraph.match.arg(mode), "out"=1L, "in"=2L, "all"=3L, "total"=3L)
max.cycle.length <- as.numeric(max.cycle.length)

on.exit( .Call(R_igraph_finalizer) )
# Function call
res <- .Call(R_igraph_simple_cycles, graph, mode, max.cycle.length)
if (igraph_opt("return.vs.es")) {
res$vertices <- lapply(res$vertices, unsafe_create_vs, graph = graph, verts = V(graph))
}
if (igraph_opt("return.vs.es")) {
res$edges <- lapply(res$edges, unsafe_create_es, graph = graph, es = E(graph))
}
res
}

simple_cycles_callback_impl <- function(graph, mode=c("out", "in", "all", "total"), max.cycle.length=-1, cycle.handler) {
# Argument checks
ensure_igraph(graph)
mode <- switch(igraph.match.arg(mode), "out"=1L, "in"=2L, "all"=3L, "total"=3L)
max.cycle.length <- as.numeric(max.cycle.length)

on.exit( .Call(R_igraph_finalizer) )
# Function call
res <- .Call(R_igraph_simple_cycles_callback, graph, mode, max.cycle.length, cycle.handler)


res
}

is_eulerian_impl <- function(graph) {
# Argument checks
ensure_igraph(graph)
Expand Down Expand Up @@ -3571,7 +3655,7 @@ eulerian_cycle_impl <- function(graph) {
res
}

fundamental_cycles_impl <- function(graph, start=NULL, bfs.cutoff, weights=NULL) {
fundamental_cycles_impl <- function(graph, start=NULL, bfs.cutoff=-1, weights=NULL) {
# Argument checks
ensure_igraph(graph)
if (!is.null(start)) start <- as_igraph_vs(graph, start)
Expand All @@ -3597,7 +3681,7 @@ fundamental_cycles_impl <- function(graph, start=NULL, bfs.cutoff, weights=NULL)
res
}

minimum_cycle_basis_impl <- function(graph, bfs.cutoff, complete, use.cycle.order, weights=NULL) {
minimum_cycle_basis_impl <- function(graph, bfs.cutoff=-1, complete=TRUE, use.cycle.order=TRUE, weights=NULL) {
# Argument checks
ensure_igraph(graph)
bfs.cutoff <- as.numeric(bfs.cutoff)
Expand Down
6 changes: 6 additions & 0 deletions src/cpp11.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -190,6 +190,7 @@ extern SEXP R_igraph_get_edgelist(SEXP, SEXP);
extern SEXP R_igraph_get_eids(SEXP, SEXP, SEXP, SEXP);
extern SEXP R_igraph_get_graph_id(SEXP);
extern SEXP R_igraph_get_isomorphisms_vf2(SEXP, SEXP, SEXP, SEXP, SEXP, SEXP);
extern SEXP R_igraph_get_isomorphisms_vf2_callback(SEXP, SEXP, SEXP, SEXP, SEXP, SEXP, SEXP);
extern SEXP R_igraph_get_k_shortest_paths(SEXP, SEXP, SEXP, SEXP, SEXP, SEXP);
extern SEXP R_igraph_get_laplacian(SEXP, SEXP, SEXP, SEXP);
extern SEXP R_igraph_get_laplacian_sparse(SEXP, SEXP, SEXP, SEXP);
Expand Down Expand Up @@ -400,6 +401,8 @@ extern SEXP R_igraph_similarity_inverse_log_weighted(SEXP, SEXP, SEXP);
extern SEXP R_igraph_similarity_jaccard(SEXP, SEXP, SEXP, SEXP);
extern SEXP R_igraph_similarity_jaccard_es(SEXP, SEXP, SEXP, SEXP);
extern SEXP R_igraph_similarity_jaccard_pairs(SEXP, SEXP, SEXP, SEXP);
extern SEXP R_igraph_simple_cycles(SEXP, SEXP, SEXP);
extern SEXP R_igraph_simple_cycles_callback(SEXP, SEXP, SEXP, SEXP);
extern SEXP R_igraph_simple_interconnected_islands_game(SEXP, SEXP, SEXP, SEXP);
extern SEXP R_igraph_simplify(SEXP, SEXP, SEXP, SEXP);
extern SEXP R_igraph_simplify_and_colorize(SEXP);
Expand Down Expand Up @@ -643,6 +646,7 @@ static const R_CallMethodDef CallEntries[] = {
{"R_igraph_get_eids", (DL_FUNC) &R_igraph_get_eids, 4},
{"R_igraph_get_graph_id", (DL_FUNC) &R_igraph_get_graph_id, 1},
{"R_igraph_get_isomorphisms_vf2", (DL_FUNC) &R_igraph_get_isomorphisms_vf2, 6},
{"R_igraph_get_isomorphisms_vf2_callback", (DL_FUNC) &R_igraph_get_isomorphisms_vf2_callback, 7},
{"R_igraph_get_k_shortest_paths", (DL_FUNC) &R_igraph_get_k_shortest_paths, 6},
{"R_igraph_get_laplacian", (DL_FUNC) &R_igraph_get_laplacian, 4},
{"R_igraph_get_laplacian_sparse", (DL_FUNC) &R_igraph_get_laplacian_sparse, 4},
Expand Down Expand Up @@ -853,6 +857,8 @@ static const R_CallMethodDef CallEntries[] = {
{"R_igraph_similarity_jaccard", (DL_FUNC) &R_igraph_similarity_jaccard, 4},
{"R_igraph_similarity_jaccard_es", (DL_FUNC) &R_igraph_similarity_jaccard_es, 4},
{"R_igraph_similarity_jaccard_pairs", (DL_FUNC) &R_igraph_similarity_jaccard_pairs, 4},
{"R_igraph_simple_cycles", (DL_FUNC) &R_igraph_simple_cycles, 3},
{"R_igraph_simple_cycles_callback", (DL_FUNC) &R_igraph_simple_cycles_callback, 4},
{"R_igraph_simple_interconnected_islands_game", (DL_FUNC) &R_igraph_simple_interconnected_islands_game, 4},
{"R_igraph_simplify", (DL_FUNC) &R_igraph_simplify, 4},
{"R_igraph_simplify_and_colorize", (DL_FUNC) &R_igraph_simplify_and_colorize, 1},
Expand Down
157 changes: 157 additions & 0 deletions src/rinterface.c
Original file line number Diff line number Diff line change
Expand Up @@ -9782,6 +9782,89 @@ SEXP R_igraph_isomorphic_vf2(SEXP graph1, SEXP graph2, SEXP vertex_color1, SEXP
return(r_result);
}

/*-------------------------------------------/
/ igraph_get_isomorphisms_vf2_callback /
/-------------------------------------------*/
SEXP R_igraph_get_isomorphisms_vf2_callback(SEXP graph1, SEXP graph2, SEXP vertex_color1, SEXP vertex_color2, SEXP edge_color1, SEXP edge_color2) {
/* Declarations */
igraph_t c_graph1;
igraph_t c_graph2;
igraph_vector_int_t c_vertex_color1;
igraph_vector_int_t c_vertex_color2;
igraph_vector_int_t c_edge_color1;
igraph_vector_int_t c_edge_color2;
igraph_vector_int_t c_map12;
igraph_vector_int_t c_map21;




SEXP map12;
SEXP map21;

SEXP r_result, r_names;
/* Convert input */
R_SEXP_to_igraph(graph1, &c_graph1);
R_SEXP_to_igraph(graph2, &c_graph2);
if (!Rf_isNull(vertex_color1)) {
IGRAPH_R_CHECK(R_SEXP_to_vector_int_copy(vertex_color1, &c_vertex_color1));
} else {
IGRAPH_R_CHECK(igraph_vector_int_init(&c_vertex_color1, 0));
}
IGRAPH_FINALLY(igraph_vector_int_destroy, &c_vertex_color1);
if (!Rf_isNull(vertex_color2)) {
IGRAPH_R_CHECK(R_SEXP_to_vector_int_copy(vertex_color2, &c_vertex_color2));
} else {
IGRAPH_R_CHECK(igraph_vector_int_init(&c_vertex_color2, 0));
}
IGRAPH_FINALLY(igraph_vector_int_destroy, &c_vertex_color2);
if (!Rf_isNull(edge_color1)) {
IGRAPH_R_CHECK(R_SEXP_to_vector_int_copy(edge_color1, &c_edge_color1));
} else {
IGRAPH_R_CHECK(igraph_vector_int_init(&c_edge_color1, 0));
}
IGRAPH_FINALLY(igraph_vector_int_destroy, &c_edge_color1);
if (!Rf_isNull(edge_color2)) {
IGRAPH_R_CHECK(R_SEXP_to_vector_int_copy(edge_color2, &c_edge_color2));
} else {
IGRAPH_R_CHECK(igraph_vector_int_init(&c_edge_color2, 0));
}
IGRAPH_FINALLY(igraph_vector_int_destroy, &c_edge_color2);
IGRAPH_R_CHECK(igraph_vector_int_init(&c_map12, 0));
IGRAPH_FINALLY(igraph_vector_int_destroy, &c_map12);
IGRAPH_R_CHECK(igraph_vector_int_init(&c_map21, 0));
IGRAPH_FINALLY(igraph_vector_int_destroy, &c_map21);
/* Call igraph */
IGRAPH_R_CHECK(igraph_get_isomorphisms_vf2_callback(&c_graph1, &c_graph2, (Rf_isNull(vertex_color1) ? 0 : &c_vertex_color1), (Rf_isNull(vertex_color2) ? 0 : &c_vertex_color2), (Rf_isNull(edge_color1) ? 0 : &c_edge_color1), (Rf_isNull(edge_color2) ? 0 : &c_edge_color2), &c_map12, &c_map21, 0, 0, 0, 0));

/* Convert output */
PROTECT(r_result=NEW_LIST(2));
PROTECT(r_names=NEW_CHARACTER(2));
igraph_vector_int_destroy(&c_vertex_color1);
IGRAPH_FINALLY_CLEAN(1);
igraph_vector_int_destroy(&c_vertex_color2);
IGRAPH_FINALLY_CLEAN(1);
igraph_vector_int_destroy(&c_edge_color1);
IGRAPH_FINALLY_CLEAN(1);
igraph_vector_int_destroy(&c_edge_color2);
IGRAPH_FINALLY_CLEAN(1);
PROTECT(map12=R_igraph_vector_int_to_SEXPp1(&c_map12));
igraph_vector_int_destroy(&c_map12);
IGRAPH_FINALLY_CLEAN(1);
PROTECT(map21=R_igraph_vector_int_to_SEXPp1(&c_map21));
igraph_vector_int_destroy(&c_map21);
IGRAPH_FINALLY_CLEAN(1);
SET_VECTOR_ELT(r_result, 0, map12);
SET_VECTOR_ELT(r_result, 1, map21);
SET_STRING_ELT(r_names, 0, Rf_mkChar("map12"));
SET_STRING_ELT(r_names, 1, Rf_mkChar("map21"));
SET_NAMES(r_result, r_names);
UNPROTECT(3);

UNPROTECT(1);
return(r_result);
}

/*-------------------------------------------/
/ igraph_count_isomorphisms_vf2 /
/-------------------------------------------*/
Expand Down Expand Up @@ -10882,6 +10965,80 @@ SEXP R_igraph_find_cycle(SEXP graph, SEXP mode) {
return(r_result);
}

/*-------------------------------------------/
/ igraph_simple_cycles /
/-------------------------------------------*/
SEXP R_igraph_simple_cycles(SEXP graph, SEXP mode, SEXP max_cycle_length) {
/* Declarations */
igraph_t c_graph;
igraph_vector_int_list_t c_vertices;
igraph_vector_int_list_t c_edges;
igraph_neimode_t c_mode;
igraph_integer_t c_max_cycle_length;
SEXP vertices;
SEXP edges;

SEXP r_result, r_names;
/* Convert input */
R_SEXP_to_igraph(graph, &c_graph);
IGRAPH_R_CHECK(igraph_vector_int_list_init(&c_vertices, 0));
IGRAPH_FINALLY(igraph_vector_int_list_destroy, &c_vertices);
IGRAPH_R_CHECK(igraph_vector_int_list_init(&c_edges, 0));
IGRAPH_FINALLY(igraph_vector_int_list_destroy, &c_edges);
c_mode = (igraph_neimode_t) Rf_asInteger(mode);
IGRAPH_R_CHECK_INT(max_cycle_length);
c_max_cycle_length = (igraph_integer_t) REAL(max_cycle_length)[0];
/* Call igraph */
IGRAPH_R_CHECK(igraph_simple_cycles(&c_graph, &c_vertices, &c_edges, c_mode, c_max_cycle_length));

/* Convert output */
PROTECT(r_result=NEW_LIST(2));
PROTECT(r_names=NEW_CHARACTER(2));
PROTECT(vertices=R_igraph_vector_int_list_to_SEXPp1(&c_vertices));
igraph_vector_int_list_destroy(&c_vertices);
IGRAPH_FINALLY_CLEAN(1);
PROTECT(edges=R_igraph_vector_int_list_to_SEXPp1(&c_edges));
igraph_vector_int_list_destroy(&c_edges);
IGRAPH_FINALLY_CLEAN(1);
SET_VECTOR_ELT(r_result, 0, vertices);
SET_VECTOR_ELT(r_result, 1, edges);
SET_STRING_ELT(r_names, 0, Rf_mkChar("vertices"));
SET_STRING_ELT(r_names, 1, Rf_mkChar("edges"));
SET_NAMES(r_result, r_names);
UNPROTECT(3);

UNPROTECT(1);
return(r_result);
}

/*-------------------------------------------/
/ igraph_simple_cycles_callback /
/-------------------------------------------*/
SEXP R_igraph_simple_cycles_callback(SEXP graph, SEXP mode, SEXP max_cycle_length, SEXP cycle_handler) {
/* Declarations */
igraph_t c_graph;
igraph_neimode_t c_mode;
igraph_integer_t c_max_cycle_length;
igraph_cycle_handler_t c_cycle_handler;

igraph_error_t c_result;
SEXP r_result;
/* Convert input */
R_SEXP_to_igraph(graph, &c_graph);
c_mode = (igraph_neimode_t) Rf_asInteger(mode);
IGRAPH_R_CHECK_INT(max_cycle_length);
c_max_cycle_length = (igraph_integer_t) REAL(max_cycle_length)[0];
/* Call igraph */
IGRAPH_R_CHECK(igraph_simple_cycles_callback(&c_graph, c_mode, c_max_cycle_length, c_cycle_handler, 0));

/* Convert output */



UNPROTECT(1);
return(r_result);
}

/*-------------------------------------------/
/ igraph_is_eulerian /
/-------------------------------------------*/
Expand Down
Loading

0 comments on commit a8469f6

Please sign in to comment.