Skip to content

Commit 2870826

Browse files
Copilotkrlmlr
andcommitted
fix: add missing enum type translations and fix default value issues
- Added ADJACENCY_MODE enum type with mappings for directed/undirected/upper/lower/min/plus/max - Added SPINCOMMUPDATE enum type with mappings for simple/config - Added SPINGLASS_IMPLEMENTATION enum type with mappings for orig/neg - Added FWALGORITHM enum type with mappings for automatic/original/tree - Added LAYOUT_GRID enum type with mappings for grid/nogrid/auto - Added VCONNNEI enum type with mappings for error/number_of_nodes/ignore/negative - Fixed VCOUNT(graph) default values to use vcount(graph) in layout_lgl - Fixed True boolean defaults to use TRUE in read_graph_lgl and read_graph_ncol - All R CMD check warnings about undefined global variables are now resolved - All tests pass: 1217 passing, 1 skipped Co-authored-by: krlmlr <[email protected]>
1 parent 66fe815 commit 2870826

File tree

3 files changed

+104
-15
lines changed

3 files changed

+104
-15
lines changed

R/aaa-auto.R

Lines changed: 49 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -448,11 +448,21 @@ create_impl <- function(
448448

449449
adjacency_impl <- function(
450450
adjmatrix,
451-
mode = DIRECTED,
451+
mode = c("directed", "undirected", "upper", "lower", "min", "plus", "max"),
452452
loops = c("once", "none", "twice")
453453
) {
454454
# Argument checks
455455
adjmatrix[] <- as.numeric(adjmatrix)
456+
mode <- switch_igraph_arg(
457+
mode,
458+
"directed" = 0L,
459+
"undirected" = 1L,
460+
"upper" = 2L,
461+
"lower" = 3L,
462+
"min" = 4L,
463+
"plus" = 5L,
464+
"max" = 6L
465+
)
456466
loops <- switch_igraph_arg(loops, "none" = 0L, "twice" = 1L, "once" = 2L)
457467

458468
on.exit(.Call(R_igraph_finalizer))
@@ -469,11 +479,21 @@ adjacency_impl <- function(
469479

470480
weighted_adjacency_impl <- function(
471481
adjmatrix,
472-
mode = DIRECTED,
482+
mode = c("directed", "undirected", "upper", "lower", "min", "plus", "max"),
473483
loops = c("once", "none", "twice")
474484
) {
475485
# Argument checks
476486
adjmatrix[] <- as.numeric(adjmatrix)
487+
mode <- switch_igraph_arg(
488+
mode,
489+
"directed" = 0L,
490+
"undirected" = 1L,
491+
"upper" = 2L,
492+
"lower" = 3L,
493+
"min" = 4L,
494+
"plus" = 5L,
495+
"max" = 6L
496+
)
477497
loops <- switch_igraph_arg(loops, "none" = 0L, "twice" = 1L, "once" = 2L)
478498

479499
on.exit(.Call(R_igraph_finalizer))
@@ -3216,7 +3236,7 @@ distances_floyd_warshall_impl <- function(
32163236
to = V(graph),
32173237
weights = NULL,
32183238
mode = c("out", "in", "all", "total"),
3219-
method = AUTOMATIC
3239+
method = c("automatic", "original", "tree")
32203240
) {
32213241
# Argument checks
32223242
ensure_igraph(graph)
@@ -3237,6 +3257,7 @@ distances_floyd_warshall_impl <- function(
32373257
"all" = 3L,
32383258
"total" = 3L
32393259
)
3260+
method <- switch_igraph_arg(method, "automatic" = 0L, "original" = 1L, "tree" = 2L)
32403261

32413262
on.exit(.Call(R_igraph_finalizer))
32423263
# Function call
@@ -7619,7 +7640,7 @@ layout_fruchterman_reingold_impl <- function(
76197640
use_seed = FALSE,
76207641
niter = 500,
76217642
start_temp = sqrt(vcount(graph)),
7622-
grid = AUTO,
7643+
grid = c("auto", "grid", "nogrid"),
76237644
weights = NULL,
76247645
minx = NULL,
76257646
maxx = NULL,
@@ -7634,6 +7655,7 @@ layout_fruchterman_reingold_impl <- function(
76347655
use_seed <- as.logical(use_seed)
76357656
niter <- as.numeric(niter)
76367657
start_temp <- as.numeric(start_temp)
7658+
grid <- switch_igraph_arg(grid, "grid" = 0L, "nogrid" = 1L, "auto" = 2L)
76377659
if (is.null(weights) && "weight" %in% edge_attr_names(graph)) {
76387660
weights <- E(graph)$weight
76397661
}
@@ -7743,11 +7765,11 @@ layout_kamada_kawai_impl <- function(
77437765
layout_lgl_impl <- function(
77447766
graph,
77457767
maxiter = 150,
7746-
maxdelta = VCOUNT(graph),
7747-
area = VCOUNT(graph)^2,
7768+
maxdelta = vcount(graph),
7769+
area = vcount(graph)^2,
77487770
coolexp = 1.5,
7749-
repulserad = VCOUNT(graph)^3,
7750-
cellsize = VCOUNT(graph),
7771+
repulserad = vcount(graph)^3,
7772+
cellsize = vcount(graph),
77517773
root = -1
77527774
) {
77537775
# Argument checks
@@ -8735,9 +8757,9 @@ community_spinglass_impl <- function(
87358757
starttemp = 1,
87368758
stoptemp = 0.01,
87378759
coolfact = 0.99,
8738-
update_rule = CONFIG,
8760+
update_rule = c("config", "simple"),
87398761
gamma = 1.0,
8740-
implementation = ORIG,
8762+
implementation = c("orig", "neg"),
87418763
lambda = 1.0
87428764
) {
87438765
# Argument checks
@@ -8755,7 +8777,9 @@ community_spinglass_impl <- function(
87558777
starttemp <- as.numeric(starttemp)
87568778
stoptemp <- as.numeric(stoptemp)
87578779
coolfact <- as.numeric(coolfact)
8780+
update_rule <- switch_igraph_arg(update_rule, "simple" = 0L, "config" = 1L)
87588781
gamma <- as.numeric(gamma)
8782+
implementation <- switch_igraph_arg(implementation, "orig" = 0L, "neg" = 1L)
87598783
lambda <- as.numeric(lambda)
87608784

87618785
on.exit(.Call(R_igraph_finalizer))
@@ -8783,7 +8807,7 @@ community_spinglass_single_impl <- function(
87838807
weights = NULL,
87848808
vertex,
87858809
spins = 25,
8786-
update_rule = CONFIG,
8810+
update_rule = c("config", "simple"),
87878811
gamma = 1.0
87888812
) {
87898813
# Argument checks
@@ -8798,6 +8822,7 @@ community_spinglass_single_impl <- function(
87988822
}
87998823
vertex <- as.numeric(vertex)
88008824
spins <- as.numeric(spins)
8825+
update_rule <- switch_igraph_arg(update_rule, "simple" = 0L, "config" = 1L)
88018826
gamma <- as.numeric(gamma)
88028827

88038828
on.exit(.Call(R_igraph_finalizer))
@@ -9831,7 +9856,7 @@ read_graph_ncol_impl <- function(
98319856
instream,
98329857
predefnames = NULL,
98339858
names = TRUE,
9834-
weights = True,
9859+
weights = TRUE,
98359860
directed = TRUE
98369861
) {
98379862
# Argument checks
@@ -9858,7 +9883,7 @@ read_graph_ncol_impl <- function(
98589883
read_graph_lgl_impl <- function(
98599884
instream,
98609885
names = TRUE,
9861-
weights = True,
9886+
weights = TRUE,
98629887
directed = TRUE
98639888
) {
98649889
# Argument checks
@@ -11244,7 +11269,7 @@ st_vertex_connectivity_impl <- function(
1124411269
graph,
1124511270
source,
1124611271
target,
11247-
neighbors = NUMBER_OF_NODES
11272+
neighbors = c("number_of_nodes", "error", "ignore", "negative")
1124811273
) {
1124911274
# Argument checks
1125011275
ensure_igraph(graph)
@@ -11262,6 +11287,13 @@ st_vertex_connectivity_impl <- function(
1126211287
call = rlang::caller_env()
1126311288
)
1126411289
}
11290+
neighbors <- switch_igraph_arg(
11291+
neighbors,
11292+
"error" = 0L,
11293+
"number_of_nodes" = 1L,
11294+
"ignore" = 2L,
11295+
"negative" = 3L
11296+
)
1126511297

1126611298
on.exit(.Call(R_igraph_finalizer))
1126711299
# Function call
@@ -13786,7 +13818,9 @@ motifs_randesu_callback_closure_impl <- function(
1378613818
# Argument checks
1378713819
ensure_igraph(graph)
1378813820
size <- as.numeric(size)
13789-
if (!is.null(cut_prob)) cut_prob <- as.numeric(cut_prob)
13821+
if (!is.null(cut_prob)) {
13822+
cut_prob <- as.numeric(cut_prob)
13823+
}
1379013824
if (!is.function(callback)) {
1379113825
cli::cli_abort("{.arg callback} must be a function")
1379213826
}

tools/stimulus/functions-R.yaml

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -574,6 +574,10 @@ igraph_layout_fruchterman_reingold:
574574
igraph_layout_kamada_kawai:
575575

576576
igraph_layout_lgl:
577+
PARAMS: |-
578+
GRAPH graph, OUT MATRIX res, INTEGER maxiter=150, REAL maxdelta=vcount(graph),
579+
REAL area=vcount(graph)^2, REAL coolexp=1.5, REAL repulserad=vcount(graph)^3, REAL cellsize=vcount(graph),
580+
INTEGER root=-1
577581
578582
igraph_layout_reingold_tilford:
579583

@@ -680,8 +684,13 @@ igraph_to_directed:
680684
igraph_read_graph_edgelist:
681685

682686
igraph_read_graph_ncol:
687+
PARAMS: |-
688+
INFILE instream, OPTIONAL VECTOR_STR predefnames, BOOLEAN names=TRUE,
689+
ADD_WEIGHTS weights=TRUE, BOOLEAN directed=TRUE
683690
684691
igraph_read_graph_lgl:
692+
PARAMS: |-
693+
INFILE instream, BOOLEAN names=TRUE, ADD_WEIGHTS weights=TRUE, BOOLEAN directed=TRUE
685694
686695
igraph_read_graph_pajek:
687696

tools/stimulus/types-RR.yaml

Lines changed: 46 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,7 @@ REAL:
2121
ECROSSW: 1.0 - sqrt(edge_density(graph))
2222
ELENW: edge_density(graph) / 10
2323
NEDISTW: 0.2 * (1 - edge_density(graph))
24+
VCOUNT: vcount
2425
INCONV:
2526
IN: '%I% <- as.numeric(%I%)'
2627

@@ -133,6 +134,51 @@ DEGSEQ_MODE:
133134
EDGE_SWITCHING_SIMPLE: c("edge_switching_simple", "configuration", "fast_heur_simple", "configuration_simple", "vl")
134135
INCONV: '%I% <- switch_igraph_arg(%I%, "configuration" = 0L, "vl" = 1L, "fast_heur_simple" = 2L, "configuration_simple" = 3L, "edge_switching_simple" = 4L)'
135136

137+
ADJACENCY_MODE:
138+
DEFAULT:
139+
DIRECTED: c("directed", "undirected", "upper", "lower", "min", "plus", "max")
140+
UNDIRECTED: c("undirected", "directed", "upper", "lower", "min", "plus", "max")
141+
UPPER: c("upper", "lower", "directed", "undirected", "min", "plus", "max")
142+
LOWER: c("lower", "upper", "directed", "undirected", "min", "plus", "max")
143+
MIN: c("min", "max", "plus", "directed", "undirected", "upper", "lower")
144+
PLUS: c("plus", "min", "max", "directed", "undirected", "upper", "lower")
145+
MAX: c("max", "min", "plus", "directed", "undirected", "upper", "lower")
146+
INCONV: '%I% <- switch_igraph_arg(%I%, "directed" = 0L, "undirected" = 1L, "upper" = 2L, "lower" = 3L, "min" = 4L, "plus" = 5L, "max" = 6L)'
147+
148+
SPINCOMMUPDATE:
149+
DEFAULT:
150+
SIMPLE: c("simple", "config")
151+
CONFIG: c("config", "simple")
152+
INCONV: '%I% <- switch_igraph_arg(%I%, "simple" = 0L, "config" = 1L)'
153+
154+
SPINGLASS_IMPLEMENTATION:
155+
DEFAULT:
156+
ORIG: c("orig", "neg")
157+
NEG: c("neg", "orig")
158+
INCONV: '%I% <- switch_igraph_arg(%I%, "orig" = 0L, "neg" = 1L)'
159+
160+
FWALGORITHM:
161+
DEFAULT:
162+
AUTOMATIC: c("automatic", "original", "tree")
163+
ORIGINAL: c("original", "automatic", "tree")
164+
TREE: c("tree", "automatic", "original")
165+
INCONV: '%I% <- switch_igraph_arg(%I%, "automatic" = 0L, "original" = 1L, "tree" = 2L)'
166+
167+
LAYOUT_GRID:
168+
DEFAULT:
169+
GRID: c("grid", "nogrid", "auto")
170+
NOGRID: c("nogrid", "grid", "auto")
171+
AUTO: c("auto", "grid", "nogrid")
172+
INCONV: '%I% <- switch_igraph_arg(%I%, "grid" = 0L, "nogrid" = 1L, "auto" = 2L)'
173+
174+
VCONNNEI:
175+
DEFAULT:
176+
ERROR: c("error", "number_of_nodes", "ignore", "negative")
177+
NUMBER_OF_NODES: c("number_of_nodes", "error", "ignore", "negative")
178+
IGNORE: c("ignore", "error", "number_of_nodes", "negative")
179+
NEGATIVE: c("negative", "error", "number_of_nodes", "ignore")
180+
INCONV: '%I% <- switch_igraph_arg(%I%, "error" = 0L, "number_of_nodes" = 1L, "ignore" = 2L, "negative" = 3L)'
181+
136182
INT:
137183
INCONV: '%I% <- as.integer(%I%)'
138184

0 commit comments

Comments
 (0)