R/AllClasses.R

# CLASSES DEFINITION AND INITIALIZATION
NULL

# Register S3 classes ==========================================================
setOldClass("dist")

## Index vectors
## (for 'i' in x[i], x[i, ], x[, i], etc.)
setClassUnion("index", members = c("logical", "numeric", "character"))

# CompositionMatrix ============================================================
#' Numeric Matrix
#'
#' S4 classes that represent a \eqn{m \times p}{m x p} numeric matrix.
#' @slot .Data A \eqn{m \times p}{m x p} `numeric` [`matrix`].
#' @note
#'  This class inherits from [`matrix`].
#' @author N. Frerebeau
#' @family classes
#' @docType class
#' @aliases NumericMatrix-class
#' @keywords internal
.NumericMatrix <- setClass(
  Class = "NumericMatrix",
  contains = "matrix"
)

#' Logical Matrix
#'
#' S4 classes that represent a \eqn{m \times p}{m x p} logical matrix.
#' @slot .Data A \eqn{m \times p}{m x p} `logical` [`matrix`].
#' @note
#'  This class inherits from [`matrix`].
#' @author N. Frerebeau
#' @family classes
#' @docType class
#' @aliases LogicalMatrix-class
#' @keywords internal
.LogicalMatrix <- setClass(
  Class = "LogicalMatrix",
  contains = "matrix"
)

#' Compositional Matrix
#'
#' An S4 class to represent compositional data.
#' @slot totals A [`numeric`] vector to store the absolute row sums (before
#'  the closure of the compositions).
#' @slot groups A [`factor`] vector to store the group names.
#' @section Coerce:
#'  In the code snippets below, `x` is a `CompositionMatrix` object.
#'  \describe{
#'   \item{`as.data.frame(x)`}{Coerces to a [`data.frame`].}
#'  }
#' @section Subset:
#'  In the code snippets below, `x` is a `CompositionMatrix` object.
#'  \describe{
#'   \item{`x[i, j]`}{Extract parts of a matrix (see [`[`][subset]).}
#'  }
#' @note
#'  This class inherits from [`matrix`].
#' @seealso [as_composition()]
#' @example inst/examples/ex-matrix.R
#' @author N. Frerebeau
#' @family classes
#' @docType class
#' @aliases CompositionMatrix-class
#' @keywords internal
.CompositionMatrix <- setClass(
  Class = "CompositionMatrix",
  slots = c(
    totals = "numeric",
    groups = "factor"
  ),
  contains = c("NumericMatrix")
)

# Transformations ==============================================================
#' Log-Ratio Matrix
#'
#' S4 classes to represent log-ratio data transformations.
#' @slot totals A [`numeric`] vector to store the absolute row sums (before
#'  the closure of the compositions).
#' @slot groups A [`factor`] vector to store the group names.
#' @slot parts A [`character`] vector to store the original part names.
#' @slot ratio A [`character`] vector to store the ratio names.
#' @slot order An [`integer`] vector to store the original ordering of the
#'  columns.
#' @slot base A [`numeric`] matrix to store the basis of the transformation.
#' @slot weights A [`numeric`] vector to store the weights assigned to the
#'  respective log-ratios.
#' @section Coerce:
#'  In the code snippets below, `x` is a `LogRatio` object.
#'  \describe{
#'   \item{`as.data.frame(x)`}{Coerces to a [`data.frame`].}
#'  }
#' @note
#'  These classes inherit from [`matrix`].
#' @seealso [transform_lr()], [transform_clr()], [transform_alr()],
#'  [transform_ilr()], [transform_plr()]
#' @author N. Frerebeau
#' @family classes
#' @docType class
#' @aliases LogRatio-class
#' @keywords internal
.LogRatio <- setClass(
  Class = "LogRatio",
  slots = c(
    totals = "numeric",
    groups = "factor",

    parts = "character",
    ratio = "character",
    order = "integer",
    base = "matrix",
    weights = "numeric"
  ),
  contains = "NumericMatrix"
)

#' @rdname LogRatio-class
#' @aliases LR-class
.LR <- setClass(
  Class = "LR",
  contains = "LogRatio"
)

#' @rdname LogRatio-class
#' @aliases CLR-class
.CLR <- setClass(
  Class = "CLR",
  contains = "LogRatio"
)

#' @rdname LogRatio-class
#' @aliases ALR-class
.ALR <- setClass(
  Class = "ALR",
  contains = "LogRatio"
)

#' @rdname LogRatio-class
#' @aliases ILR-class
.ILR <- setClass(
  Class = "ILR",
  contains = "LogRatio"
)

#' @rdname LogRatio-class
#' @aliases PLR-class
.PLR <- setClass(
  Class = "PLR",
  contains = "ILR"
)

# OutlierIndex =================================================================
#' Outliers
#'
#' An S4 class to store the result of outlier detection.
#' @slot samples A [`character`] vector to store the sample identifiers.
#' @slot groups A [`factor`] vector to store the group names.
#' @slot standard A [`numeric`] matrix giving the standard squared Mahalanobis
#'  distances.
#' @slot robust A [`numeric`] matrix giving the robust squared Mahalanobis
#'  distances.
#' @slot limit A [`numeric`] value giving the cut-off value used for outliers
#'  detection (quantile of the Chi-squared distribution).
#' @slot dof A (non-negative) [`numeric`] value giving the degrees of freedom.
#' @section Coerce:
#'  In the code snippets below, `x` is an `OutlierIndex` object.
#'  \describe{
#'   \item{`as.data.frame(x)`}{Coerces to a [`data.frame`].}
#'  }
#' @author N. Frerebeau
#' @family classes
#' @docType class
#' @aliases OutlierIndex-class
#' @keywords internal
.OutlierIndex <- setClass(
  Class = "OutlierIndex",
  slots = c(
    samples = "character",
    groups = "factor",
    standard = "numeric",
    robust = "numeric",
    limit = "numeric",
    dof = "integer"
  )
)

Try the nexus package in your browser

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

nexus documentation built on Sept. 11, 2024, 6:43 p.m.