Skip to content

Commit

Permalink
allow inverting a filter for rows
Browse files Browse the repository at this point in the history
  • Loading branch information
EhrmannS committed Jul 2, 2024
1 parent babb0fa commit e1a7dc7
Show file tree
Hide file tree
Showing 6 changed files with 31 additions and 9 deletions.
12 changes: 11 additions & 1 deletion R/helpers.R
Original file line number Diff line number Diff line change
Expand Up @@ -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"){

Expand Down
2 changes: 1 addition & 1 deletion R/schema.R
Original file line number Diff line number Diff line change
Expand Up @@ -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.")
}
}
Expand Down
9 changes: 6 additions & 3 deletions R/setFilter.R
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand All @@ -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 ----
Expand All @@ -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)){
Expand All @@ -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)
Expand Down
4 changes: 2 additions & 2 deletions R/setFormat.R
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down
11 changes: 10 additions & 1 deletion man/setFilter.Rd

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

2 changes: 1 addition & 1 deletion man/setFormat.Rd

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

0 comments on commit e1a7dc7

Please sign in to comment.