R/compact.R

# DATA CLEANING: COMPACT
#' @include AllGenerics.R
NULL

## compact rows/columns ========================================================
#' @export
#' @rdname compact
#' @aliases compact,ANY-method
setMethod(
  f = "compact",
  signature = c(x = "ANY"),
  definition = function(x, margin = 1, na.rm = FALSE) {
    vide <- function(x) {
      if (is_numeric(x)) x == 0
      else if (is_logical(x)) !x
      else if (is_character(x)) x == ""
      else rep(FALSE, length(x))
    }
    discard(x, f = vide, margin = margin, all = TRUE, na.rm = na.rm)
  }
)

#' @export
#' @rdname compact
#' @aliases compact_cols,ANY-method
setMethod(
  f = "compact_cols",
  signature = c(x = "ANY"),
  definition = function(x, na.rm = FALSE) {
    compact(x, margin = 2, na.rm = na.rm)
  }
)

#' @export
#' @rdname compact
#' @aliases compact_rows,ANY-method
setMethod(
  f = "compact_rows",
  signature = c(x = "ANY"),
  definition = function(x, na.rm = FALSE) {
    compact(x, margin = 1, na.rm = na.rm)
  }
)

Try the arkhe package in your browser

Any scripts or data that you put into this service are public.

arkhe documentation built on Nov. 17, 2023, 5:09 p.m.