Skip to content

Commit

Permalink
avoid loaded term
Browse files Browse the repository at this point in the history
  • Loading branch information
IndrajeetPatil committed Oct 6, 2023
1 parent ec6a9ce commit b42571d
Show file tree
Hide file tree
Showing 11 changed files with 12 additions and 12 deletions.
4 changes: 2 additions & 2 deletions R/data_match.R
Original file line number Diff line number Diff line change
Expand Up @@ -117,7 +117,7 @@ data_match <- function(x, to, match = "and", return_indices = FALSE, drop_na = T
"or"
)

# sanity check
# validation check
shared_columns <- intersect(colnames(x), colnames(to))
if (is.null(shared_columns) || length(shared_columns) == 0) {
insight::format_error(
Expand Down Expand Up @@ -207,7 +207,7 @@ data_filter.data.frame <- function(x, ...) {
symbol <- dots[[i]]
# evaluate, we may have a variable with filter expression
eval_symbol <- .dynEval(symbol, ifnotfound = NULL)
# sanity check: is variable named like a function?
# validation check: is variable named like a function?
if (is.function(eval_symbol)) {
eval_symbol <- .dynGet(symbol, ifnotfound = NULL)
}
Expand Down
2 changes: 1 addition & 1 deletion R/data_partition.R
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,7 @@ data_partition <- function(data,
verbose = TRUE,
training_proportion = proportion,
...) {
# Sanity checks
# validation checks
data <- .coerce_to_dataframe(data)

if (sum(proportion) > 1) {
Expand Down
2 changes: 1 addition & 1 deletion R/labels_to_levels.R
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ labels_to_levels.data.frame <- function(x,
regex = FALSE,
verbose = TRUE,
...) {
# sanity check, return as is for complete factor
# validation check, return as is for complete factor
if (all(vapply(x, is.factor, TRUE))) {
return(x)
}
Expand Down
2 changes: 1 addition & 1 deletion R/means_by_group.R
Original file line number Diff line number Diff line change
Expand Up @@ -60,7 +60,7 @@ means_by_group.numeric <- function(x,
weights = NULL,
digits = NULL,
...) {
# sanity check for arguments
# validation check for arguments

# "group" must be provided
if (is.null(group)) {
Expand Down
2 changes: 1 addition & 1 deletion R/to_factor.R
Original file line number Diff line number Diff line change
Expand Up @@ -89,7 +89,7 @@ to_factor.data.frame <- function(x,
regex = FALSE,
verbose = TRUE,
...) {
# sanity check, return as is for complete factor
# validation check, return as is for complete factor
if (all(vapply(x, is.factor, FUN.VALUE = logical(1L)))) {
return(x)
}
Expand Down
2 changes: 1 addition & 1 deletion R/to_numeric.R
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,7 @@ to_numeric.data.frame <- function(x,
regex = FALSE,
verbose = TRUE,
...) {
# sanity check, return as is for complete numeric
# validation check, return as is for complete numeric
if (all(vapply(x, is.numeric, FUN.VALUE = logical(1L)))) {
return(x)
}
Expand Down
2 changes: 1 addition & 1 deletion R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -210,7 +210,7 @@
nchar_open <- nchar(open)
nchar_close <- nchar(close)

# Sanity checks
# validation checks
stopifnot(exprs = {
is.character(fmt)
length(fmt) == 1L
Expand Down
2 changes: 1 addition & 1 deletion R/utils_labels.R
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@
# check positions of matching values and levels
levels_in_labs <- stats::na.omit(match(value_labels, levels(x)))
labs_in_levels <- stats::na.omit(match(levels(x), value_labels))
# sanity check - if labelled values and levels don't match
# validation check - if labelled values and levels don't match
if (!length(levels_in_labs) || !length(labs_in_levels)) {
if (verbose) {
insight::format_alert(
Expand Down
2 changes: 1 addition & 1 deletion R/utils_standardize_center.R
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@
vals <- x[valid_x]
}

# Sanity checks
# validation checks
check <- .check_standardize_numeric(x, name = NULL, verbose = verbose, reference = reference, center = center)

if (is.factor(vals) || is.character(vals)) {
Expand Down
2 changes: 1 addition & 1 deletion R/weighted_mean_median_sd_mad.R
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ weighted_median <- function(x, weights = NULL, remove_na = TRUE, verbose = TRUE,
weights <- complete$weights[order]

rw <- cumsum(weights) / sum(weights)
# sanity check
# validation check
if (all(is.na(rw))) {
return(NA_real_)
}
Expand Down
2 changes: 1 addition & 1 deletion tests/testthat/test-data_partition.R
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ test_that("data_partition works as expected", {

expect_snapshot(data_partition(letters, seed = 123))

# sanity checks
# validation checks

expect_warning(
data_partition(iris, 0.7, row_id = "Species"),
Expand Down

0 comments on commit b42571d

Please sign in to comment.