Skip to content

Commit

Permalink
use TRUE/FALSE instead of T/F
Browse files Browse the repository at this point in the history
  • Loading branch information
polettif committed Mar 13, 2024
1 parent 5931c64 commit 894203e
Show file tree
Hide file tree
Showing 16 changed files with 59 additions and 59 deletions.
32 changes: 16 additions & 16 deletions R/biproportional-check.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,70 +5,70 @@ check_params.pukelsheim = function(votes_df, district_seats_df, new_seats_col, u
if(!is.data.frame(votes_df) || ncol(votes_df) != 3) {
stop("`", .votes_df, "` must be a data frame with 3 columns in the ",
"following order:\nparty, district and votes (names can differ).",
call. = F)
call. = FALSE)
}

if(!is.numeric(votes_df[[3]]) || any(votes_df[[3]] < 0)) {
stop("Vote values in `",
.votes_df,
"`s third column must be numbers >= 0.", call. = F)
"`s third column must be numbers >= 0.", call. = FALSE)
}

if(length(unique(district_seats_df[[1]])) != nrow(district_seats_df)) {
stop("District ids in `", .district_seats_df,
"` are not unique.", call. = F)
"` are not unique.", call. = FALSE)
}
if(nrow(votes_df[,c(1,2)]) != nrow(unique(votes_df[,c(1,2)]))) {
stop("There are duplicate party-district pairs in `", .votes_df, "`.",
call. = F)
call. = FALSE)
}

if(!all(district_seats_df[[1]] %in% votes_df[[2]])) {
if(all(district_seats_df[[1]] %in% votes_df[[1]])) {
stop("District ids not found in second column of `", .votes_df,
"`. Are columns in the correct order (party, district, votes)?",
call. = F)
call. = FALSE)
}
stop("Not all district ids in `", .district_seats_df, "`s first column ",
"exist in `", .votes_df, "`s second column.", call. = F)
"exist in `", .votes_df, "`s second column.", call. = FALSE)
}

if(!all(votes_df[[2]] %in% district_seats_df[[1]])) {
stop("Not all district ids in `", .votes_df, "`s second column exist in `",
.district_seats_df, "`s first column.", call. = F)
.district_seats_df, "`s first column.", call. = FALSE)
}
}

prep_votes_matrix = function(votes_matrix, votes_matrix.name) {
vmn = paste0("`", votes_matrix.name, "`")
if(!is.matrix(votes_matrix)) {
stop(vmn, " must be a matrix.", call. = F)
stop(vmn, " must be a matrix.", call. = FALSE)
}
if(sum(votes_matrix %% 1) != 0) {
stop(vmn, " must only contain integers.", call. = F)
stop(vmn, " must only contain integers.", call. = FALSE)
}
if(!is.null(rownames(votes_matrix)) &&
length(unique(rownames(votes_matrix))) != nrow(votes_matrix)) {
stop("rownames in ", vmn , " must be unique.", call. = F)
stop("rownames in ", vmn , " must be unique.", call. = FALSE)
}
if(!is.null(colnames(votes_matrix)) &&
length(unique(colnames(votes_matrix))) != ncol(votes_matrix)) {
stop("colnames in ", vmn, " must be unique.", call. = F)
stop("colnames in ", vmn, " must be unique.", call. = FALSE)
}

return(votes_matrix)
}

prep_method = function(method) {
if(!length(method) %in% c(1,2)) {
stop("Only one or two methods allowed.", call. = F)
stop("Only one or two methods allowed.", call. = FALSE)
}
if(length(method) == 1) {
method <- c(method, method)
}
if(any(method == "largest_remainder_method")) {
stop('Cannot use "largest_remainder_method", only divisor methods ',
'are possible in biproportional apportionment.', call. = F)
'are possible in biproportional apportionment.', call. = FALSE)
}

return(method)
Expand All @@ -83,20 +83,20 @@ prep_district_seats = function(district_seats, votes_matrix,
if(ncol(votes_matrix) != length(district_seats)) {
stop("`", .votes_matrix.name,
"` needs to have districts as columns and parties as rows.",
call. = F)
call. = FALSE)
}
if(!is.null(colnames(votes_matrix))) {
if(is.null(names(district_seats)) ||
!all(sort(colnames(votes_matrix)) == sort(names(district_seats)))) {
stop(.district_seats.name,
" needs to have the same names as the columns in ",
.votes_matrix.name, ".", call. = F)
.votes_matrix.name, ".", call. = FALSE)
}
district_seats <- district_seats[colnames(votes_matrix)]
}
}
if(sum(district_seats %% 1) != 0) {
stop("`", .district_seats.name, "` must be integers.", call. = F)
stop("`", .district_seats.name, "` must be integers.", call. = FALSE)
}
assert(is.atomic(district_seats))

Expand Down
6 changes: 3 additions & 3 deletions R/biproportional.R
Original file line number Diff line number Diff line change
Expand Up @@ -242,7 +242,7 @@ upper_apportionment = function(votes_matrix, district_seats,

# check enough votes in districts
if(!identical(colSums(votes_matrix) > 0, seats_district > 0)) {
stop("No votes in a district with at least one seat", call. = F)
stop("No votes in a district with at least one seat", call. = FALSE)
}

# return values
Expand Down Expand Up @@ -341,7 +341,7 @@ lower_apportionment = function(votes_matrix, seats_cols,
method_impl <- get_method_implementation(method)
if(method_impl != "divisor_round") {
warning('Lower apportionment is only guaranteed to terminate with the default ',
'Sainte-Lagu\u00EB/Webster method (method = "round")', call. = F)
'Sainte-Lagu\u00EB/Webster method (method = "round")', call. = FALSE)
}
round_func = get_round_function(method_impl)
}
Expand Down Expand Up @@ -456,7 +456,7 @@ find_divisor = function(votes,
divisor_range = sort(c(divisor_from, divisor_to))

if(any(is.infinite(votes)) || any(is.nan(votes))) {
stop("Result is undefined, cannot assign all seats in lower apportionment", call. = F)
stop("Result is undefined, cannot assign all seats in lower apportionment", call. = FALSE)
}

# Divisors should be within votes/(seats-1) and votes/(seats+1).
Expand Down
8 changes: 4 additions & 4 deletions R/divisor-check.R
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ check_edge_quotient = function(mtrx_quotient, n_seats, return_indices = FALSE) {
if(quotient_last_with == quotient_first_without) {
indices = which(mtrx_quotient == quotient_last_with, arr.ind = TRUE)[,"col"]
parties = paste0(indices, collapse = " & ")
stop("Result is undefined, equal quotient for parties: ", parties, call. = F)
stop("Result is undefined, equal quotient for parties: ", parties, call. = FALSE)
}
}

Expand All @@ -25,7 +25,7 @@ check_enough_seats = function(votes, n_seats, method) {
return()
}
stop("With ", method," rounding there must be at least as many seats as ",
"there are parties with non-zero votes.", call. = F)
"there are parties with non-zero votes.", call. = FALSE)
}

check_seats_number = function(n_seats, n_seats.name) {
Expand All @@ -34,13 +34,13 @@ check_seats_number = function(n_seats, n_seats.name) {
n_seats >= 0) {
return()
}
stop("`", n_seats.name, "` must be an integer >= 0", call. = F)
stop("`", n_seats.name, "` must be an integer >= 0", call. = FALSE)
}

check_votes_vector = function(votes, votes.name) {
if(is.numeric(votes) && all(!is.na(votes)) &&
all(votes >= 0) && is.vector(votes)) {
return()
}
stop("`", votes.name, "` must be a numeric vector >= 0", call. = F)
stop("`", votes.name, "` must be a numeric vector >= 0", call. = FALSE)
}
2 changes: 1 addition & 1 deletion R/divisor.R
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ highest_averages_method = function(votes, n_seats, divisors) {
if(length(divisors) == 1) {
divisors <- seq(from = divisors, by = 1, length.out = n_seats)
} else if(length(divisors) != n_seats) {
stop("Number of divisors is not equal to the number of seats", call. = F)
stop("Number of divisors is not equal to the number of seats", call. = FALSE)
}
n_parties = length(votes)

Expand Down
2 changes: 1 addition & 1 deletion R/proporz.R
Original file line number Diff line number Diff line change
Expand Up @@ -71,7 +71,7 @@ get_method_implementation = function(method_name) {
method_name <- tolower(method_name)
if(!method_name %in% names(proporz_methods)) {
stop("Unknown apportion method: ", method_name, ".\nAvailable: ",
paste0(names(proporz_methods), collapse=", "), call. = F)
paste0(names(proporz_methods), collapse=", "), call. = FALSE)
}
return(proporz_methods[[method_name]])
}
Expand Down
10 changes: 5 additions & 5 deletions R/quorum.R
Original file line number Diff line number Diff line change
Expand Up @@ -150,7 +150,7 @@ reached_quorums = function(votes_matrix, quorum_funcs) {
assert(is.matrix(votes_matrix))
if(!is.list(quorum_funcs) || !is.function(quorum_funcs[[1]])) {
stop("`", deparse(substitute(quorum_funcs)),
"` is not a list of functions.", call. = F)
"` is not a list of functions.", call. = FALSE)
}

# list of vector whether quorum was reached for each party
Expand All @@ -161,7 +161,7 @@ reached_quorums = function(votes_matrix, quorum_funcs) {
if(length(quorum_funcs) == 1) {
return(quorum_funcs[[1]](votes_matrix))
} else if(is.null(attributes(quorum_funcs)$type)) {
stop("type must be set as list attribute.", call. = F)
stop("type must be set as list attribute.", call. = FALSE)
}

quorum_matrix = do.call(cbind, has_reached_quorum)
Expand All @@ -170,7 +170,7 @@ reached_quorums = function(votes_matrix, quorum_funcs) {
} else if(attributes(quorum_funcs)$type == "ANY") {
quorum_bool = apply(quorum_matrix, 1, any)
} else {
stop("Unknown type `", attributes(quorum_funcs)$type, "`.", call. = F)
stop("Unknown type `", attributes(quorum_funcs)$type, "`.", call. = FALSE)
}
return(quorum_bool)
}
Expand All @@ -187,7 +187,7 @@ apply_quorum_matrix = function(votes_matrix, quorum) {
stopifnot(length(quorum) == nrow(votes_matrix))
quorum_bool = quorum
} else {
stop("Cannot parse quorum function or vector.", call. = F)
stop("Cannot parse quorum function or vector.", call. = FALSE)
}

if(any(!quorum_bool)) {
Expand All @@ -207,7 +207,7 @@ apply_quorum_vector = function(votes_vector, quorum) {
}

if(all(votes_vector < quorum)) {
stop("No party reached the quorum.", call. = F)
stop("No party reached the quorum.", call. = FALSE)
}

votes_vector[votes_vector < quorum] <- 0
Expand Down
4 changes: 2 additions & 2 deletions R/quota.R
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,7 @@ lr_quota = function(votes, n_seats, method = "hare") {
if(method %in% c("hare", "hare-niemeyer", "vinton", "simple")) {
quota = sum(votes)/n_seats
} else {
stop("Unknown quota method '", method, "'", call. = F)
stop("Unknown quota method '", method, "'", call. = FALSE)
}
return(quota)
}
Expand All @@ -76,6 +76,6 @@ check_equal_entries = function(remainders, ordered_remainders, n_seats_remaining
indices = which(remainders == remainder_last_with, arr.ind = TRUE)
parties = paste0(indices, collapse = " & ")
stop("Result is undefined, equal remainder for parties: ", parties,
call. = F)
call. = FALSE)
}
}
4 changes: 2 additions & 2 deletions R/round.R
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ ceil_at = function(x, threshold) {

if(is.numeric(threshold)) {
if(threshold < 0 || threshold > 1) {
stop("Threshold argument must be in [0,1].", call. = F)
stop("Threshold argument must be in [0,1].", call. = FALSE)
}
threshold <- floor(values) + threshold
} else if(threshold == "harmonic") {
Expand All @@ -32,7 +32,7 @@ ceil_at = function(x, threshold) {
threshold <- threshold_geometric(values)
} else {
stop('Numeric value, "harmonic" or "geometric" expected for threshold argument.',
call. = F)
call. = FALSE)
}

ceiled = ceiling(values)
Expand Down
4 changes: 2 additions & 2 deletions R/shinyapp.R
Original file line number Diff line number Diff line change
Expand Up @@ -17,10 +17,10 @@
run_app = function(votes_matrix = NULL, district_seats = NULL) {
# load packages / "import" ####
if(!requireNamespace("shiny", quietly = TRUE)) {
stop("Please install shiny: install.packages('shiny')", call. = F)
stop("Please install shiny: install.packages('shiny')", call. = FALSE)
}
if(!requireNamespace("shinyMatrix", quietly = TRUE)) {
stop("Please install shinyMatrix: install.packages('shinyMatrix')", call. = F)
stop("Please install shinyMatrix: install.packages('shinyMatrix')", call. = FALSE)
}
tags = shiny::tags
fluidRow = shiny::fluidRow
Expand Down
2 changes: 1 addition & 1 deletion R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -98,7 +98,7 @@ pivot_to_df = function(matrix_wide, value_colname = "values") {
assert = function(check) {
if(!all(check)) {
.x = deparse(substitute(check))
stop(.x, " is not TRUE", call. = F)
stop(.x, " is not TRUE", call. = FALSE)
}
invisible()
}
2 changes: 1 addition & 1 deletion data-raw/finland2019.R
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ zip::unzip(zipfile, exdir = "finland_2019")

# Load data ####
suomi19.csv = data.table::fread("finland_2019/ekv-2019_tpat_maa.csv",
header = F,
header = FALSE,
encoding = "Latin-1")

suomi19 <- suomi19.csv |>
Expand Down
18 changes: 9 additions & 9 deletions tests/testthat/test-biproportional.R
Original file line number Diff line number Diff line change
Expand Up @@ -58,8 +58,8 @@ test_that("quorum with vote counts", {
expect_equal(reached_quorum_any_district(vm, 35), rowSums(q1) > 0)
expect_equal(reached_quorum_total(vm, 45), rowSums(q2) > 0)

expect_equal(sum(apply_quorum_matrix(vm, c(F,F,F))), 0)
expect_equal(sum(apply_quorum_matrix(vm, c(F,T,F))), 30)
expect_equal(sum(apply_quorum_matrix(vm, c(FALSE,FALSE,FALSE))), 0)
expect_equal(sum(apply_quorum_matrix(vm, c(FALSE,TRUE,FALSE))), 30)
expect_error_fixed(apply_quorum_matrix(vm, "x"), "Cannot parse quorum function or vector.")
})

Expand All @@ -78,10 +78,10 @@ test_that("quorum with percentages counts", {
test_that("quorum", {
vm = matrix(c(90, 4, 5, 1, 104, 4, 1, 1), ncol = 2)*10

q_district = c(T,F,T,F)
q_total = c(T,T,F,F)
q_district_and_total = c(T,F,F,F)
q_district_or_total = c(T,T,T,F)
q_district = c(TRUE,FALSE,TRUE,FALSE)
q_total = c(TRUE,TRUE,FALSE,FALSE)
q_district_and_total = c(TRUE,FALSE,FALSE,FALSE)
q_district_or_total = c(TRUE,TRUE,TRUE,FALSE)

# reached_quorums
expect_equal(reached_quorums(vm, quorum_any(any_district = 0.05)),
Expand Down Expand Up @@ -275,11 +275,11 @@ test_that("almost empty vote_matrix", {
test_that("undefined result biproportional", {
seats = c(10, 20, 1, 1)
set.seed(1284)
vm = matrix(runif(4*10), ncol = 4) * matrix(rep(seats, 10), byrow = T, ncol = 4) * 1000
vm = matrix(runif(4*10), ncol = 4) * matrix(rep(seats, 10), byrow = TRUE, ncol = 4) * 1000
vm <- round(vm)
vm[vm < 200] <- 0

expect_equal(upper_apportionment(vm, seats, use_list_votes = F)$party,
expect_equal(upper_apportionment(vm, seats, use_list_votes = FALSE)$party,
proporz(rowSums(vm), sum(seats), "round"))

expect_error_fixed(upper_apportionment(vm, seats),
Expand Down Expand Up @@ -312,7 +312,7 @@ test_that("districts with one seat", {
seats = c(10, 20, 1, 1)
set.seed(80)

votes_matrix = matrix(runif(4*10), ncol = 4) * matrix(rep(seats, 10), byrow = T, ncol = 4) * 100
votes_matrix = matrix(runif(4*10), ncol = 4) * matrix(rep(seats, 10), byrow = TRUE, ncol = 4) * 100
votes_matrix <- round(votes_matrix)
votes_matrix[votes_matrix < 30] <- 0

Expand Down
8 changes: 4 additions & 4 deletions tests/testthat/test-proporz.R
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ test_that("generic proporz", {
}

test_that("proporz parameter range", {
method_list = unique(unlist(proporz_methods, use.names = F))
method_list = unique(unlist(proporz_methods, use.names = FALSE))

set.seed(0)
for(n_parties in 1:2) {
Expand All @@ -43,7 +43,7 @@ test_that("proporz parameter range", {
expect_equal(sum(seats), n_seats)

if(n_seats > 0) {
.quorum = sort(c(votes,0), decreasing = T)[2]+0.5
.quorum = sort(c(votes,0), decreasing = TRUE)[2]+0.5
seats_Q = proporz(votes, n_seats, method_impl, quorum = .quorum)
expect_equal(sum(seats_Q > 0), 1)
}
Expand All @@ -67,7 +67,7 @@ test_that("proporz parameter range", {
})

test_that("quorum", {
method_list = unique(unlist(proporz_methods, use.names = F))
method_list = unique(unlist(proporz_methods, use.names = FALSE))

for(method in method_list) {
expect_error(proporz(c(50, 30), 3, method, 60), "No party reached the quorum.",
Expand All @@ -84,7 +84,7 @@ test_that("all method names", {

test_that("undefined result errors", {
expect_error(proporz(c(1, 10, 10), 1, "round"),
"Result is undefined, equal quotient for parties: 2 & 3", fixed = T)
"Result is undefined, equal quotient for parties: 2 & 3", fixed = TRUE)
expect_equal(proporz(c(1, 10, 10), 2, "round"), c(0,1,1))

expect_error(largest_remainder_method(c(10, 10, 0), 1),
Expand Down
Loading

0 comments on commit 894203e

Please sign in to comment.