https://github.com/cran/coin
Raw File
Tip revision: 4f813a5f635d62178763b975c32f68fce30097c5 authored by Torsten Hothorn on 27 September 2023, 16:10:02 UTC
version 1.4-3
Tip revision: 4f813a5
ContrastTest.R
### contrast test
contrast_test <- function(object, ...) UseMethod("contrast_test")

contrast_test.formula <- function(formula, data = list(), subset = NULL,
    weights = NULL, ...) {

    ft("contrast_test", "IndependenceProblem", formula, data, subset, weights,
       frame = parent.frame(), ...)
}

contrast_test.IndependenceProblem <- function(object,
    cmatrix, distribution = c("asymptotic", "approximate"), ...) {

    if (!(ncol(object@x) == 1 && is.factor(object@x[[1]])))
        stop(sQuote("object@x"), " is not univariate or a factor")

    if  (!is.matrix(cmatrix) || nrow(cmatrix) != nlevels(object@x[[1]]))
        stop(sQuote("cmatrix"), " is not a matrix with ",
             nlevels(object@x), " rows")

    if (is.null(colnames(cmatrix)))
        colnames(cmatrix) <- paste0("C", 1:ncol(cmatrix))

    args <- setup_args(
        teststat = "maximum",
        distribution = check_distribution_arg(
            distribution, values = c("asymptotic", "approximate")
        ),
        xtrafo = function(data)
            trafo(data) %*% cmatrix
    )

    object <- do.call(independence_test, c(object = object, args))

    object@method <- "General Contrast Test"

    object
}
back to top