Skip to content

Commit

Permalink
refactor: eliminate manual edits from autogenerated files (#1207)
Browse files Browse the repository at this point in the history
  • Loading branch information
aviator-app[bot] authored Feb 6, 2024
2 parents 9cc9560 + 32ef7b3 commit 5a5acb7
Show file tree
Hide file tree
Showing 4 changed files with 126 additions and 166 deletions.
35 changes: 28 additions & 7 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 @@ -970,9 +985,7 @@ edge_betweenness_subset_impl <- function(graph, eids=E(graph), directed=TRUE, so
on.exit( .Call(R_igraph_finalizer) )
# Function call
res <- .Call(R_igraph_edge_betweenness_subset, graph, eids-1, directed, sources-1, targets-1, weights)
if (igraph_opt("add.vertex.names") && is_named(graph)) {
names(res) <- vertex_attr(graph, "name", V(graph))
}

res
}

Expand Down Expand Up @@ -2257,6 +2270,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 Expand Up @@ -3229,9 +3253,6 @@ subisomorphic_vf2_impl <- function(graph1, graph2, vertex.color1=NULL, vertex.co
res
}

# get_subisomorphisms_vf2_callback_impl gives LTO warnings
# wrong number of arguments to R_igraph_get_subisomorphisms_vf2_callback()

count_subisomorphisms_vf2_impl <- function(graph1, graph2, vertex.color1, vertex.color2, edge.color1, edge.color2) {
# Argument checks
ensure_igraph(graph1)
Expand Down Expand Up @@ -3816,7 +3837,6 @@ stochastic_imitation_impl <- function(graph, vid, algo, quantities, strategies,
res
}


vertex_path_from_edge_path_impl <- function(graph, start, edge.path, mode=c("out", "in", "all", "total")) {
# Argument checks
ensure_igraph(graph)
Expand All @@ -3835,3 +3855,4 @@ vertex_path_from_edge_path_impl <- function(graph, start, edge.path, mode=c("out
}
res
}

4 changes: 4 additions & 0 deletions src/cpp11.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -247,6 +247,7 @@ extern SEXP R_igraph_induced_subgraph(void *, void *, void *);
extern SEXP R_igraph_induced_subgraph_map(void *, void *, void *);
extern SEXP R_igraph_intersection(void *, void *);
extern SEXP R_igraph_is_acyclic(void *);
extern SEXP R_igraph_is_biconnected(void *);
extern SEXP R_igraph_is_bipartite(void *);
extern SEXP R_igraph_is_chordal(void *, void *, void *, void *, void *);
extern SEXP R_igraph_is_connected(void *, void *);
Expand Down Expand Up @@ -375,6 +376,7 @@ extern SEXP R_igraph_read_graph_graphml(void *, void *);
extern SEXP R_igraph_read_graph_lgl(void *, void *, void *, void *);
extern SEXP R_igraph_read_graph_ncol(void *, void *, void *, void *, void *);
extern SEXP R_igraph_read_graph_pajek(void *);
extern SEXP R_igraph_realize_bipartite_degree_sequence(void *, void *, void *, void *);
extern SEXP R_igraph_realize_degree_sequence(void *, void *, void *, void *);
extern SEXP R_igraph_recent_degree_aging_game(void *, void *, void *, void *, void *, void *, void *, void *, void *, void *);
extern SEXP R_igraph_reciprocity(void *, void *, void *);
Expand Down Expand Up @@ -705,6 +707,7 @@ static const R_CallMethodDef CallEntries[] = {
{"R_igraph_induced_subgraph_map", (DL_FUNC) &R_igraph_induced_subgraph_map, 3},
{"R_igraph_intersection", (DL_FUNC) &R_igraph_intersection, 2},
{"R_igraph_is_acyclic", (DL_FUNC) &R_igraph_is_acyclic, 1},
{"R_igraph_is_biconnected", (DL_FUNC) &R_igraph_is_biconnected, 1},
{"R_igraph_is_bipartite", (DL_FUNC) &R_igraph_is_bipartite, 1},
{"R_igraph_is_chordal", (DL_FUNC) &R_igraph_is_chordal, 5},
{"R_igraph_is_connected", (DL_FUNC) &R_igraph_is_connected, 2},
Expand Down Expand Up @@ -833,6 +836,7 @@ static const R_CallMethodDef CallEntries[] = {
{"R_igraph_read_graph_lgl", (DL_FUNC) &R_igraph_read_graph_lgl, 4},
{"R_igraph_read_graph_ncol", (DL_FUNC) &R_igraph_read_graph_ncol, 5},
{"R_igraph_read_graph_pajek", (DL_FUNC) &R_igraph_read_graph_pajek, 1},
{"R_igraph_realize_bipartite_degree_sequence", (DL_FUNC) &R_igraph_realize_bipartite_degree_sequence, 4},
{"R_igraph_realize_degree_sequence", (DL_FUNC) &R_igraph_realize_degree_sequence, 4},
{"R_igraph_recent_degree_aging_game", (DL_FUNC) &R_igraph_recent_degree_aging_game, 10},
{"R_igraph_reciprocity", (DL_FUNC) &R_igraph_reciprocity, 3},
Expand Down
218 changes: 62 additions & 156 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 Expand Up @@ -9853,93 +9915,6 @@ SEXP R_igraph_subisomorphic_vf2(SEXP graph1, SEXP graph2, SEXP vertex_color1, SE
return(r_result);
}

/*-------------------------------------------/
/ igraph_get_subisomorphisms_vf2_callback /
/-------------------------------------------*/
SEXP R_igraph_get_subisomorphisms_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)) {
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)) {
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)) {
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)) {
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);
if (0 != igraph_vector_int_init(&c_map12, 0)) {
igraph_error("", __FILE__, __LINE__, IGRAPH_ENOMEM);
}
IGRAPH_FINALLY(igraph_vector_int_destroy, &c_map12);
if (0 != igraph_vector_int_init(&c_map21, 0)) {
igraph_error("", __FILE__, __LINE__, IGRAPH_ENOMEM);
}
IGRAPH_FINALLY(igraph_vector_int_destroy, &c_map21);
/* Call igraph */
IGRAPH_R_CHECK(igraph_get_subisomorphisms_vf2_callback(&c_graph1, &c_graph2, (Rf_isNull(vertex_color1) ? 0 : (Rf_isNull(vertex_color1) ? 0 : &c_vertex_color1)), (Rf_isNull(vertex_color2) ? 0 : (Rf_isNull(vertex_color2) ? 0 : &c_vertex_color2)), (Rf_isNull(edge_color1) ? 0 : (Rf_isNull(edge_color1) ? 0 : &c_edge_color1)), (Rf_isNull(edge_color2) ? 0 : (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_subisomorphisms_vf2 /
/-------------------------------------------*/
Expand Down Expand Up @@ -10743,7 +10718,6 @@ SEXP R_igraph_dim_select(SEXP sv) {
return(r_result);
}


/*-------------------------------------------/
/ igraph_solve_lsap /
/-------------------------------------------*/
Expand Down Expand Up @@ -11392,28 +11366,6 @@ SEXP R_igraph_stochastic_imitation(SEXP graph, SEXP vid, SEXP algo, SEXP quantit
return(r_result);
}

/*-------------------------------------------/
/ igraph_has_attribute_table /
/-------------------------------------------*/
// FIXME: Change Stimulus to generate (void) instead of ()
SEXP R_igraph_has_attribute_table(void) {
/* Declarations */
igraph_bool_t c_result;
SEXP r_result;
/* Convert input */

/* Call igraph */
c_result=igraph_has_attribute_table();

/* Convert output */

PROTECT(r_result=NEW_LOGICAL(1));
LOGICAL(r_result)[0]=c_result;

UNPROTECT(1);
return(r_result);
}

/*-------------------------------------------/
/ igraph_expand_path_to_pairs /
/-------------------------------------------*/
Expand Down Expand Up @@ -11499,49 +11451,3 @@ SEXP R_igraph_vertex_path_from_edge_path(SEXP graph, SEXP start, SEXP edge_path,
UNPROTECT(1);
return(r_result);
}

/*-------------------------------------------/
/ igraph_version /
/-------------------------------------------*/
// FIXME: Change Stimulus to generate (void) instead of ()
SEXP R_igraph_version(void) {
/* Declarations */
const char* c_version_string;
int c_major;
int c_minor;
int c_subminor;
SEXP version_string;
SEXP major;
SEXP minor;
SEXP subminor;

SEXP r_result, r_names;
/* Convert input */

/* Call igraph */
igraph_version(&c_version_string, &c_major, &c_minor, &c_subminor);

/* Convert output */
PROTECT(r_result=NEW_LIST(4));
PROTECT(r_names=NEW_CHARACTER(4));
PROTECT(version_string = Rf_mkCharLenCE(c_version_string, strlen(c_version_string), CE_UTF8));
PROTECT(major=NEW_INTEGER(1));
INTEGER(major)[0]=(int) c_major;
PROTECT(minor=NEW_INTEGER(1));
INTEGER(minor)[0]=(int) c_minor;
PROTECT(subminor=NEW_INTEGER(1));
INTEGER(subminor)[0]=(int) c_subminor;
SET_VECTOR_ELT(r_result, 0, version_string);
SET_VECTOR_ELT(r_result, 1, major);
SET_VECTOR_ELT(r_result, 2, minor);
SET_VECTOR_ELT(r_result, 3, subminor);
SET_STRING_ELT(r_names, 0, Rf_mkChar("version_string"));
SET_STRING_ELT(r_names, 1, Rf_mkChar("major"));
SET_STRING_ELT(r_names, 2, Rf_mkChar("minor"));
SET_STRING_ELT(r_names, 3, Rf_mkChar("subminor"));
SET_NAMES(r_result, r_names);
UNPROTECT(5);

UNPROTECT(1);
return(r_result);
}
Loading

0 comments on commit 5a5acb7

Please sign in to comment.