Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
8 changes: 4 additions & 4 deletions R/as.data.table.R
Original file line number Diff line number Diff line change
Expand Up @@ -89,10 +89,10 @@ as.data.table.array = function(x, keep.rownames=FALSE, key=NULL, sorted=TRUE, va
stopf("as.data.table.array method should only be called for arrays with 3+ dimensions; use the matrix method for 2-dimensional arrays")
if (!is.character(value.name) || length(value.name)!=1L || is.na(value.name) || !nzchar(value.name))
stopf("Argument 'value.name' must be scalar character, non-NA and at least one character")
if (!is.logical(sorted) || length(sorted)!=1L || is.na(sorted))
stopf("Argument 'sorted' must be scalar logical and non-NA")
if (!is.logical(na.rm) || length(na.rm)!=1L || is.na(na.rm))
stopf("Argument 'na.rm' must be scalar logical and non-NA")
if (!isTRUEorFALSE(sorted))
stopf("'%s' must be TRUE or FALSE", "sorted")
if (!isTRUEorFALSE(na.rm))
stopf("'%s' must be TRUE or FALSE", "na.rm")
if (!missing(sorted) && !is.null(key))
stopf("Please provide either 'key' or 'sorted', but not both.")

Expand Down
16 changes: 8 additions & 8 deletions R/data.table.R
Original file line number Diff line number Diff line change
Expand Up @@ -244,7 +244,7 @@ replace_dot_alias = function(e) {
if ((isTRUE(which)||is.na(which)) && !missing(j)) stopf("which==%s (meaning return row numbers) but j is also supplied. Either you need row numbers or the result of j, but only one type of result can be returned.", which)
if (is.null(nomatch) && is.na(which)) stopf("which=NA with nomatch=0|NULL would always return an empty vector. Please change or remove either which or nomatch.")
if (!with && missing(j)) stopf("j must be provided when with=FALSE")
if (!missing(by) && !isTRUEorFALSE(showProgress)) stopf("%s must be TRUE or FALSE", "showProgress")
if (!missing(by) && !isTRUEorFALSE(showProgress)) stopf("'%s' must be TRUE or FALSE", "showProgress")
irows = NULL # Meaning all rows. We avoid creating 1:nrow(x) for efficiency.
notjoin = FALSE
rightcols = leftcols = integer()
Expand Down Expand Up @@ -1509,8 +1509,8 @@ replace_dot_alias = function(e) {
###########################################################################

o__ = integer()
if (".N" %chin% ansvars) stopf("The column '.N' can't be grouped because it conflicts with the special .N variable. Try setnames(DT,'.N','N') first.")
if (".I" %chin% ansvars) stopf("The column '.I' can't be grouped because it conflicts with the special .I variable. Try setnames(DT,'.I','I') first.")
if (".N" %chin% ansvars) stopf("The column '.%1$s' can't be grouped because it conflicts with the special .%1$s variable. Try setnames(DT,'.%1$s','%1$s') first.", "N")
if (".I" %chin% ansvars) stopf("The column '.%1$s' can't be grouped because it conflicts with the special .%1$s variable. Try setnames(DT,'.%1$s','%1$s') first.", "I")
SDenv$.iSD = NULL # null.data.table()
SDenv$.xSD = NULL # null.data.table() - introducing for FR #2693 and Gabor's post on fixing for FAQ 2.8

Expand Down Expand Up @@ -2530,7 +2530,7 @@ Ops.data.table = function(e1, e2 = NULL)
}

split.data.table = function(x, f, drop = FALSE, by, sorted = FALSE, keep.by = TRUE, flatten = TRUE, ..., verbose = getOption("datatable.verbose")) {
if (!is.data.table(x)) internal_error("x argument to split.data.table must be a data.table") # nocov
if (!is.data.table(x)) internal_error("'%s' argument to split.data.table must be a data.table") # nocov
stopifnot(is.logical(drop), is.logical(sorted), is.logical(keep.by), is.logical(flatten))
# split data.frame way, using `f` and not `by` argument
if (!missing(f)) {
Expand Down Expand Up @@ -3110,10 +3110,10 @@ rowid = function(..., prefix=NULL) {

rowidv = function(x, cols=seq_along(x), prefix=NULL) {
if (!is.null(prefix) && (!is.character(prefix) || length(prefix) != 1L))
stopf("'prefix' must be NULL or a character vector of length 1.")
stopf("'prefix' must be NULL or a character vector of length 1")
if (is.atomic(x)) {
if (!missing(cols) && !is.null(cols))
stopf("x is a single vector, non-NULL 'cols' doesn't make sense.")
stopf("x is a single vector, non-NULL 'cols' doesn't make sense")
cols = 1L
x = as_list(x)
} else if (!length(cols)) {
Expand All @@ -3135,10 +3135,10 @@ rleid = function(..., prefix=NULL) {

rleidv = function(x, cols=seq_along(x), prefix=NULL) {
if (!is.null(prefix) && (!is.character(prefix) || length(prefix) != 1L))
stopf("'prefix' must be NULL or a character vector of length 1.")
stopf("'prefix' must be NULL or a character vector of length 1")
if (is.atomic(x)) {
if (!missing(cols) && !is.null(cols))
stopf("x is a single vector, non-NULL 'cols' doesn't make sense.")
stopf("x is a single vector, non-NULL 'cols' doesn't make sense")
cols = 1L
x = as_list(x)
} else if (!length(cols)) {
Expand Down
2 changes: 1 addition & 1 deletion R/duplicated.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ duplicated.data.table = function(x, incomparables=FALSE, fromLast=FALSE, by=seq_
.NotYetUsed("incomparables != FALSE")
}
if (nrow(x) == 0L || ncol(x) == 0L) return(logical(0L)) # fix for bug #28
if (is.na(fromLast) || !is.logical(fromLast)) stopf("'fromLast' must be TRUE or FALSE")
if (is.na(fromLast) || !is.logical(fromLast)) stopf("'%s' must be TRUE or FALSE", "fromLast")
if (!length(by)) by = NULL #4594
query = .duplicated.helper(x, by)

Expand Down
12 changes: 7 additions & 5 deletions R/fcast.R
Original file line number Diff line number Diff line change
Expand Up @@ -122,13 +122,15 @@ aggregate_funs = function(funs, vals, sep="_", ...) {
}

dcast.data.table = function(data, formula, fun.aggregate = NULL, sep = "_", ..., margins = NULL, subset = NULL, fill = NULL, drop = TRUE, value.var = guess(data), verbose = getOption("datatable.verbose"), value.var.in.dots = FALSE, value.var.in.LHSdots = value.var.in.dots, value.var.in.RHSdots = value.var.in.dots) {
if (!is.data.table(data)) stopf("'data' must be a data.table.")
if (!is.data.table(data)) stopf("'%s' must be a data.table", "data")
drop = as.logical(rep_len(drop, 2L))
if (anyNA(drop)) stopf("'drop' must be logical TRUE/FALSE")
if (anyNA(drop)) stopf("'drop' must be logical vector with no missing entries")
if (!isTRUEorFALSE(value.var.in.dots))
stopf("Argument 'value.var.in.dots' should be logical TRUE/FALSE")
if (!isTRUEorFALSE(value.var.in.LHSdots) || !isTRUEorFALSE(value.var.in.RHSdots))
stopf("Arguments 'value.var.in.LHSdots', 'value.var.in.RHSdots' should be logical TRUE/FALSE")
stopf("'%s' must be TRUE or FALSE", "value.var.in.dots")
if (!isTRUEorFALSE(value.var.in.LHSdots))
stopf("'%s' must be TRUE or FALSE", "value.var.in.LHSdots")
if (!isTRUEorFALSE(value.var.in.RHSdots))
stopf("'%s' must be TRUE or FALSE", "value.var.in.RHSdots")
# #2980 if explicitly providing fun.aggregate=length but not a value.var,
# just use the last column (as guess(data) would do) because length will be
# the same on all columns
Expand Down
2 changes: 1 addition & 1 deletion R/fmelt.R
Original file line number Diff line number Diff line change
Expand Up @@ -181,7 +181,7 @@ measurev = function(fun.list, sep="_", pattern, cols, multiple.keyword="value.na
melt.data.table = function(data, id.vars, measure.vars, variable.name = "variable",
value.name = "value", ..., na.rm = FALSE, variable.factor = TRUE, value.factor = FALSE,
verbose = getOption("datatable.verbose")) {
if (!is.data.table(data)) stopf("'data' must be a data.table")
if (!is.data.table(data)) stopf("'%s' must be a data.table", "data")
for(type.vars in c("id.vars","measure.vars")){
sub.lang <- substitute({
if (missing(VAR)) VAR=NULL
Expand Down
8 changes: 4 additions & 4 deletions R/foverlaps.R
Original file line number Diff line number Diff line change
Expand Up @@ -9,8 +9,8 @@ foverlaps = function(x, y, by.x=key(x) %||% key(y), by.y=key(y), maxgap=0L, mino
stopf("maxgap must be a non-negative integer value of length 1")
if (!length(minoverlap) || length(minoverlap) != 1L || is.na(minoverlap) || minoverlap < 1L)
stopf("minoverlap must be a positive integer value of length 1")
if (!length(which) || length(which) != 1L || is.na(which))
stopf("which must be a logical vector of length 1. Either TRUE/FALSE")
if (!isTRUEorFALSE(which))
stopf("'%s' must be TRUE or FALSE", "which")
if (!length(nomatch) || length(nomatch) != 1L || (!is.na(nomatch) && nomatch!=0L))
stopf("nomatch must either be NA or NULL")
type = match.arg(type)
Expand All @@ -33,9 +33,9 @@ foverlaps = function(x, y, by.x=key(x) %||% key(y), by.y=key(y), maxgap=0L, mino
by.y = names(y)[by.y]
}
if (!is.character(by.x))
stopf("A non-empty vector of column names or numbers is required for by.x")
stopf("A non-empty vector of column names or numbers is required for '%s'", "by.x")
if (!is.character(by.y))
stopf("A non-empty vector of column names or numbers is required for by.y")
stopf("A non-empty vector of column names or numbers is required for '%s'", "by.y")
if (!identical(by.y, key(y)[seq_along(by.y)]))
stopf("The first %d columns of y's key must be identical to the columns specified in by.y.", length(by.y))
if (anyNA(chmatch(by.x, names(x))))
Expand Down
2 changes: 1 addition & 1 deletion R/frank.R
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ frankv = function(x, cols=seq_along(x), order=1L, na.last=TRUE, ties.method=c("a
} else {
cols = colnamesInt(x, cols, check_dups=TRUE)
if (!length(cols))
stopf("x is a list, 'cols' can not be 0-length")
stopf("x is a list, 'cols' cannot be 0-length.")
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Suggested change
stopf("x is a list, 'cols' cannot be 0-length.")
stopf("x is a list, 'cols' cannot be 0-length")

since "most" error messages dont end with ., but NIT

}
# need to unlock for #4429
x = .shallow(x, cols, unlock = TRUE) # shallow copy even if list..
Expand Down
10 changes: 5 additions & 5 deletions R/frollapply.R
Original file line number Diff line number Diff line change
Expand Up @@ -133,15 +133,15 @@ frollapply = function(X, N, FUN, ..., by.column=TRUE, fill=NA, align=c("right","
stopf("'n' is deprecated in frollapply, use 'N' instead")
}
if (!isTRUEorFALSE(by.column))
stopf("'by.column' must be TRUE or FALSE")
stopf("'%s' must be TRUE or FALSE", "by.column")
if (!isTRUEorFALSE(adaptive))
stopf("'adaptive' must be TRUE or FALSE")
stopf("'%s' must be TRUE or FALSE", "adaptive")
if (!isTRUEorFALSE(partial))
stopf("'partial' must be TRUE or FALSE")
stopf("'%s' must be TRUE or FALSE", "partial")
if (!isTRUEorFALSE(give.names))
stopf("'give.names' must be TRUE or FALSE")
stopf("'%s' must be TRUE or FALSE", "give.names")
if (!isTRUEorFALSE(simplify) && !is.function(simplify))
stopf("'simplify' must be TRUE or FALSE or a function")
stopf("'%s' must be TRUE or FALSE or a function", "simplify")

align = match.arg(align)
FUN = match.fun(FUN)
Expand Down
6 changes: 3 additions & 3 deletions R/groupingsets.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ rollup = function(x, ...) {
rollup.data.table = function(x, j, by, .SDcols, id = FALSE, label = NULL, ...) {
# input data type basic validation
if (!is.data.table(x))
stopf("Argument 'x' must be a data.table object", class="dt_invalid_input_error")
stopf("'%s' must be a data.table", "x", class="dt_invalid_input_error")
if (!is.character(by))
stopf("Argument 'by' must be a character vector of column names used in grouping.")
if (!is.logical(id))
Expand All @@ -22,7 +22,7 @@ cube = function(x, ...) {
cube.data.table = function(x, j, by, .SDcols, id = FALSE, label = NULL, ...) {
# input data type basic validation
if (!is.data.table(x))
stopf("Argument 'x' must be a data.table object", class="dt_invalid_input_error")
stopf("'%s' must be a data.table", "x", class="dt_invalid_input_error")
if (!is.character(by))
stopf("Argument 'by' must be a character vector of column names used in grouping.")
if (!is.logical(id))
Expand All @@ -44,7 +44,7 @@ groupingsets = function(x, ...) {
groupingsets.data.table = function(x, j, by, sets, .SDcols, id = FALSE, jj, label = NULL, enclos = parent.frame(), ...) {
# input data type basic validation
if (!is.data.table(x))
stopf("Argument 'x' must be a data.table object")
stopf("'%s' must be a data.table", "x")
if (ncol(x) < 1L)
stopf("Argument 'x' is a 0-column data.table; no measure to apply grouping over.")
if (anyDuplicated(names(x)) > 0L)
Expand Down
4 changes: 2 additions & 2 deletions R/helpers.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,9 @@
# convert char to factor retaining order #4837
fctr = function(x, levels=unique(x), ..., sort=FALSE, rev=FALSE) {
if (!isTRUEorFALSE(sort))
stopf("argument 'sort' must be TRUE or FALSE")
stopf("'%s' must be TRUE or FALSE", "sort")
if (!isTRUEorFALSE(rev))
stopf("argument 'rev' must be TRUE or FALSE")
stopf("'%s' must be TRUE or FALSE", "rev")
if (sort) levels = sort(levels)
if (rev) levels = frev(levels)
factor(x, levels=levels, ...)
Expand Down
8 changes: 4 additions & 4 deletions R/merge.R
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
merge.data.table = function(x, y, by = NULL, by.x = NULL, by.y = NULL, all = FALSE, all.x = all,
all.y = all, sort = TRUE, suffixes = c(".x", ".y"), no.dups = TRUE, allow.cartesian=getOption("datatable.allow.cartesian"), incomparables=NULL, ...) {
if (!sort %in% c(TRUE, FALSE))
stopf("Argument 'sort' should be logical TRUE/FALSE")
if (!no.dups %in% c(TRUE, FALSE))
stopf("Argument 'no.dups' should be logical TRUE/FALSE")
if (!isTRUEorFALSE(sort))
stopf("'%s' must be TRUE or FALSE", "sort")
if (!isTRUEorFALSE(no.dups))
stopf("'%s' must be TRUE or FALSE", "no.dups")
class_x = class(x)
if (!is.data.table(y)) {
y = as.data.table(y)
Expand Down
4 changes: 2 additions & 2 deletions R/setkey.R
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ setkeyv = function(x, cols, verbose=getOption("datatable.verbose"), physical=TRU
on.exit(options(oldverbose))
}
if (!is.data.table(x)) stopf("x is not a data.table")
if (!is.character(cols)) stopf("cols is not a character vector. Please see further information in ?setkey.")
if (!is.character(cols)) stopf("cols is not a character vector. Please see further information in ?%s.", "setkey")
if (physical && .Call(C_islocked, x)) stopf("Setting a physical key on .SD is reserved for possible future use; to modify the original data's order by group. Try setindex() instead. Or, set*(copy(.SD)) as a (slow) last resort.")
if (!length(cols)) {
warningf("cols is a character vector of zero length. Removed the key, but use NULL instead, or wrap with suppressWarnings() to avoid this warning.")
Expand Down Expand Up @@ -257,7 +257,7 @@ setorderv = function(x, cols = colnames(x), order=1L, na.last=FALSE)
if (!is.data.frame(x)) stopf("x must be a data.frame or data.table")
na.last = as.logical(na.last)
if (is.na(na.last) || !length(na.last)) stopf('na.last must be logical TRUE/FALSE')
if (!is.character(cols)) stopf("cols is not a character vector. Please see further information in ?setorder.")
if (!is.character(cols)) stopf("cols is not a character vector. Please see further information in ?%s.", "setorder")
if (!length(cols)) {
warningf("cols is a character vector of zero length. Use NULL instead, or wrap with suppressWarnings() to avoid this warning.")
return(x)
Expand Down
4 changes: 2 additions & 2 deletions inst/tests/froll.Rraw
Original file line number Diff line number Diff line change
Expand Up @@ -423,9 +423,9 @@ test(6000.118, frollmean(1:5, as.factor("a")), error="'n' must be an integer")
#### is.list(n)
test(6000.119, frollmean(1:5, list(1:5)), error="'n' must be an integer, list is accepted for adaptive TRUE")
#### adaptive=NA
test(6000.1192, frollmean(1:5, 2, adaptive=NA), error="adaptive must be TRUE or FALSE")
test(6000.1192, frollmean(1:5, 2, adaptive=NA), error="'adaptive' must be TRUE or FALSE")
#### na.rm=NA
test(6000.1193, frollmean(1:5, 2, na.rm=NA), error="na.rm must be TRUE or FALSE")
test(6000.1193, frollmean(1:5, 2, na.rm=NA), error="'na.rm' must be TRUE or FALSE")
#### has.nf=1
test(6000.1194, frollmean(1:5, 2, has.nf=1), error="has.nf must be TRUE, FALSE or NA")
#### has.nf=FALSE na.rm=TRUE
Expand Down
2 changes: 1 addition & 1 deletion inst/tests/nafill.Rraw
Original file line number Diff line number Diff line change
Expand Up @@ -149,7 +149,7 @@ test(4.26, colnamesInt(dt, c(1, 4), skip_absent=TRUE), c(1L,0L))
test(4.27, colnamesInt(dt, c("a", NA), skip_absent=TRUE), c(1L,0L))
test(4.28, colnamesInt(dt, c(1L, 0L), skip_absent=TRUE), error="received non-existing column*.*0")
test(4.29, colnamesInt(dt, c(1, -5), skip_absent=TRUE), error="received non-existing column*.*-5")
test(4.30, colnamesInt(dt, c(1, 4), skip_absent=NULL), error="skip_absent must be TRUE or FALSE")
test(4.30, colnamesInt(dt, c(1, 4), skip_absent=NULL), error="'skip_absent' must be TRUE or FALSE")
test(4.31, colnamesInt(dt, c(1L, 1000L), skip_absent=TRUE), c(1L,0L))
cols=c(1L,100L)
test(4.32, colnamesInt(dt, cols, skip_absent=TRUE), c(1L, 0L))
Expand Down
Loading
Loading