From 3d7c2ff6f84117bb42a2c1e34a4e3c3b913a8a95 Mon Sep 17 00:00:00 2001 From: Etienne Bacher <52219252+etiennebacher@users.noreply.github.com> Date: Thu, 8 Aug 2024 14:37:04 +0200 Subject: [PATCH] refactor: fix some lints (#1176) --- R/dataframe__frame.R | 2 +- R/polars_envvars.R | 2 +- R/utils.R | 6 +- inst/misc/develop_polars.R | 4 +- tests/testthat/helper.R | 2 +- tests/testthat/test-Rerr.R | 10 +-- tests/testthat/test-as_polars.R | 6 +- tests/testthat/test-csv-read.R | 2 +- tests/testthat/test-dataframe.R | 13 ++-- tests/testthat/test-expr_expr.R | 110 ++++++++++++++---------------- tests/testthat/test-expr_name.R | 10 +-- tests/testthat/test-groupby.R | 2 +- tests/testthat/test-lazy.R | 8 +-- tests/testthat/test-rbackground.R | 12 ++-- tests/testthat/test-series.R | 6 +- tests/testthat/test-whenthen.R | 10 +-- 16 files changed, 92 insertions(+), 113 deletions(-) diff --git a/R/dataframe__frame.R b/R/dataframe__frame.R index 57b7c71a9..06ad5688f 100644 --- a/R/dataframe__frame.R +++ b/R/dataframe__frame.R @@ -1638,7 +1638,7 @@ DataFrame_rename = function(...) { #' df #' #' df$describe() -DataFrame_describe = function(percentiles = c(.25, .75), interpolation = "nearest") { +DataFrame_describe = function(percentiles = c(0.25, 0.75), interpolation = "nearest") { uw = \(res) unwrap(res, "in $describe():") if (length(self$columns) == 0) { diff --git a/R/polars_envvars.R b/R/polars_envvars.R index 7eef6936e..6a103a1f4 100644 --- a/R/polars_envvars.R +++ b/R/polars_envvars.R @@ -109,7 +109,7 @@ polars_envvars = function() { c("POLARS_WARN_UNSTABLE", "0") ) |> as.data.frame() out = vector("list", length(envvars)) - for (i in 1:nrow(envvars)) { + for (i in seq_len(nrow(envvars))) { e = envvars[[1]][i] out[[e]] = Sys.getenv(e, unset = envvars[[2]][i]) } diff --git a/R/utils.R b/R/utils.R index 46141eef7..188e59fb4 100644 --- a/R/utils.R +++ b/R/utils.R @@ -323,7 +323,7 @@ get_method_usages = function(env, pattern = "") { paste0_len = function(..., collapse = NULL, sep = "") { dot_args = list2(...) # any has zero length, return zero length - if (any(!sapply(dot_args, length))) { + if (!all(lengths(dot_args))) { character() } else { paste(..., collapse = collapse, sep = sep) @@ -385,7 +385,7 @@ print_env = function(api, name, max_depth = 10) { #' @noRd #' @return X without any AsIs subclass unAsIs = function(X) { - if ("AsIs" %in% class(X)) { + if (inherits(X, "AsIs")) { class(X) = class(X)[-match("AsIs", class(X))] } X @@ -421,7 +421,7 @@ restruct_list = function(l) { if (!length(structs_found_list)) { return(l) } - structs_found_list = structs_found_list |> (\(x) x[order(-sapply(x, length))])() + structs_found_list = structs_found_list |> (\(x) x[order(-lengths(x))])() val = NULL # to satisyfy R CMD check no undefined global # restruct all tags in list diff --git a/inst/misc/develop_polars.R b/inst/misc/develop_polars.R index a117974bc..0b6a4902a 100644 --- a/inst/misc/develop_polars.R +++ b/inst/misc/develop_polars.R @@ -266,7 +266,7 @@ find_missing_return = function() { has_value() }) - names(all_doc_values[sapply(all_doc_values, length) < 1]) + names(all_doc_values[lengths(all_doc_values) < 1]) } @@ -298,7 +298,7 @@ run_all_examples_collect_errors = \(skip_these = character(), time_examples = FA if (time_examples) { t2 = Sys.time() duration = difftime(t2, t1, units = "secs") - if (duration > .1) cat(" ", duration, "s") + if (duration > 0.1) cat(" ", duration, "s") } if (!is.null(err)) list(err = err, txt = txt) }) diff --git a/tests/testthat/helper.R b/tests/testthat/helper.R index 4e1095418..25a2b7f91 100644 --- a/tests/testthat/helper.R +++ b/tests/testthat/helper.R @@ -75,7 +75,7 @@ make_print_cases = function() { expect_rpolarserr = function(expr, ctxs) { res = result(expr) expect_identical(class(res$err), "RPolarsErr") - expect_identical(names(res$err$contexts()), ctxs) + expect_named(res$err$contexts(), ctxs) } expect_snapshot_file = function(path, ...) { diff --git a/tests/testthat/test-Rerr.R b/tests/testthat/test-Rerr.R index d580f46b9..7c43a01a3 100644 --- a/tests/testthat/test-Rerr.R +++ b/tests/testthat/test-Rerr.R @@ -6,8 +6,8 @@ test_that("can add any context to err", { rpolarserr = .pr$Err$new() for (i in err_types) rpolarserr = rpolarserr[[i]](i) - expect_identical( - names(rpolarserr$contexts()), + expect_named( + rpolarserr$contexts(), c( "When", "PlainErrorMessage", "ValueOutOfScope", "TypeMismatch", "Hint", "BadValue", "BadValue", "BadArgument" @@ -20,11 +20,11 @@ test_that("set/replace/read rcall & rinfo", { err1 = err0$rinfo("in $foo()") err2 = err1$rinfo("in $bar()") - expect_identical(err0$get_rinfo(), NULL) + expect_null(err0$get_rinfo()) expect_identical(err1$get_rinfo(), "in $foo()") expect_identical(err2$get_rinfo(), "in $bar()") - expect_identical(err2$get_rcall(), NULL) + expect_null(err2$get_rcall()) err_a = unwrap_err(result(unwrap(Err(err2), "in $bob()"))) expect_identical(err_a$get_rcall(), call_to_string(sys.call(1))) @@ -39,6 +39,6 @@ test_that("err_on_named_args", { # err on named args ctx = err_on_named_args(a = 1, b = 2)$err$contexts() - expect_identical(names(ctx), c("Hint", "PlainErrorMessage", "BadArgument")) + expect_named(ctx, c("Hint", "PlainErrorMessage", "BadArgument")) expect_identical(ctx$BadArgument, "a, b") }) diff --git a/tests/testthat/test-as_polars.R b/tests/testthat/test-as_polars.R index 3c04f46a5..385fdcb1f 100644 --- a/tests/testthat/test-as_polars.R +++ b/tests/testthat/test-as_polars.R @@ -150,7 +150,7 @@ patrick::with_parameters_test_that( pl_series = as_polars_series(x) expect_s3_class(pl_series, "RPolarsSeries") - expect_identical(length(pl_series), 1L) + expect_length(pl_series, 1L) expect_equal(pl_series$name, expected_name) if (inherits(x, "nanoarrow_array_stream")) { @@ -204,7 +204,7 @@ test_that("tests for vctrs_rcrd", { vec = latlon(c(32.71, 2.95), c(-117.17, 1.67)) - expect_identical(length(as_polars_series(vec)), 2L) + expect_length(as_polars_series(vec), 2L) expect_snapshot(pl$DataFrame(foo = vec)$dtypes, cran = TRUE) @@ -353,7 +353,7 @@ patrick::with_parameters_test_that("as_polars_series for nanoarrow_array_stream" expect_s3_class(pl_series, "RPolarsSeries") expect_grepl_error(x$get_next(), "already been released") - expect_identical(length(pl_series), 2L) + expect_length(pl_series, 2L) }, .cases = make_nanoarrow_array_stream_cases() ) diff --git a/tests/testthat/test-csv-read.R b/tests/testthat/test-csv-read.R index bd1a0f410..73b6aeeb7 100644 --- a/tests/testthat/test-csv-read.R +++ b/tests/testthat/test-csv-read.R @@ -194,6 +194,6 @@ test_that("cache url tempfile", { check_is_link(url, reuse_downloaded = TRUE) attempt_2 = cache_temp_file[[url]] - expect_true(!is.null(cache_temp_file[[url]])) + expect_false(is.null(cache_temp_file[[url]])) expect_equal(attempt_1, attempt_2) }) diff --git a/tests/testthat/test-dataframe.R b/tests/testthat/test-dataframe.R index 46bba75a1..2091576f7 100644 --- a/tests/testthat/test-dataframe.R +++ b/tests/testthat/test-dataframe.R @@ -132,10 +132,7 @@ test_that("get set properties", { )) ) - expect_equal( - df$columns, - names(df$schema) - ) + expect_named(df$schema, df$columns) }) @@ -152,7 +149,7 @@ test_that("DataFrame, custom schema", { FUN = "==" )) ) - expect_identical(names(df$schema), names(iris)) + expect_named(df$schema, names(iris)) # works fine if a variable is called "schema" expect_no_error( @@ -458,7 +455,7 @@ test_that("with_columns: create a list variable", { test_that("with_columns lazy/eager", { l = list( a = 1:4, - b = c(.5, 4, 10, 13), + b = c(0.5, 4, 10, 13), c = c(TRUE, TRUE, FALSE, TRUE) ) df = pl$DataFrame(l) @@ -523,7 +520,7 @@ test_that("with_columns_seq", { test_that("head lazy/eager", { l = list( a = 1:4, - b = c(.5, 4, 10, 13), + b = c(0.5, 4, 10, 13), c = c(TRUE, TRUE, FALSE, TRUE) ) df = pl$DataFrame(l) @@ -630,7 +627,7 @@ test_that("simple translations", { expect_equal(a, b, ignore_attr = TRUE) a = pl$DataFrame(mtcars)$estimated_size() - expect_equal(a, 2816, tolerance = .1) + expect_equal(a, 2816, tolerance = 0.1) # trigger u8 conversion errors expect_grepl_error(pl$DataFrame(mtcars)$std(256), c("ddof", "exceed the upper bound for u8 of 255")) diff --git a/tests/testthat/test-expr_expr.R b/tests/testthat/test-expr_expr.R index 4b46b81f2..fa7f26c34 100644 --- a/tests/testthat/test-expr_expr.R +++ b/tests/testthat/test-expr_expr.R @@ -32,7 +32,7 @@ test_that("expression boolean operators", { results = unlist(cmp_operators_df$to_list()) fails = results[!unlist(results)] - expect_equal(names(fails), character()) + expect_named(fails, character()) }) make_cases = function() { @@ -185,7 +185,7 @@ test_that("first last heaad tail", { results = unlist(check_list) fails = results[!unlist(results)] - expect_equal(names(fails), character()) + expect_named(fails, character()) df = pl$DataFrame(list(a = 1:11))$select( pl$col("a")$head()$alias("head10"), @@ -230,8 +230,8 @@ test_that("is_null", { data.frame( a = c(1:2, NA_integer_, 1L, 5L), b = c(1, 2, NaN, 1, 5), - a_isnull = c(F, F, T, F, F), - b_isnull = rep(F, 5) + a_isnull = c(FALSE, FALSE, TRUE, FALSE, FALSE), + b_isnull = rep(FALSE, 5) ) ) @@ -249,7 +249,7 @@ test_that("min max", { results = unlist(check_list) fails = results[!unlist(results)] - expect_equal(names(fails), character()) + expect_named(fails, character()) }) test_that("$over()", { @@ -449,24 +449,24 @@ test_that("prefix suffix reverse", { test_that("and or is_in xor", { df = pl$DataFrame(list()) - expect_true(df$select(pl$lit(T) & T)$to_data_frame()[[1L]]) - expect_true(!df$select(pl$lit(T) & F)$to_data_frame()[[1L]]) - expect_true(!df$select(pl$lit(F) & T)$to_data_frame()[[1L]]) - expect_true(!df$select(pl$lit(F) & F)$to_data_frame()[[1L]]) + expect_true(df$select(pl$lit(TRUE) & TRUE)$to_data_frame()[[1L]]) + expect_false(df$select(pl$lit(TRUE) & FALSE)$to_data_frame()[[1L]]) + expect_false(df$select(pl$lit(FALSE) & TRUE)$to_data_frame()[[1L]]) + expect_false(df$select(pl$lit(FALSE) & FALSE)$to_data_frame()[[1L]]) - expect_true(df$select(pl$lit(T) | T)$to_data_frame()[[1L]]) - expect_true(df$select(pl$lit(T) | F)$to_data_frame()[[1L]]) - expect_true(df$select(pl$lit(F) | T)$to_data_frame()[[1L]]) - expect_true(!df$select(pl$lit(F) | F)$to_data_frame()[[1L]]) + expect_true(df$select(pl$lit(TRUE) | TRUE)$to_data_frame()[[1L]]) + expect_true(df$select(pl$lit(TRUE) | FALSE)$to_data_frame()[[1L]]) + expect_true(df$select(pl$lit(FALSE) | TRUE)$to_data_frame()[[1L]]) + expect_false(df$select(pl$lit(FALSE) | FALSE)$to_data_frame()[[1L]]) - expect_true(!df$select(pl$lit(T)$xor(pl$lit(T)))$to_data_frame()[[1L]]) - expect_true(df$select(pl$lit(T)$xor(pl$lit(F)))$to_data_frame()[[1L]]) - expect_true(df$select(pl$lit(F)$xor(pl$lit(T)))$to_data_frame()[[1L]]) - expect_true(!df$select(pl$lit(F)$xor(pl$lit(F)))$to_data_frame()[[1L]]) + expect_false(df$select(pl$lit(TRUE)$xor(pl$lit(TRUE)))$to_data_frame()[[1L]]) + expect_true(df$select(pl$lit(TRUE)$xor(pl$lit(FALSE)))$to_data_frame()[[1L]]) + expect_true(df$select(pl$lit(FALSE)$xor(pl$lit(TRUE)))$to_data_frame()[[1L]]) + expect_false(df$select(pl$lit(FALSE)$xor(pl$lit(FALSE)))$to_data_frame()[[1L]]) df = pl$DataFrame(list(a = c(1:3, NA_integer_))) expect_true(df$select(pl$lit(1L)$is_in(pl$col("a")))$to_data_frame()[[1L]]) - expect_true(!df$select(pl$lit(4L)$is_in(pl$col("a")))$to_data_frame()[[1L]]) + expect_false(df$select(pl$lit(4L)$is_in(pl$col("a")))$to_data_frame()[[1L]]) # NA_int == NA_int @@ -554,16 +554,10 @@ test_that("to_physical + cast", { ) # strict = FALSE yield NULL for overflow - expect_identical( - df_big_n$with_columns(pl$col("big")$cast(pl$Int32, strict = FALSE)$is_null())$to_data_frame()$big, - TRUE - ) + expect_true(df_big_n$with_columns(pl$col("big")$cast(pl$Int32, strict = FALSE)$is_null())$to_data_frame()$big) # no overflow to Int64 - expect_identical( - df_big_n$with_columns(pl$col("big")$cast(pl$Int64)$is_null())$to_data_frame()$big, - FALSE - ) + expect_false(df_big_n$with_columns(pl$col("big")$cast(pl$Int64)$is_null())$to_data_frame()$big) }) @@ -586,7 +580,7 @@ test_that("pow, rpow, sqrt, log10", { # log expect_equal(pl$DataFrame(list(a = exp(1)^(-1:3)))$select(pl$col("a")$log())$to_data_frame()$a, -1:3) - expect_equal(pl$DataFrame(list(a = .42^(-1:3)))$select(pl$col("a")$log(0.42))$to_data_frame()$a, -1:3) + expect_equal(pl$DataFrame(list(a = 0.42^(-1:3)))$select(pl$col("a")$log(0.42))$to_data_frame()$a, -1:3) # exp log10123 = suppressWarnings(log(-1:3)) @@ -1000,9 +994,9 @@ test_that("sort_by", { pl$col("ab")$sort_by("v3")$alias("ab3"), pl$col("ab")$sort_by("v2")$alias("ab2"), pl$col("ab")$sort_by("v1")$alias("ab1"), - pl$col("ab")$sort_by(list("v3", pl$col("v1")), descending = c(F, T))$alias("ab13FT"), - pl$col("ab")$sort_by(list("v3", pl$col("v1")), descending = T)$alias("ab13T"), - pl$col("ab")$sort_by(c("v3", "v1"), descending = T)$alias("ab13T2") + pl$col("ab")$sort_by(list("v3", pl$col("v1")), descending = c(FALSE, TRUE))$alias("ab13FT"), + pl$col("ab")$sort_by(list("v3", pl$col("v1")), descending = TRUE)$alias("ab13T"), + pl$col("ab")$sort_by(c("v3", "v1"), descending = TRUE)$alias("ab13T2") )$to_list(), list( ab4 = l$ab[order(l$v4)], @@ -1010,8 +1004,8 @@ test_that("sort_by", { ab2 = l$ab[order(l$v2)], ab1 = l$ab[order(l$v1)], ab13FT = l$ab[order(l$v3, rev(l$v1))], - ab13T = l$ab[order(l$v3, l$v1, decreasing = T)], - ab13T2 = l$ab[order(l$v3, l$v1, decreasing = T)] + ab13T = l$ab[order(l$v3, l$v1, decreasing = TRUE)], + ab13T2 = l$ab[order(l$v3, l$v1, decreasing = TRUE)] ) ) @@ -1372,18 +1366,18 @@ test_that("Expr_quantile", { expect_identical( pl$select( - pl$lit(0:1)$quantile(.5, "nearest")$alias("nearest"), - pl$lit(0:1)$quantile(.5, "linear")$alias("linear"), - pl$lit(0:1)$quantile(.5, "higher")$alias("higher"), - pl$lit(0:1)$quantile(.5, "lower")$alias("lower"), - pl$lit(0:1)$quantile(.5, "midpoint")$alias("midpoint") + pl$lit(0:1)$quantile(0.5, "nearest")$alias("nearest"), + pl$lit(0:1)$quantile(0.5, "linear")$alias("linear"), + pl$lit(0:1)$quantile(0.5, "higher")$alias("higher"), + pl$lit(0:1)$quantile(0.5, "lower")$alias("lower"), + pl$lit(0:1)$quantile(0.5, "midpoint")$alias("midpoint") )$to_list(), list( nearest = 1.0, linear = 0.5, higher = 1, lower = 0, - midpoint = .5 + midpoint = 0.5 ) ) @@ -1393,14 +1387,14 @@ test_that("Expr_quantile", { pl$lit(c(0:1, NA_integer_))$quantile(0.5, "midpoint")$alias("midpoint_na"), pl$lit(c(0:1, NaN))$quantile(0.5, "midpoint")$alias("midpoint_nan"), pl$lit(c(0:1, NA_integer_))$quantile(0, "nearest")$alias("nearest_na"), - pl$lit(c(0:1, NaN))$quantile(.7, "nearest")$alias("nearest_nan"), + pl$lit(c(0:1, NaN))$quantile(0.7, "nearest")$alias("nearest_nan"), pl$lit(c(0:1, NA_integer_))$quantile(0, "linear")$alias("linear_na"), - pl$lit(c(0:1, NaN))$quantile(.51, "linear")$alias("linear_nan"), - pl$lit(c(0:1, NaN))$quantile(.7, "linear")$alias("linear_nan_0.7"), - pl$lit(c(0, Inf, NaN))$quantile(.51, "linear")$alias("linear_nan_inf") + pl$lit(c(0:1, NaN))$quantile(0.51, "linear")$alias("linear_nan"), + pl$lit(c(0:1, NaN))$quantile(0.7, "linear")$alias("linear_nan_0.7"), + pl$lit(c(0, Inf, NaN))$quantile(0.51, "linear")$alias("linear_nan_inf") )$to_list(), list( - midpoint_na = .5, + midpoint_na = 0.5, midpoint_nan = 1, nearest_na = 0, nearest_nan = 1, @@ -1567,8 +1561,8 @@ test_that("hash + reinterpret", { hash_values1 = unname(unlist(df$select(pl$col(c("Sepal.Width", "Species"))$unique()$hash()$implode())$to_list())) hash_values2 = unname(unlist(df$select(pl$col(c("Sepal.Width", "Species"))$unique()$hash(1, 2, 3, 4)$implode())$to_list())) hash_values3 = unname((df$select(pl$col(c("Sepal.Width", "Species"))$unique()$hash(1, 2, 3, 4)$implode()$cast(pl$List(pl$String)))$to_list())) - expect_true(!any(duplicated(hash_values1))) - expect_true(!any(sapply(hash_values3, \(x) any(duplicated(x))))) + expect_false(anyDuplicated(hash_values1) > 0) + expect_false(any(sapply(hash_values3, \(x) anyDuplicated(x) > 0))) # In current r-polars + py+polars setting seeds does not change the hash # CONTRIBUTE POLARS, py-polars now also has this behavior. Could be a bug. @@ -1664,7 +1658,7 @@ test_that("Expr_rolling_", { pl$col("a")$rolling_var(window_size = 2)$alias("var"), pl$col("a")$rolling_median(window_size = 2)$alias("median"), pl$col("a")$rolling_quantile( - quantile = .33, window_size = 2, interpolation = "linear" + quantile = 0.33, window_size = 2, interpolation = "linear" )$alias("quantile_linear") )$to_data_frame(), expected @@ -1708,7 +1702,7 @@ test_that("Expr_rolling_*_by", { pl$col("a")$rolling_var_by("date", window_size = "2d")$alias("var"), pl$col("a")$rolling_median_by("date", window_size = "2d")$alias("median"), pl$col("a")$rolling_quantile_by( - quantile = .33, "date", window_size = "2d", interpolation = "linear" + quantile = 0.33, "date", window_size = "2d", interpolation = "linear" )$alias("quantile_linear") )$to_data_frame(), expected @@ -1756,7 +1750,7 @@ test_that("Expr_rolling_*_by: arg 'min_periods'", { pl$col("a")$rolling_var_by("date", window_size = "2d", min_periods = 2)$alias("var"), pl$col("a")$rolling_median_by("date", window_size = "2d", min_periods = 2)$alias("median"), pl$col("a")$rolling_quantile_by( - quantile = .33, "date", window_size = "2d", min_periods = 2, interpolation = "linear" + quantile = 0.33, "date", window_size = "2d", min_periods = 2, interpolation = "linear" )$alias("quantile_linear") )$to_data_frame(), expected @@ -1795,7 +1789,7 @@ test_that("Expr_rolling_*_by: arg 'closed'", { pl$col("a")$rolling_var_by("date", window_size = "2d", closed = "left")$alias("var"), pl$col("a")$rolling_median_by("date", window_size = "2d", closed = "left")$alias("median"), pl$col("a")$rolling_quantile_by( - quantile = .33, "date", window_size = "2d", closed = "left", interpolation = "linear" + quantile = 0.33, "date", window_size = "2d", closed = "left", interpolation = "linear" )$alias("quantile_linear") )$to_data_frame(), expected @@ -1955,9 +1949,9 @@ test_that("skew", { )$to_list(), list( a_skew = R_skewness(l$a), - a_skew_bias_F = R_skewness(l$a, bias = F), + a_skew_bias_F = R_skewness(l$a, bias = FALSE), b_skew = R_skewness(l$b, na.rm = TRUE), - b_skew_bias_F = R_skewness(l$b, bias = F, na.rm = TRUE) + b_skew_bias_F = R_skewness(l$b, bias = FALSE, na.rm = TRUE) ) ) }) @@ -2013,9 +2007,9 @@ test_that("kurtosis", { # pl$col("a")$kurtosis(fisher = FALSE, bias=FALSE)$alias("kurt_FF") )$to_list(), list2( - kurt_TT = R_kurtosis(l2$a, T, T), + kurt_TT = R_kurtosis(l2$a, TRUE, TRUE), # kurt_TF = R_kurtosis(l2$a,T,F), - kurt_FT = R_kurtosis(l2$a, F, T) + kurt_FT = R_kurtosis(l2$a, FALSE, TRUE) # kurt_FF = R_kurtosis(l2$a,F,F) ) ) @@ -2255,9 +2249,9 @@ test_that("ewm_", { pl$col("a")$ewm_mean(com = 1)$alias("com1"), pl$col("a")$ewm_mean(span = 2)$alias("span2"), pl$col("a")$ewm_mean(half_life = 2)$alias("hl2"), - pl$col("a")$ewm_mean(alpha = .5)$alias("a.5"), + pl$col("a")$ewm_mean(alpha = 0.5)$alias("a.5"), pl$col("a")$ewm_mean(com = 1, adjust = FALSE)$alias("com1_noadjust"), - pl$col("a")$ewm_mean(alpha = .5, adjust = FALSE)$alias("a.5_noadjust"), + pl$col("a")$ewm_mean(alpha = 0.5, adjust = FALSE)$alias("a.5_noadjust"), pl$col("a")$ewm_mean(half_life = 3, adjust = FALSE)$alias("hl2_noadjust"), pl$col("a")$ewm_mean(com = 1, min_periods = 4)$alias("com1_min_periods") ) @@ -2317,7 +2311,7 @@ test_that("rep", { expect_identical(pl$lit(c("a", "b"))$rep(5)$to_r(), rep(c("a", "b"), 5)) expect_identical(pl$lit((1:3) * 1)$rep(5)$to_r(), rep((1:3) * 1, 5)) expect_identical(pl$lit(c("a", "b"))$rep(5)$to_r(), rep(c("a", "b"), 5)) - expect_identical(pl$lit(c(T, T, F))$rep(2)$to_r(), rep(c(T, T, F), 2)) + expect_identical(pl$lit(c(TRUE, TRUE, FALSE))$rep(2)$to_r(), rep(c(TRUE, TRUE, FALSE), 2)) expect_grepl_error(pl$lit(1:4)$rep(-1)) expect_grepl_error(pl$lit(1:4)$rep(Inf)) }) @@ -2333,7 +2327,7 @@ test_that("to_r", { for (i in l) expect_identical(pl$lit(i)$to_r(), i) # NULL to NULL - expect_identical(pl$lit(NULL)$to_r(), NULL) + expect_null(pl$lit(NULL)$to_r()) }) @@ -2472,7 +2466,7 @@ test_that("shrink_dtype", { e = c(-112L, 2L, 129L), f = c("a", "b", "c"), g = c(0.1, 1.32, 0.12), - h = c(T, NA, F) + h = c(TRUE, NA, FALSE) )$with_columns(pl$col("b")$cast(pl$Int64) * 32L)$select(pl$all()$shrink_dtype()) expect_true(all(mapply( diff --git a/tests/testthat/test-expr_name.R b/tests/testthat/test-expr_name.R index a4f33114a..26d7e7adb 100644 --- a/tests/testthat/test-expr_name.R +++ b/tests/testthat/test-expr_name.R @@ -1,17 +1,11 @@ test_that("name to_lowercase", { df = pl$DataFrame(Var1 = 1, vAR2 = 2) - expect_equal( - names(df$select(pl$all()$name$to_lowercase())), - c("var1", "var2") - ) + expect_named(df$select(pl$all()$name$to_lowercase()), c("var1", "var2")) }) test_that("name to_uppercase", { df = pl$DataFrame(Var1 = 1, vAR2 = 2) - expect_equal( - names(df$select(pl$all()$name$to_uppercase())), - c("VAR1", "VAR2") - ) + expect_named(df$select(pl$all()$name$to_uppercase()), c("VAR1", "VAR2")) }) test_that("name keep", { diff --git a/tests/testthat/test-groupby.R b/tests/testthat/test-groupby.R index cf1ddf5da..c853152ea 100644 --- a/tests/testthat/test-groupby.R +++ b/tests/testthat/test-groupby.R @@ -80,7 +80,7 @@ test_that("quantile", { b = pl$DataFrame(mtcars)$group_by("cyl", maintain_order = FALSE)$max()$to_data_frame() expect_equal(a[order(a$cyl), ], b[order(b$cyl), ], ignore_attr = TRUE) - a = pl$DataFrame(mtcars)$group_by("cyl", maintain_order = FALSE)$quantile(.5, "midpoint")$to_data_frame() + a = pl$DataFrame(mtcars)$group_by("cyl", maintain_order = FALSE)$quantile(0.5, "midpoint")$to_data_frame() b = pl$DataFrame(mtcars)$group_by("cyl", maintain_order = FALSE)$median()$to_data_frame() expect_equal(a[order(a$cyl), ], b[order(b$cyl), ], ignore_attr = TRUE) }) diff --git a/tests/testthat/test-lazy.R b/tests/testthat/test-lazy.R index 85a441895..912ea601f 100644 --- a/tests/testthat/test-lazy.R +++ b/tests/testthat/test-lazy.R @@ -67,7 +67,7 @@ test_that("LazyFrame, custom schema", { FUN = "==" )) ) - expect_identical(names(df$schema), names(iris)) + expect_named(df$schema, names(iris)) # works fine if a variable is called "schema" expect_no_error( @@ -345,7 +345,7 @@ test_that("sort", { pl$DataFrame(mtcars)$lazy()$sort( by = list("cyl", pl$col("gear")), # mixed types which implements Into "disp", # ... args other unamed args Into - descending = c(T, T, F) # vector of same length as number of Expr's + descending = c(TRUE, TRUE, FALSE) # vector of same length as number of Expr's )$collect() ) @@ -383,9 +383,9 @@ test_that("sort", { # test raise rust-polars error for mismatch number of booleans ctx = pl$DataFrame(mtcars)$lazy()$ - sort(by = c("cyl", "mpg", "cyl"), descending = c(T, F))$collect() |> + sort(by = c("cyl", "mpg", "cyl"), descending = c(TRUE, FALSE))$collect() |> get_err_ctx() - expect_true(!is.null(ctx$PolarsError)) + expect_false(is.null(ctx$PolarsError)) # test bad arg ctx = pl$DataFrame(mtcars)$ diff --git a/tests/testthat/test-rbackground.R b/tests/testthat/test-rbackground.R index 95f2cc33a..f75dd3e63 100644 --- a/tests/testthat/test-rbackground.R +++ b/tests/testthat/test-rbackground.R @@ -28,7 +28,7 @@ test_that("Test using $map_batches() in background", { expect_equal(polars_options()$rpool_active, 0) compute = lf$select(pl$col("y")$map_batches(\(x) x * x, in_background = FALSE)) compute_bg = lf$select(pl$col("y")$map_batches(\(x) { - Sys.sleep(.3) + Sys.sleep(0.3) x * x }, in_background = TRUE)) res_ref = compute$collect()$to_data_frame() @@ -53,7 +53,7 @@ test_that("Test using $map_batches() in background", { { compute = lf$select(pl$col("y")$map_batches(\(x) x * x, in_background = FALSE)) compute_bg = lf$select(pl$col("y")$map_batches(\(x) { - Sys.sleep(.3) + Sys.sleep(0.3) x * x }, in_background = TRUE)) @@ -71,7 +71,7 @@ test_that("Test using $map_batches() in background", { invisible() # can ask if joined after exhausted - expect_equal(handle$is_finished(), NULL) + expect_null(handle$is_finished()) # gives correct err message expect_rpolarserr(handle$join(), "Handled") @@ -119,15 +119,15 @@ test_that("reduce cap and active while jobs in queue", { { l_expr = lapply(1:5, \(i) { pl$lit(i)$map_batches(\(x) { - Sys.sleep(.4) + Sys.sleep(0.4) -i }, in_background = TRUE)$alias(paste0("lit_", i)) }) lf = pl$LazyFrame()$select(l_expr) handle = lf$collect(collect_in_background = TRUE) - Sys.sleep(.2) + Sys.sleep(0.2) options(polars.rpool_cap = 2) - Sys.sleep(.1) + Sys.sleep(0.1) options(polars.rpool_cap = 1) df = handle$join() diff --git a/tests/testthat/test-series.R b/tests/testthat/test-series.R index 08db1004d..4f2f0c7b8 100644 --- a/tests/testthat/test-series.R +++ b/tests/testthat/test-series.R @@ -250,13 +250,13 @@ test_that("n_chunks", { test_that("floor & ceil", { expect_identical( - as_polars_series(c(1.5, .5, -.5, NA_real_, NaN))$ + as_polars_series(c(1.5, 0.5, -0.5, NA_real_, NaN))$ floor()$ to_r(), c(1, 0, -1, NA_real_, NaN) ) expect_identical( - as_polars_series(c(1.5, .5, -.5, NA_real_, NaN))$ + as_polars_series(c(1.5, 0.5, -0.5, NA_real_, NaN))$ ceil()$ to_r(), c(2, 1, 0, NA_real_, NaN) @@ -528,7 +528,7 @@ test_that("to_series", { l = list(a = 1:3, b = c("a", "b", "c")) expect_identical(pl$DataFrame(l)$to_series(0)$to_r(), l$a) expect_identical(pl$DataFrame(l)$to_series(1)$to_r(), l$b) - expect_identical(pl$DataFrame(l)$to_series(2), NULL) + expect_null(pl$DataFrame(l)$to_series(2)) }) test_that("internal method get_fmt and to_fmt_char", { diff --git a/tests/testthat/test-whenthen.R b/tests/testthat/test-whenthen.R index e9255b974..3a6b08e0e 100644 --- a/tests/testthat/test-whenthen.R +++ b/tests/testthat/test-whenthen.R @@ -12,10 +12,7 @@ test_that("When-class", { expect_true(grepl("When", capture.output(print(pl$when("a"))))) ctx = result(pl$when(complex(2)))$err$contexts() - expect_identical( - names(ctx), - c("BadArgument", "PlainErrorMessage", "BadValue", "When", "PolarsError") - ) + expect_named(ctx, c("BadArgument", "PlainErrorMessage", "BadValue", "When", "PolarsError")) expect_identical( ctx$BadArgument, "condition" @@ -30,10 +27,7 @@ test_that("Then-class", { expect_s3_class(pl$when(TRUE)$then(FALSE)$otherwise(NA), "RPolarsExpr") ctx = result(pl$when("a")$then(complex(2)))$err$contexts() - expect_identical( - names(ctx), - c("BadArgument", "PlainErrorMessage", "BadValue", "When", "PolarsError") - ) + expect_named(ctx, c("BadArgument", "PlainErrorMessage", "BadValue", "When", "PolarsError")) expect_identical( ctx$BadArgument, "statement"