Skip to content

Commit

Permalink
finish?
Browse files Browse the repository at this point in the history
  • Loading branch information
etiennebacher committed Dec 20, 2024
1 parent da5850e commit 5701e92
Show file tree
Hide file tree
Showing 37 changed files with 644 additions and 104 deletions.
34 changes: 19 additions & 15 deletions R/join.R
Original file line number Diff line number Diff line change
Expand Up @@ -46,6 +46,13 @@
#' * `"one-to-many"` expects each row in `y` to match at most 1 row in `x`.
#' * `"many-to-one"` expects each row in `x` matches at most 1 row in `y`.
#'
#' @section Unknown arguments:
#'
#' Arguments that are supported by the original implementation in the tidyverse
#' but are not listed above will throw a warning by default if they are
#' specified. To change this behavior to error instead, use
#' `options(tidypolars_unknown_args = "error")`.
#'
#' @export
#' @examplesIf require("dplyr", quietly = TRUE) && require("tidyr", quietly = TRUE)
#' test <- polars::pl$DataFrame(
Expand Down Expand Up @@ -108,9 +115,7 @@
left_join.RPolarsDataFrame <- function(x, y, by = NULL,
suffix = c(".x", ".y"), ...,
na_matches = "na", relationship = NULL) {
check_unsupported_arg("copy", ..., .action = "warn")
check_unsupported_arg("keep", ..., .action = "warn")
check_dots_empty_ignore(..., .ignore = c("copy", "keep"))
check_dots_empty_ignore(..., .unsupported = c("copy", "keep"))
join_(
x = x,
y = y,
Expand All @@ -127,9 +132,7 @@ left_join.RPolarsDataFrame <- function(x, y, by = NULL,
right_join.RPolarsDataFrame <- function(x, y, by = NULL,
suffix = c(".x", ".y"), ...,
na_matches = "na", relationship = NULL) {
check_unsupported_arg("copy", ..., .action = "warn")
check_unsupported_arg("keep", ..., .action = "warn")
check_dots_empty_ignore(..., .ignore = c("copy", "keep"))
check_dots_empty_ignore(..., .unsupported = c("copy", "keep"))
join_(
x = x,
y = y,
Expand All @@ -146,9 +149,7 @@ right_join.RPolarsDataFrame <- function(x, y, by = NULL,
full_join.RPolarsDataFrame <- function(x, y, by = NULL,
suffix = c(".x", ".y"), ...,
na_matches = "na", relationship = NULL) {
check_unsupported_arg("copy", ..., .action = "warn")
check_unsupported_arg("keep", ..., .action = "warn")
check_dots_empty_ignore(..., .ignore = c("copy", "keep"))
check_dots_empty_ignore(..., .unsupported = c("copy", "keep"))
join_(
x = x,
y = y,
Expand All @@ -165,9 +166,7 @@ full_join.RPolarsDataFrame <- function(x, y, by = NULL,
inner_join.RPolarsDataFrame <- function(x, y, by = NULL,
suffix = c(".x", ".y"), ...,
na_matches = "na", relationship = NULL) {
check_unsupported_arg("copy", ..., .action = "warn")
check_unsupported_arg("keep", ..., .action = "warn")
check_dots_empty_ignore(..., .ignore = c("copy", "keep"))
check_dots_empty_ignore(..., .unsupported = c("copy", "keep"))
join_(
x = x,
y = y,
Expand Down Expand Up @@ -205,6 +204,8 @@ inner_join.RPolarsLazyFrame <- inner_join.RPolarsDataFrame
#' @param x,y Two Polars Data/LazyFrames
#' @inheritParams left_join.RPolarsDataFrame
#'
#' @inheritSection left_join.RPolarsDataFrame Unknown arguments
#'
#' @export
#' @examplesIf require("dplyr", quietly = TRUE) && require("tidyr", quietly = TRUE)
#' test <- polars::pl$DataFrame(
Expand All @@ -229,7 +230,7 @@ inner_join.RPolarsLazyFrame <- inner_join.RPolarsDataFrame
#' # only keep the rows of `test` that don't have matching keys in `test2`
#' anti_join(test, test2, by = c("x", "y"))
semi_join.RPolarsDataFrame <- function(x, y, by = NULL, ..., na_matches = "na") {
check_dots_empty()
check_dots_empty_ignore(..., .unsupported = "copy")
join_(
x = x,
y = y,
Expand All @@ -245,7 +246,7 @@ semi_join.RPolarsDataFrame <- function(x, y, by = NULL, ..., na_matches = "na")
#' @export

anti_join.RPolarsDataFrame <- function(x, y, by = NULL, ..., na_matches = "na") {
check_dots_empty()
check_dots_empty_ignore(..., .unsupported = "copy")
join_(
x = x,
y = y,
Expand All @@ -272,6 +273,8 @@ anti_join.RPolarsLazyFrame <- anti_join.RPolarsDataFrame
#'
#' @inheritParams left_join.RPolarsDataFrame
#'
#' @inheritSection left_join.RPolarsDataFrame Unknown arguments
#'
#' @export
#' @examplesIf require("dplyr", quietly = TRUE) && require("tidyr", quietly = TRUE)
#' test <- polars::pl$DataFrame(
Expand All @@ -289,7 +292,8 @@ anti_join.RPolarsLazyFrame <- anti_join.RPolarsDataFrame
#' test2
#'
#' cross_join(test, test2)
cross_join.RPolarsDataFrame <- function(x, y, suffix = c(".x", ".y"), ...) {
cross_join.RPolarsDataFrame <- function(x, y, ..., suffix = c(".x", ".y")) {
check_dots_empty_ignore(..., .unsupported = "copy")
join_(
x = x,
y = y,
Expand Down
11 changes: 10 additions & 1 deletion R/pivot_longer.R
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,8 @@
#' data stored in cell values.
#' @inheritParams rlang::check_dots_empty0
#'
#' @inheritSection left_join.RPolarsDataFrame Unknown arguments
#'
#' @export
#' @examplesIf require("dplyr", quietly = TRUE) && require("tidyr", quietly = TRUE)
#' pl_relig_income <- polars::pl$DataFrame(tidyr::relig_income)
Expand All @@ -32,7 +34,14 @@
pivot_longer.RPolarsDataFrame <- function(data, cols, ..., names_to = "name",
names_prefix = NULL,
values_to = "value") {
check_dots_empty()
check_dots_empty_ignore(
...,
.unsupported = c(
"cols_vary", "names_sep", "names_pattern", "names_ptypes",
"names_transform", "names_repair", "values_drop_na", "values_ptypes",
"values_transform"
)
)
data_names <- names(data)
on <- tidyselect_named_arg(data, rlang::enquo(cols))
index <- data_names[!data_names %in% on]
Expand Down
10 changes: 9 additions & 1 deletion R/pivot_wider.R
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,8 @@
#' columns. For example, if you provide a character value to fill numeric
#' columns, then all these columns will be converted to character.
#'
#' @inheritSection left_join.RPolarsDataFrame Unknown arguments
#'
#' @export
#' @examplesIf require("dplyr", quietly = TRUE) && require("tidyr", quietly = TRUE)
#' pl_fish_encounters <- polars::pl$DataFrame(tidyr::fish_encounters)
Expand Down Expand Up @@ -71,7 +73,13 @@ pivot_wider.RPolarsDataFrame <- function(
names_sep = "_",
names_glue = NULL,
values_fill = NULL) {
check_dots_empty()
check_dots_empty_ignore(
...,
.unsupported = c(
"id_expand", "names_sort", "names_vary", "names_expand", "names_repair",
"values_fn", "unused_fn"
)
)
data_names <- names(data)
value_vars <- tidyselect_named_arg(data, rlang::enquo(values_from))
names_vars <- tidyselect_named_arg(data, rlang::enquo(names_from))
Expand Down
5 changes: 3 additions & 2 deletions R/slice.R
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,8 @@
#' is not maintained, use `group_by()` if you want more control over it.
#' @inheritParams rlang::check_dots_empty0
#'
#' @inheritSection left_join.RPolarsDataFrame Unknown arguments
#'
#' @export
#' @examplesIf require("dplyr", quietly = TRUE) && require("tidyr", quietly = TRUE)
#' pl_test <- polars::as_polars_df(iris)
Expand Down Expand Up @@ -81,8 +83,7 @@ slice_head.RPolarsLazyFrame <- slice_head.RPolarsDataFrame
#' @export

slice_sample.RPolarsDataFrame <- function(.data, ..., n = NULL, prop = NULL, by = NULL, replace = FALSE) {
check_unsupported_arg("weight_by", ...)
check_dots_empty0(...)
check_dots_empty_ignore(..., .unsupported = "weight_by")

grps <- get_grps(.data, rlang::enquo(by), env = rlang::current_env())
mo <- attributes(.data)$maintain_grp_order
Expand Down
49 changes: 32 additions & 17 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -111,30 +111,45 @@ select_by_name_or_position <- function(expr, name, position, default, env) {
}
}

check_unsupported_arg <- function(.arg_name, ..., .action = "error") {
check_dots_empty_ignore <- function(..., .unsupported = NULL) {
dots <- enquos(...)
if (.arg_name %in% names(dots)) {
if (.action == "error") {
fn <- abort
rlang_action <- getOption("tidypolars_unknown_args", "warn")
unsupported_dots <- names(dots[.unsupported])
unsupported_dots <- unsupported_dots[!is.na(unsupported_dots)]

if (length(unsupported_dots) > 0) {
if (length(unsupported_dots) == 1) {
msg <- paste0("Argument `", unsupported_dots, "` is not supported by tidypolars.")
} else {
fn <- warn
msg <- paste(
"Arguments",
toString(paste0("`", unsupported_dots, "`")),
"are not supported by tidypolars."
)
}
do.call(
fn,
list(
paste0("Argument `", .arg_name, "` is not supported by tidypolars yet."),
if (rlang_action == "warn") {
warn(msg, call = caller_env())
} else if (rlang_action == "error") {
abort(
c(
msg,
"i" = "Use `options(tidypolars_unknown_args = \"warn\")` to warn when this happens instead of throwing an error."
),
call = caller_env()
)
)
}
}
}

check_dots_empty_ignore <- function(..., .ignore = NULL) {
dots <- list2(...)
for (i in seq_along(.ignore)) {
dots[[.ignore[i]]] <- NULL
for (i in .unsupported) {
dots[[i]] <- NULL
}

if (length(dots) > 0) {
abort("`...` must be empty.", call = caller_env())
abort(
c(
"`...` must be empty."
# "i" = paste("Unknown args:", dots))
),
call = caller_env()
)
}
}
17 changes: 13 additions & 4 deletions man/cross_join.RPolarsDataFrame.Rd

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

6 changes: 2 additions & 4 deletions man/group_vars.RPolarsDataFrame.Rd

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

9 changes: 9 additions & 0 deletions man/left_join.RPolarsDataFrame.Rd

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

9 changes: 9 additions & 0 deletions man/pivot_longer.RPolarsDataFrame.Rd

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

9 changes: 9 additions & 0 deletions man/pivot_wider.RPolarsDataFrame.Rd

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

9 changes: 9 additions & 0 deletions man/semi_join.RPolarsDataFrame.Rd

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

1 change: 0 additions & 1 deletion man/sink_csv.Rd

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

1 change: 0 additions & 1 deletion man/sink_parquet.Rd

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

9 changes: 9 additions & 0 deletions man/slice_tail.RPolarsDataFrame.Rd

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

10 changes: 10 additions & 0 deletions tests/testthat/_snaps/collect.md
Original file line number Diff line number Diff line change
Expand Up @@ -6,3 +6,13 @@
Error in `UseMethod()`:
! no applicable method for 'collect' applied to an object of class "RPolarsDataFrame"

# error on unknown args

Code
collect(pl_iris, foo = TRUE)
Condition
Error in `collect()`:
! `...` must be empty.
x Problematic argument:
* foo = TRUE

Loading

0 comments on commit 5701e92

Please sign in to comment.