Skip to content

Commit

Permalink
update documentation for S4 classes
Browse files Browse the repository at this point in the history
proper documentation in Roxygen 4.0 style
  • Loading branch information
Sebastian Kopf committed Apr 25, 2014
1 parent d73a86f commit 7ffb710
Show file tree
Hide file tree
Showing 4 changed files with 72 additions and 1 deletion.
12 changes: 12 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -21,3 +21,15 @@ export(is.ratio)
export(ratio)
export(register_standard)
export(use_permil)
exportMethods(as.abundance)
exportMethods(as.alpha)
exportMethods(as.delta)
exportMethods(as.epsilon)
exportMethods(as.ratio)
exportMethods(as.value)
exportMethods(as.weight)
exportMethods(as.weighted_value)
exportMethods(fractionate)
exportMethods(mass_balance)
exportMethods(shift_reference)
exportMethods(weight)
23 changes: 22 additions & 1 deletion R/attribs.R
Original file line number Diff line number Diff line change
Expand Up @@ -87,14 +87,20 @@ setMethod("update_iso", "Intensity", function(obj, attribs) {
#' @param iso - object to get weight or add weight
#' @param weight - vector of weight values, has to be a single value or the same length
#' as the data stored in the isotope value object.
#' @export
#' @note This can also be achieved when first initializing (or updating) an object
#' via calls to \code{\link{ratio}}, \code{\link{abundance}}, \code{\link{delta}}, etc.
#' @examples
#' r <- ratio(0.2)
#' r <- weight(r, 10)
#' print(as.weight(r)) # returns 10
#' @method weight
#' @export
setGeneric("weight", function(iso, weight) standardGeneric("weight"))

#' @method weight
#' @export
setMethod("weight", "ANY", function(iso, weight) stop("weight not defined for objects of class ", class(iso)))

setMethod("weight", signature("Isoval", "numeric"), function(iso, weight) {
iso <- update_iso(iso, list(weight = weight))
validObject(iso)
Expand All @@ -115,8 +121,13 @@ setMethod("weight", signature("Isoval", "numeric"), function(iso, weight) {
#' frame but keep the isotope values intact, use \code{\link{as.data.frame}} instead.
#' @seealso \code{\link{as.data.frame}}, \code{\link[base]{as.data.frame}} (base method)
#' @family data type conversions
#' @method as.value
#' @export
setGeneric("as.value", function(iso) standardGeneric("as.value"))

#' @method as.value
#' @export
setMethod("as.value", "ANY", function(iso) stop("as.value not defined for objects of class ", class(iso)))
setMethod("as.value", "Isoval", function(iso) [email protected])
setMethod("as.value", "Isosys", function(iso) {
data.frame(lapply(iso,
Expand All @@ -136,8 +147,13 @@ setMethod("as.value", "Isosys", function(iso) {
#' objects replaced with their weight values.
#' @seealso \code{\link{as.data.frame}}, \code{\link[base]{as.data.frame}} (base method)
#' @family data type conversions
#' @method as.weight
#' @export
setGeneric("as.weight", function(iso) standardGeneric("as.weight"))

#' @method as.weight
#' @export
setMethod("as.weight", "ANY", function(iso) stop("as.weight not defined for objects of class ", class(iso)))
setMethod("as.weight", "Isoval", function(iso) iso@weight)
setMethod("as.weight", "Isosys", function(iso) {
data.frame(lapply(iso,
Expand All @@ -157,8 +173,13 @@ setMethod("as.weight", "Isosys", function(iso) {
#' objects replaced with their weighted values.
#' @seealso \code{\link{as.data.frame}}, \code{\link[base]{as.data.frame}} (base method)
#' @family data type conversions
#' @method as.weighted_value
#' @export
setGeneric("as.weighted_value", function(iso) standardGeneric("as.weighted_value"))

#' @method as.weighted_value
#' @export
setMethod("as.weighted_value", "ANY", function(iso) stop("as.weighted_value not defined for objects of class ", class(iso)))
setMethod("as.weighted_value", "Isoval", function(iso) as.weight(iso) * as.value(iso))
setMethod("as.weighted_value", "Isosys", function(iso) {
data.frame(lapply(iso,
Expand Down
20 changes: 20 additions & 0 deletions R/conversion.R
Original file line number Diff line number Diff line change
Expand Up @@ -61,8 +61,12 @@ conversion_error <- function(from, to) {
#' @return isotope \code{\link{ratio}} object if iso can be converted to a \code{\link{ratio}}, an error otherwise
#' @rdname as.ratio
#' @family data type conversions
#' @method as.ratio
#' @export
setGeneric("as.ratio", function(iso) standardGeneric("as.ratio"))

#' @method as.ratio
#' @export
setMethod("as.ratio", "ANY", function(iso) conversion_error(iso, "isotope ratio"))
setMethod("as.ratio", "Ratio", function(iso) iso)
setMethod("as.ratio", "Ratios", function(iso) iso)
Expand Down Expand Up @@ -143,8 +147,12 @@ setMethod("as.ratio", "Delta", function(iso) {
#' @return isotope \code{\link{abundance}} object if iso can be converted to a \code{\link{abundance}}, an error otherwise
#' @rdname as.abundance
#' @family data type conversions
#' @method as.abundance
#' @export
setGeneric("as.abundance", function(iso) standardGeneric("as.abundance"))

#' @method as.abundance
#' @export
setMethod("as.abundance", "ANY", function(iso) conversion_error(iso, "isotope abundance"))
setMethod("as.abundance", "Abundance", function(iso) iso)
setMethod("as.abundance", "Abundances", function(iso) iso)
Expand Down Expand Up @@ -187,8 +195,12 @@ setMethod("as.abundance", "Delta", function(iso) {
#' @return isotope \code{\link{alpha}} object if iso can be converted to a \code{\link{alpha}}, an error otherwise
#' @rdname as.alpha
#' @family data type conversions
#' @method as.alpha
#' @export
setGeneric("as.alpha", function(iso1, iso2) standardGeneric("as.alpha"))

#' @method as.alpha
#' @export
setMethod("as.alpha", "ANY", function(iso1, iso2) conversion_error(iso1, "alpha value (ratio of ratios)"))

# two ratios to alpha (uses the arithmetic shorthand)
Expand Down Expand Up @@ -217,8 +229,12 @@ setMethod("as.alpha", signature("Epsilon", "Epsilon"), function(iso1, iso2) {
#' @return isotope \code{\link{epsilon}} object if iso can be converted to an \code{\link{epsilon}}, an error otherwise
#' @rdname as.epsilon
#' @family data type conversions
#' @method as.epsilon
#' @export
setGeneric("as.epsilon", function(iso, permil = use_permil()) standardGeneric("as.epsilon"))

#' @method as.epsilon
#' @export
setMethod("as.epsilon", "ANY", function(iso, permil = use_permil()) conversion_error(iso, "epsilon value"))
setMethod("as.epsilon", "Isosys", function(iso, permil = use_permil())
convert_isosys(iso, "Epsilons", function(df) lapply(as.data.frame(df), function(i) as.epsilon(i, permil = permil))))
Expand Down Expand Up @@ -255,8 +271,12 @@ setMethod("as.epsilon", signature(iso = "Epsilon"), function(iso, permil = use_p
#' @return isotope \code{\link{delta}} object if iso can be converted to a \code{\link{delta}}, an error otherwise
#' @rdname as.delta
#' @family data type conversions
#' @method as.delta
#' @export
setGeneric("as.delta", function(iso, ref_ratio, permil = use_permil()) standardGeneric("as.delta"))

#' @method as.delta
#' @export
setMethod("as.delta", "ANY", function(iso, ref_ratio, permil = use_permil()) conversion_error(iso, "delta value"))
setMethod("as.delta", signature(iso = "Isosys", ref_ratio = "missing"), function(iso, ref_ratio, permil = use_permil()) {
convert_isosys(iso, "Deltas", function(df) lapply(as.data.frame(df), function(i) as.delta(i, permil = permil)))
Expand Down
18 changes: 18 additions & 0 deletions R/operations.R
Original file line number Diff line number Diff line change
Expand Up @@ -11,8 +11,14 @@ NULL
#' @param exact - whether to calculate mass balance of delta values exactly (default FALSE),
#' use exact_mass_balance to set this paramter globally
#' @return weighted abundance or delta value object that represents the combination of the parameters
#' @method mass_balance
#' @export
setGeneric("mass_balance", function(iso, iso2, ..., exact = exact_mass_balance()) standardGeneric("mass_balance"))

#' @method mass_balance
#' @export
setMethod("mass_balance", "ANY", function(iso, iso2, ..., exact = exact_mass_balance()) stop("mass_balance not defined for objects of class ", class(iso), ", ", class(iso2)))

setMethod("mass_balance", signature("Abundance", "Abundance"), function(iso, iso2, ..., exact = exact_mass_balance()) {
# consider implementing a performance optimized version for many additions
all <- c(list(iso2), list(...))
Expand Down Expand Up @@ -47,8 +53,14 @@ setMethod("mass_balance", signature("Deltas", "Deltas"), function(iso, iso2, ...
#' implemented with an \code{\link{arithmetic}} shorthand. All calculatinos are
#' only permissible if the fractionation factors and isotope values have matching
#' attributes.
#' @method fractionate
#' @export
setGeneric("fractionate", function(frac, iso) standardGeneric("fractionate"))

#' @method fractionate
#' @export
setMethod("fractionate", "ANY", function(frac, iso) stop("fractionate not defined for objects of class ", class(frac), ", ", class(iso)))

setMethod("fractionate", signature("Alpha", "Ratio"), function(frac, iso) {
iso_attribs_check(frac, iso, include = c("isoname", "major"), text = "cannot generate a ratio from a fractionation factor and a ratio")
if (frac@compound2 != iso@compound)
Expand Down Expand Up @@ -90,8 +102,14 @@ setMethod("fractionate", signature("Epsilon", "ANY"), function(frac, iso) fracti
#' also implemented with an \code{\link{arithmetic}} shorthand. All calculatinos are
#' only permissible if the fractionation factors and isotope values have matching
#' attributes.
#' @method shift_reference
#' @export
setGeneric("shift_reference", function(iso, ref) standardGeneric("shift_reference"))

#' @method shift_reference
#' @export
setMethod("shift_reference", "ANY", function(iso, ref) stop("shift_reference not defined for objects of class ", class(iso), ", ", class(ref)))

setMethod("shift_reference", signature("Delta", "Delta"), function(iso, ref) {
a <- as.alpha(iso) # convert value to shift to an alpha value
fractionate(a, ref) # "fractionte" new reference with this (will automatically make sure everything is correct)
Expand Down

0 comments on commit 7ffb710

Please sign in to comment.