Search code examples
rr-packageroxygen2r-s3

"no applicable method" for S3 generic despite existence of default method


This is tricky because this problem only happens in the context of a package -- everything works as expected when defined in the global namespace.

I've defined an S3 generic called coerce_na_range(), which has two methods, coerce_na_range.factor() and coerce_na_range.default(). coerce_na_range() is exported, but the two methods aren't. (The purpose of the function is to replace numbers encoded as character or factor labels with NA within a given range.)

When defined in the global namespace, if I pass a character vector to coerce_na_range(), it dispatches it to coerce_na_range.default() and works as expected:

vec <- c("green", "yellow", "-9", "red", "-1")
coerce_na_range(vec)
# [1] "green"  "yellow" NA       "red"    NA   

However, if I instead load the package in a fresh session, it seemingly ignores the default method:

library(lighthouse)

vec <- c("green", "yellow", "-9", "red", "-1")
coerce_na_range(vec)
# Error in UseMethod("coerce_na_range") : 
#  no applicable method for 'coerce_na_range' applied to an object of class "character"

I don't think the problem is that the methods aren't exported? e.g., tidyr:::full_seq.Date(), etc., aren't exported, and tidyr::full_seq() obviously works.

The package is hosted at https://github.com/ccsarapas/lighthouse. The code for coerce_na_range(), its methods, and a few functions they depend on, is:

#' Suppress NA warning when coercing to numeric
#'
#' Coerces `x` to numeric. If `x` cannot be coerced, returns `NA` and suppresses
#' coercion warning.
#'
#' @export
try_numeric <- function(x) {
  if (is.factor(x)) {
    warning(
      "`x` is a factor and will be converted based on factor codes, not factor labels."
    )
  }
  withCallingHandlers(
    warning = function(w) {
      if (conditionMessage(w) == "NAs introduced by coercion") {
        rlang::cnd_muffle(w)
      }
    },
    as.numeric(x)
  )
}

#' @rdname try_numeric
#'
#' @export
try.numeric <- function(x) try_numeric(x)

#' Generate NA values of appropriate type
#'
#' Returns compatible `NA` based on `x`. This is usually of the same type as `x`
#' (e.g., `NA_real_` if `x` is a double vector). If `x` is a factor, will
#' return `NA_character_` if `factor_as_character = TRUE` (the default) and
#' `NA_integer_` otherwise.
#'
#' @export
na_like <- function(x, factor_as_character = TRUE, match_length = FALSE) {
  stopifnot("`x` must be an atomic vector" = is.atomic(x))
  type_out <- if (factor_as_character && is.factor(x)) "character" else typeof(x)
  length_out <- if (match_length) length(x) else 1L
  rep(methods::as(NA, type_out), length_out)
}


#' Set NA values based on numbers stored as strings.
#'
#' Changes values coercible to numeric in range `range_min`:`range_max` to `NA`.
#' Useful for imported SPSS files.
#'
#' @export
coerce_na_range <- function(x, ...) UseMethod("coerce_na_range")
coerce_na_range.default <- function(x, range_min = -Inf, range_max = -1) {
  coerced <- try.numeric(x)
  dplyr::if_else(
    is.na(coerced) | (coerced < range_min) | (coerced > range_max),
    x,
    na_like(x)
  )
}
coerce_na_range.factor <- function(x, range_min = -Inf, range_max = -1) {
  lvls <- levels(x)
  coerced <- try.numeric(as.character(lvls))
  lvls <- lvls[is.na(coerced) | coerced < range_min | coerced > range_max]
  factor(x, levels = lvls)
}

Solution

  • Adding the @export tag before the generic.factor and running roxgenize should fix it:

    # [...]
    #' @exportS3Method coerce_na_range factor
    coerce_na_range.factor <- function(x, range_min = -Inf, range_max = -1) {
      lvls <- levels(x)
      coerced <- try.numeric(as.character(lvls))
      lvls <- lvls[is.na(coerced) | coerced < range_min | coerced > range_max]
      factor(x, levels = lvls)
    }
    

    Then in the console run: roxygen2::roxygenise()