Skip to content

Commit

Permalink
remove melt
Browse files Browse the repository at this point in the history
  • Loading branch information
eunseopkim committed Feb 3, 2024
1 parent 3df925a commit 1719bd6
Show file tree
Hide file tree
Showing 6 changed files with 15 additions and 10 deletions.
2 changes: 1 addition & 1 deletion R/el_pairwise.R
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,7 @@ el_pairwise <- function(formula, data, control = NULL, k = 1L, alpha = 0.05,
# General block design
gbd <-
list("model_matrix" = x, "incidence_matrix" = c, "trt" = levels(mf[[2L]]))
class(gbd) <- c("gbd", "melt")
class(gbd) <- c("gbd", "elgbd")
# Check whether all pairwise comparisons or comparisons to control
match.arg(control, gbd$trt)
if (is.null(control)) {
Expand Down
2 changes: 1 addition & 1 deletion R/el_test.R
Original file line number Diff line number Diff line change
Expand Up @@ -111,7 +111,7 @@ el_test <- function(formula, data, lhs, rhs = NULL, maxit = 1e+04,
# General block design
gbd <-
list("model_matrix" = x, "incidence_matrix" = c, "trt" = levels(mf[[2L]]))
class(gbd) <- c("gbd", "melt")
class(gbd) <- c("gbd", "elgbd")

# Test for lhs and rhs
if (is.null(rhs)) {
Expand Down
12 changes: 6 additions & 6 deletions R/elgbd-S3.R
Original file line number Diff line number Diff line change
@@ -1,19 +1,19 @@
#' @export
print.el_aov <- function(x, ...) {
stopifnot(inherits(x, "melt"))
stopifnot(inherits(x, "elgbd"))
cat("Call:\n")
dput(x$call, control = NULL)
cat("\nminimizer:\n")
cat(format(round(x$optim$par, 4), scientific = FALSE))
cat("\nMinimizer:\n")
cat(format(round(x$optim$par, 4L), scientific = FALSE))
cat("\n\n")
cat("statistic:\n")
cat(format(round(x$optim$n2logLR, 4), scientific = FALSE))
cat("Statistic:\n")
cat(format(round(x$optim$n2logLR, 4L), scientific = FALSE))
cat("\n\n")
}

#' @export
print.pairwise <- function(x, ...) {
stopifnot(inherits(x, "melt"))
stopifnot(inherits(x, "elgbd"))
cat("\n\tEmpirical Likelihood Multiple Tests\n\n")
if (is.null(x$control)) {
cat("All pairwise comparisons\n\n")
Expand Down
5 changes: 5 additions & 0 deletions cran-comments.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
## R CMD check results

0 errors | 0 warnings | 1 note

* This is a new release.
2 changes: 1 addition & 1 deletion src/gbd.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,6 @@ Rcpp::List ELtest(const Eigen::MatrixXd& x,
Rcpp::Named("n2logLR") = 2 * el.nlogLR,
Rcpp::Named("iterations") = el.iterations,
Rcpp::Named("convergence") = el.convergence);
result.attr("class") = "melt";
result.attr("class") = "elgbd";
return result;
}
2 changes: 1 addition & 1 deletion src/pairwise.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -115,6 +115,6 @@ Rcpp::List pairwise(const Eigen::MatrixXd& x,
result["level"] = level;
result["method"] = method;
result["B"] = bootstrap_statistics_pairwise.size();
result.attr("class") = Rcpp::CharacterVector({"pairwise", "melt"});
result.attr("class") = Rcpp::CharacterVector({"pairwise", "elgbd"});
return result;
}

0 comments on commit 1719bd6

Please sign in to comment.