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
11 changes: 7 additions & 4 deletions R/aaa-auto.R
Original file line number Diff line number Diff line change
Expand Up @@ -9730,6 +9730,7 @@ fundamental_cycles_impl <- function(
call = rlang::caller_env()
)
}
start <- start - 1
}
bfs_cutoff <- as.numeric(bfs_cutoff)
if (is.null(weights) && "weight" %in% edge_attr_names(graph)) {
Expand All @@ -9746,7 +9747,7 @@ fundamental_cycles_impl <- function(
res <- .Call(
R_igraph_fundamental_cycles,
graph,
start - 1,
start,
bfs_cutoff,
weights
)
Expand Down Expand Up @@ -9971,7 +9972,7 @@ minimum_spanning_tree_prim_impl <- function(

random_spanning_tree_impl <- function(
graph,
vid = 0
vid = NULL
) {
# Argument checks
ensure_igraph(graph)
Expand All @@ -9983,14 +9984,15 @@ random_spanning_tree_impl <- function(
call = rlang::caller_env()
)
}
vid <- vid - 1
}

on.exit(.Call(R_igraph_finalizer))
# Function call
res <- .Call(
R_igraph_random_spanning_tree,
graph,
vid - 1
vid
)
if (igraph_opt("return.vs.es")) {
res <- create_es(graph, res)
Expand Down Expand Up @@ -10316,6 +10318,7 @@ vertex_path_from_edge_path_impl <- function(
call = rlang::caller_env()
)
}
start <- start - 1
}
edge_path <- as_igraph_es(graph, edge_path)
mode <- switch_igraph_arg(
Expand All @@ -10331,7 +10334,7 @@ vertex_path_from_edge_path_impl <- function(
res <- .Call(
R_igraph_vertex_path_from_edge_path,
graph,
start - 1,
start,
edge_path - 1,
mode
)
Expand Down
4 changes: 2 additions & 2 deletions R/trees.R
Original file line number Diff line number Diff line change
Expand Up @@ -152,7 +152,7 @@ to_prufer <- function(graph) {
#' @param graph The input graph to sample from. Edge directions are ignored if
#' the graph is directed.
#' @param vid When the graph is disconnected, this argument specifies how to
#' handle the situation. When the argument is zero (the default), the sampling
#' handle the situation. When the argument is `NULL` (the default), the sampling
#' will be performed component-wise, and the result will be a spanning forest.
#' When the argument contains a vertex ID, only the component containing the
#' given vertex will be processed, and the result will be a spanning tree of the
Expand All @@ -171,7 +171,7 @@ to_prufer <- function(graph) {
#' @family trees
#' @export
#' @cdocs igraph_random_spanning_tree
sample_spanning_tree <- function(graph, vid = 0) {
sample_spanning_tree <- function(graph, vid = NULL) {
random_spanning_tree_impl(
graph = graph,
vid = vid
Expand Down
4 changes: 2 additions & 2 deletions man/sample_spanning_tree.Rd

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

6 changes: 3 additions & 3 deletions src/rinterface.c
Original file line number Diff line number Diff line change
Expand Up @@ -13168,7 +13168,7 @@ SEXP R_igraph_fundamental_cycles(SEXP graph, SEXP start, SEXP bfs_cutoff, SEXP w
Rz_SEXP_to_vector(weights, &c_weights);
}
/* Call igraph */
IGRAPH_R_CHECK(igraph_fundamental_cycles(&c_graph, &c_basis, (Rf_isNull(start) ? 0 : c_start), c_bfs_cutoff, (Rf_isNull(weights) ? 0 : &c_weights)));
IGRAPH_R_CHECK(igraph_fundamental_cycles(&c_graph, &c_basis, (Rf_isNull(start) ? -1 : c_start), c_bfs_cutoff, (Rf_isNull(weights) ? 0 : &c_weights)));

/* Convert output */
PROTECT(basis=Ry_igraph_vector_int_list_to_SEXPp1(&c_basis));
Expand Down Expand Up @@ -13482,7 +13482,7 @@ SEXP R_igraph_random_spanning_tree(SEXP graph, SEXP vid) {
c_vid = (igraph_integer_t) REAL(vid)[0];
}
/* Call igraph */
IGRAPH_R_CHECK(igraph_random_spanning_tree(&c_graph, &c_res, (Rf_isNull(vid) ? 0 : c_vid)));
IGRAPH_R_CHECK(igraph_random_spanning_tree(&c_graph, &c_res, (Rf_isNull(vid) ? -1 : c_vid)));

/* Convert output */
PROTECT(res=Ry_igraph_vector_int_to_SEXPp1(&c_res));
Expand Down Expand Up @@ -13869,7 +13869,7 @@ SEXP R_igraph_vertex_path_from_edge_path(SEXP graph, SEXP start, SEXP edge_path,
IGRAPH_FINALLY(igraph_vector_int_destroy, &c_vertex_path);
c_mode = (igraph_neimode_t) Rf_asInteger(mode);
/* Call igraph */
IGRAPH_R_CHECK(igraph_vertex_path_from_edge_path(&c_graph, (Rf_isNull(start) ? 0 : c_start), &c_edge_path, &c_vertex_path, c_mode));
IGRAPH_R_CHECK(igraph_vertex_path_from_edge_path(&c_graph, (Rf_isNull(start) ? -1 : c_start), &c_edge_path, &c_vertex_path, c_mode));

/* Convert output */
igraph_vector_int_destroy(&c_edge_path);
Expand Down
20 changes: 16 additions & 4 deletions tools/py-stimulus/src/stimulus/generators/r.py
Original file line number Diff line number Diff line change
Expand Up @@ -255,7 +255,15 @@ def handle_argument_check(param: ParamSpec) -> str:

if param.is_optional and param.is_input and res:
res = optional_wrapper_r(res)

# For optional VERTEX parameters, add the subtraction inside the NULL check
if param.type == "VERTEX":
# Add the subtraction at the end of the wrapped block
name = get_r_parameter_name(param)
res = res.rstrip()
if res.endswith("}"):
# Insert before the closing brace
res = res[:-1] + f" {name} <- {name} - 1\n}}"

# Replace template placeholders
res = indent(res).replace("%I%", get_r_parameter_name(param))
for i, dep in enumerate(param.dependencies):
Expand Down Expand Up @@ -299,9 +307,13 @@ def handle_argument_check(param: ParamSpec) -> str:
name = get_r_parameter_name(param)
call = type.get("CALL", name)
if call:
call_formatted = call.replace("%I%", name)
# Add spaces around arithmetic operators
call_formatted = re.sub(r'(\w+)(\+|\-|\*|/)(\d+)', r'\1 \2 \3', call_formatted)
# For optional VERTEX parameters, subtraction is done in INCONV, so just use the name
if param.is_optional and param.type == "VERTEX":
call_formatted = name
else:
call_formatted = call.replace("%I%", name)
# Add spaces around arithmetic operators
call_formatted = re.sub(r'(\w+)(\+|\-|\*|/)(\d+)', r'\1 \2 \3', call_formatted)
parts.append(call_formatted)

# Format .Call() as multi-line with each argument on its own line
Expand Down
2 changes: 1 addition & 1 deletion tools/stimulus/functions-R.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -992,7 +992,7 @@ igraph_minimum_spanning_tree_unweighted:
igraph_minimum_spanning_tree_prim:

igraph_random_spanning_tree:
PARAMS: GRAPH graph, OUT EDGE_INDICES res, OPTIONAL VERTEX vid=0
PARAMS: GRAPH graph, OUT EDGE_INDICES res, OPTIONAL VERTEX vid

#######################################
# Coloring
Expand Down