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
50 changes: 25 additions & 25 deletions R/aaa-auto.R
Original file line number Diff line number Diff line change
Expand Up @@ -768,14 +768,14 @@ realize_degree_sequence_impl <- function(
out.deg,
in.deg = NULL,
allowed.edge.types = c("simple", "loops", "multi", "all"),
method = c("smallest", "largest", "index")
algorithm = c("smallest", "largest", "index")
) {
# Argument checks
out.deg <- as.numeric(out.deg)
if (!is.null(in.deg)) in.deg <- as.numeric(in.deg)
allowed.edge.types <- switch_igraph_arg(allowed.edge.types,
"simple" = 0L, "loop" = 1L, "loops" = 1L, "multi" = 6L, "multiple" = 6L, "all" = 7L)
method <- switch_igraph_arg(method, "smallest" = 0L, "largest" = 1L, "index" = 2L)
algorithm <- switch_igraph_arg(algorithm, "smallest" = 0L, "largest" = 1L, "index" = 2L)

on.exit(.Call(R_igraph_finalizer))
# Function call
Expand All @@ -784,15 +784,15 @@ realize_degree_sequence_impl <- function(
out.deg,
in.deg,
allowed.edge.types,
method
algorithm
)

if (igraph_opt("add.params")) {
res$name <- 'Graph from degree sequence'
res$out.deg <- out.deg
res$in.deg <- in.deg
res$allowed.edge.types <- allowed.edge.types
res$method <- method
res$algorithm <- algorithm
}

res
Expand All @@ -802,14 +802,14 @@ realize_bipartite_degree_sequence_impl <- function(
degrees1,
degrees2,
allowed.edge.types = c("simple", "loops", "multi", "all"),
method = c("smallest", "largest", "index")
algorithm = c("smallest", "largest", "index")
) {
# Argument checks
degrees1 <- as.numeric(degrees1)
degrees2 <- as.numeric(degrees2)
allowed.edge.types <- switch_igraph_arg(allowed.edge.types,
"simple" = 0L, "loop" = 1L, "loops" = 1L, "multi" = 6L, "multiple" = 6L, "all" = 7L)
method <- switch_igraph_arg(method, "smallest" = 0L, "largest" = 1L, "index" = 2L)
algorithm <- switch_igraph_arg(algorithm, "smallest" = 0L, "largest" = 1L, "index" = 2L)

on.exit(.Call(R_igraph_finalizer))
# Function call
Expand All @@ -818,15 +818,15 @@ realize_bipartite_degree_sequence_impl <- function(
degrees1,
degrees2,
allowed.edge.types,
method
algorithm
)

if (igraph_opt("add.params")) {
res$name <- 'Bipartite graph from degree sequence'
res$degrees1 <- degrees1
res$degrees2 <- degrees2
res$allowed.edge.types <- allowed.edge.types
res$method <- method
res$algorithm <- algorithm
}

res
Expand Down Expand Up @@ -2441,7 +2441,7 @@ harmonic_centrality_cutoff_impl <- function(

personalized_pagerank_impl <- function(
graph,
algo = c("prpack", "arpack"),
algorithm = c("prpack", "arpack"),
vids = V(graph),
directed = TRUE,
damping = 0.85,
Expand All @@ -2451,7 +2451,7 @@ personalized_pagerank_impl <- function(
) {
# Argument checks
ensure_igraph(graph)
algo <- switch_igraph_arg(algo, "arpack" = 1L, "prpack" = 2L)
algorithm <- switch_igraph_arg(algorithm, "arpack" = 1L, "prpack" = 2L)
vids <- as_igraph_vs(graph, vids)
directed <- as.logical(directed)
damping <- as.numeric(damping)
Expand Down Expand Up @@ -2479,7 +2479,7 @@ personalized_pagerank_impl <- function(
res <- .Call(
R_igraph_personalized_pagerank,
graph,
algo,
algorithm,
vids - 1,
directed,
damping,
Expand All @@ -2495,7 +2495,7 @@ personalized_pagerank_impl <- function(

personalized_pagerank_vs_impl <- function(
graph,
algo = c("prpack", "arpack"),
algorithm = c("prpack", "arpack"),
vids = V(graph),
directed = TRUE,
damping = 0.85,
Expand All @@ -2506,7 +2506,7 @@ personalized_pagerank_vs_impl <- function(
) {
# Argument checks
ensure_igraph(graph)
algo <- switch_igraph_arg(algo, "arpack" = 1L, "prpack" = 2L)
algorithm <- switch_igraph_arg(algorithm, "arpack" = 1L, "prpack" = 2L)
vids <- as_igraph_vs(graph, vids)
directed <- as.logical(directed)
damping <- as.numeric(damping)
Expand Down Expand Up @@ -2534,7 +2534,7 @@ personalized_pagerank_vs_impl <- function(
res <- .Call(
R_igraph_personalized_pagerank_vs,
graph,
algo,
algorithm,
vids - 1,
directed,
damping,
Expand All @@ -2554,7 +2554,7 @@ personalized_pagerank_vs_impl <- function(
rewire_impl <- function(
rewire,
n,
mode = 0L
mode = SIMPLE
) {
# Argument checks
ensure_igraph(rewire)
Expand Down Expand Up @@ -2972,7 +2972,7 @@ topological_sorting_impl <- function(
feedback_arc_set_impl <- function(
graph,
weights = NULL,
algo = c("approx_eades", "exact_ip")
algorithm = c("approx_eades", "exact_ip")
) {
# Argument checks
ensure_igraph(graph)
Expand All @@ -2984,15 +2984,15 @@ feedback_arc_set_impl <- function(
} else {
weights <- NULL
}
algo <- switch_igraph_arg(algo, "exact_ip" = 0L, "approx_eades" = 1L)
algorithm <- switch_igraph_arg(algorithm, "exact_ip" = 0L, "approx_eades" = 1L)

on.exit(.Call(R_igraph_finalizer))
# Function call
res <- .Call(
R_igraph_feedback_arc_set,
graph,
weights,
algo
algorithm
)
if (igraph_opt("return.vs.es")) {
res <- create_es(graph, res)
Expand All @@ -3003,7 +3003,7 @@ feedback_arc_set_impl <- function(
feedback_vertex_set_impl <- function(
graph,
weights = NULL,
algo = c("exact_ip")
algorithm = c("exact_ip")
) {
# Argument checks
ensure_igraph(graph)
Expand All @@ -3015,15 +3015,15 @@ feedback_vertex_set_impl <- function(
} else {
weights <- NULL
}
algo <- switch_igraph_arg(algo, "exact_ip" = 0L)
algorithm <- switch_igraph_arg(algorithm, "exact_ip" = 0L)

on.exit(.Call(R_igraph_finalizer))
# Function call
res <- .Call(
R_igraph_feedback_vertex_set,
graph,
weights,
algo
algorithm
)
if (igraph_opt("return.vs.es")) {
res <- create_vs(graph, res)
Expand Down Expand Up @@ -6695,7 +6695,7 @@ write_graph_pajek_impl <- function(
write_graph_gml_impl <- function(
graph,
outstream,
options = 0L,
options = DEFAULT,
id,
creator = NULL
) {
Expand Down Expand Up @@ -9384,20 +9384,20 @@ random_spanning_tree_impl <- function(
tree_game_impl <- function(
n,
directed = FALSE,
method = c("lerw", "prufer")
algorithm = c("lerw", "prufer")
) {
# Argument checks
n <- as.numeric(n)
directed <- as.logical(directed)
method <- switch_igraph_arg(method, "prufer" = 0L, "lerw" = 1L)
algorithm <- switch_igraph_arg(algorithm, "prufer" = 0L, "lerw" = 1L)

on.exit(.Call(R_igraph_finalizer))
# Function call
res <- .Call(
R_igraph_tree_game,
n,
directed,
method
algorithm
)

res
Expand Down
46 changes: 39 additions & 7 deletions R/centrality.R
Original file line number Diff line number Diff line change
Expand Up @@ -30,19 +30,28 @@ subgraph.centrality <- function(graph, diag = FALSE) {
#' @export
page.rank <- function(
graph,
algo = c("prpack", "arpack"),
algo = deprecated(),
vids = V(graph),
directed = TRUE,
damping = 0.85,
personalized = NULL,
weights = NULL,
options = NULL
options = NULL,
algorithm = c("prpack", "arpack")
) {
# nocov start
lifecycle::deprecate_soft("2.0.0", "page.rank()", "page_rank()")

if (lifecycle::is_present(algo)) {
lifecycle::deprecate_warn("2.1.0", "page.rank(algo = )", "page.rank(algorithm = )")
if (missing(algorithm)) {
algorithm <- algo
}
}

page_rank(
graph = graph,
algo = algo,
algorithm = algorithm,
vids = vids,
directed = directed,
damping = damping,
Expand Down Expand Up @@ -1645,14 +1654,15 @@ hub_score <- function(
#' increase at all.
#'
#' @param graph The graph object.
#' @param algo Character scalar, which implementation to use to carry out the
#' @param algorithm Character scalar, which implementation to use to carry out the
#' calculation. The default is `"prpack"`, which uses the PRPACK library
#' (<https://github.com/dgleich/prpack>) to calculate PageRank scores
#' by solving a set of linear equations. This is a new implementation in igraph
#' version 0.7, and the suggested one, as it is the most stable and the fastest
#' for all but small graphs. `"arpack"` uses the ARPACK library, the
#' default implementation from igraph version 0.5 until version 0.7. It computes
#' PageRank scores by solving an eingevalue problem.
#' @param algo `r lifecycle::badge("deprecated")` Use `algorithm` instead.
#' @param vids The vertices of interest.
#' @param directed Logical, if true directed paths will be considered for
#' directed graphs. It is ignored for undirected graphs.
Expand Down Expand Up @@ -1713,17 +1723,39 @@ hub_score <- function(
#' @cdocs igraph_personalized_pagerank
page_rank <- function(
graph,
algo = c("prpack", "arpack"),
algo = deprecated(),
vids = V(graph),
directed = TRUE,
damping = 0.85,
personalized = NULL,
weights = NULL,
options = NULL
options = NULL,
algorithm = c("prpack", "arpack")
) {
if (lifecycle::is_present(algo)) {
lifecycle::deprecate_warn("2.1.0", "page_rank(algo = )", "page_rank(algorithm = )")
if (missing(algorithm)) {
algorithm <- algo
}
}

# Don't call personalized_pagerank_impl directly due to a Stimulus bug
# where renamed parameters aren't properly handled in conditional logic.
# Instead, replicate the logic here.

# Handle options initialization based on algorithm (before conversion to integer)
if (is.null(options)) {
algorithm_val <- match.arg(algorithm)
if (algorithm_val == "arpack") {
options <- arpack_defaults()
} else if (algorithm_val == "prpack") {
options <- list(niter=1000, eps=0.001)
}
}

personalized_pagerank_impl(
graph = graph,
algo = algo,
algorithm = algorithm,
vids = vids,
directed = directed,
damping = damping,
Expand Down
Loading