Search code examples
rdocumentationr-s4roxygen2

How to document S4 methods that rely on classes from external packages?


I'm struggeling to find the correct way to document S4 methods that act on classes in external packages. Disclaimer: I'm quite new to S4 and OOP in general.

Suppose I have the following generic with roxygen comments:

#' Converting an object to a polygon data.frame
#'
#' @param object some description
#' @param selection some description
#'
#' @details This function tries to parameterise polygons.
#' @return A data.frame
#' @export
#' @examples
#' x <- S4Vectors::Rle(rep(1:5, each = 5))
#' to_poly(x)
setGeneric("to_poly", function(object, selection) standardGeneric("to_poly"))

And I've written the following method for the class Rle from the S4Vectors package (on bioconductor). These Rle's do similar things to what base::rle does, but has some additional convenient functions.

#' @rdname to_poly
setMethod(
  "to_poly",
  signature(object = "Rle", selection = "missing"),
  function(object) {
    requireNamespace("S4Vectors", quietly = TRUE)
    df <- data.frame(
      x = c(1, base::rbind(start(object), end(object)), length(object)),
      y = c(0, base::rbind(runValue(object), runValue(object)), 0)
    )
    df[!duplicated(df),]
  }
)

Now the reason that I use requireNamespace instead of adding #' importFrom S4Vectors Rle at the top, is that I don't want people to be forced to download S4Vectors when installing the package. I still want this method to exists, alongside similar methods for base::rle.

However, when I run devtools::document(roclets = c('rd', 'collate', 'namespace')) to use roxygen2 to document the above, I get the following warning:

in method for ‘to_poly’ with signature ‘object="Rle",selection="missing"’: no definition for class “Rle”

So clearly, this seems to be a suboptimal way of documenting since the #' importFrom S4Vectors Rle method works fine, but this then becomes a dependency I'm not keen on (I think).

What would be the optimal way to document this method, that doesn't let roxygen2 throw errors and doesn't force users to install S4Vectors?


Solution

  • I'll answer my own question for when anyone in the future might face the same issue.

    I don't know if this is the best way of doing it, but I found some hints in ?signature-class.

    Briefly, next to a slot to hold the class name (.Data) and the argument names (names), the signature class object also has a package slot. This particular slot is not a formal argument of signature() and neither is it of the constructor new("signature", functionDef, ...).

    The way around this is to manually build a structure and pass the structure to as(..., "signature"). The documentation doesn't give any errors, the functions still work and I don't need the package names in the import field.

    setMethod(
      "to_poly",
      as(structure(.Data = c("Rle", "missing"),
                   names = c("object", "selection"),
                   package = c("S4Vectors", "")),
         "signature"),
      function(object) {
        requireNamespace("S4Vectors", quietly = TRUE)
        df <- data.frame(
          x = c(1, base::rbind(start(object), end(object)), length(object)),
          y = c(0, base::rbind(runValue(object), runValue(object)), 0)
        )
        df[!duplicated(df),]
      }
    )