Skip to content

Commit

Permalink
add name to exported generic methods
Browse files Browse the repository at this point in the history
  • Loading branch information
Sebastian Kopf committed Apr 25, 2014
1 parent fa59ae8 commit 9b615b0
Show file tree
Hide file tree
Showing 2 changed files with 7 additions and 1 deletion.
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -32,5 +32,6 @@ exportMethods(as.weighted_value)
exportMethods(fractionate)
exportMethods(label)
exportMethods(mass_balance)
exportMethods(name)
exportMethods(shift_reference)
exportMethods(weight)
7 changes: 6 additions & 1 deletion R/show.R
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,13 @@ ratio_name <- function(text1, text2, spacer = "", top = "", bottom = "") {

#' Get the name of an isotopic data object
#' @export
#' @method name
setGeneric("name", function(object) standardGeneric("name"))

#' @export
#' @method name
setMethod("name", "ANY", function(object) stop("the name() function is not defined for objects of type ", class(object)))

setMethod("name", "Isoval", function(object) object@isoname)
setMethod("name", "Ratio", function(object) ratio_name("R", "", spacer = " ", object@isoname, object@major))
setMethod("name", "Abundance", function(object) ratio_name("F", object@isoname))
Expand All @@ -56,7 +62,6 @@ setMethod("name", "Epsilon", function(object) {
setMethod("name", "Delta", function(object) paste("δ", object@isoname, sep = ""))

#' Get the units of an isotope data object
#' @export
setGeneric("unit", function(object) standardGeneric("unit"))
setMethod("unit", "Isoval", function(object) "")
setMethod("unit", "Epsilon", function(object) if(object@permil) "‰" else "")
Expand Down

0 comments on commit 9b615b0

Please sign in to comment.