R/varExpl.R

Defines functions varExpl.prcurve varExpl.cca varExpl.default varExpl

Documented in varExpl varExpl.cca varExpl.default varExpl.prcurve

varExpl <- function(object, ...)
    UseMethod("varExpl")

varExpl.default <- function(object, ...) {
    stop("No default method for 'varExpl()'")
}

varExpl.cca <- function(object, axes = 1L, cumulative = FALSE,
                        pcent = FALSE, ...) {
    if(is.null(object$CCA))
        res <- object$CA$eig[axes]
    else
        res <- object$CCA$eig[axes]
    res <- res / object$tot.chi
    if(cumulative)
        res <- cumsum(res)
    if(pcent)
        res <- 100 * res
    res
}

varExpl.prcurve <- function(object, pcent = FALSE, ...) {
    res <- 1 - object$dist / object$totalDist
    if(pcent)
        res <- 100 * res
    names(res) <- "PrC"
    res
}

Try the analogue package in your browser

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

analogue documentation built on June 21, 2021, 1:08 a.m.