diff --git a/R/helpers.R b/R/helpers.R index f57100a..05d855c 100644 --- a/R/helpers.R +++ b/R/helpers.R @@ -791,8 +791,18 @@ for(i in seq_along(row)){ if(names(row)[i] == "position"){ + inVal <- 1 + outVal <- 0 + + if(any(names(row) %in% "invert")){ + if(row$invert){ + inVal <- 0 + outVal <- 1 + } + } + rows <- input %>% - mutate(it = if_else(row_number() %in% row[[i]], 1, 0)) %>% + mutate(it = if_else(row_number() %in% row[[i]], inVal, outVal)) %>% pull(it) } else if(names(row)[i] == "find"){ diff --git a/R/schema.R b/R/schema.R index aad046c..f7954c3 100755 --- a/R/schema.R +++ b/R/schema.R @@ -162,7 +162,7 @@ setValidity(Class = "schema", function(object){ errors <- c(errors, "'names(schema$format)' must be a permutation of set {header,del,dec,na,flags}") } if(!is.null(object@format$header)){ - if(!is.integer(object@format$header)){ + if(!is_integerish(object@format$header)){ errors <- c(errors, "'schema$format$header' must must have a integer value.") } } diff --git a/R/setFilter.R b/R/setFilter.R index c5b730f..9f2a952 100644 --- a/R/setFilter.R +++ b/R/setFilter.R @@ -7,6 +7,8 @@ #' @param rows [\code{integerish(.)}]\cr rows that are mentioned here are kept. #' @param columns [\code{integerish(.)}]\cr columns that are mentioned here are #' kept. +#' @param invert [\code{logical(1)}]\cr whether or not to invert the specified +#' columns or rows. #' @param operator [\code{function(1)}]\cr \code{\link[base]{Logic}} operators #' by which the current filter should be combined with the directly preceeding #' filter; hence this argument is not used in case no other filter was defined @@ -27,10 +29,10 @@ #' #' reorganise(schema = schema, input = input) #' @family functions to describe table arrangement -#' @importFrom checkmate assertClass testIntegerish testClass +#' @importFrom checkmate assertClass testIntegerish testClass assertLogical #' @export -setFilter <- function(schema = NULL, rows = NULL, columns = NULL, +setFilter <- function(schema = NULL, rows = NULL, columns = NULL, invert = FALSE, operator = NULL){ # assertions ---- @@ -43,6 +45,7 @@ setFilter <- function(schema = NULL, rows = NULL, columns = NULL, assert(colInt, colList) if(rowList) assertSubset(x = names(rows), choices = c("find")) if(colList) assertSubset(x = names(columns), choices = c("find")) + assertLogical(x = invert, any.missing = FALSE) # update schema ---- if(is.null(schema)){ @@ -55,7 +58,7 @@ setFilter <- function(schema = NULL, rows = NULL, columns = NULL, if(!is.null(rows)){ if(!is.list(rows)){ - rows <- list(position = rows) + rows <- list(position = rows, invert = invert) } if(!is.null(schema@filter$row)){ rows <- c(operator = operator, rows) diff --git a/R/setFormat.R b/R/setFormat.R index 3ef222a..8ae8322 100644 --- a/R/setFormat.R +++ b/R/setFormat.R @@ -33,12 +33,12 @@ #' @importFrom dplyr bind_rows #' @export -setFormat <- function(schema = NULL, header = 0L, decimal = NULL, +setFormat <- function(schema = NULL, header = 0, decimal = NULL, thousand = NULL, na_values = NULL, flags = NULL){ # assertions ---- assertClass(x = schema, classes = "schema", null.ok = TRUE) - assertIntegerish(x = header, len = 1, lower = 0L, any.missing = FALSE) + assertIntegerish(x = header, len = 1, lower = 0, any.missing = FALSE) assertCharacter(x = decimal, len = 1, any.missing = FALSE, null.ok = TRUE) assertCharacter(x = thousand, len = 1, any.missing = FALSE, null.ok = TRUE) assertCharacter(x = na_values, any.missing = FALSE, null.ok = TRUE) diff --git a/man/setFilter.Rd b/man/setFilter.Rd index 065e70a..c8fcc48 100644 --- a/man/setFilter.Rd +++ b/man/setFilter.Rd @@ -4,7 +4,13 @@ \alias{setFilter} \title{Set filters} \usage{ -setFilter(schema = NULL, rows = NULL, columns = NULL, operator = NULL) +setFilter( + schema = NULL, + rows = NULL, + columns = NULL, + invert = FALSE, + operator = NULL +) } \arguments{ \item{schema}{[\code{schema(1)}]\cr In case this information is added to an @@ -16,6 +22,9 @@ information).} \item{columns}{[\code{integerish(.)}]\cr columns that are mentioned here are kept.} +\item{invert}{[\code{logical(1)}]\cr whether or not to invert the specified +columns or rows.} + \item{operator}{[\code{function(1)}]\cr \code{\link[base]{Logic}} operators by which the current filter should be combined with the directly preceeding filter; hence this argument is not used in case no other filter was defined diff --git a/man/setFormat.Rd b/man/setFormat.Rd index f8ba549..68e52ab 100644 --- a/man/setFormat.Rd +++ b/man/setFormat.Rd @@ -6,7 +6,7 @@ \usage{ setFormat( schema = NULL, - header = 0L, + header = 0, decimal = NULL, thousand = NULL, na_values = NULL,