Skip to content

Commit

Permalink
ANOPA v0.1.3
Browse files Browse the repository at this point in the history
  • Loading branch information
dcousin3 committed Mar 19, 2024
1 parent 6d1c99f commit ac53156
Show file tree
Hide file tree
Showing 75 changed files with 1,009 additions and 2,800 deletions.
4 changes: 2 additions & 2 deletions DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
Package: ANOPA
Type: Package
Title: Analyses of Proportions using Anscombe Transform
Version: 0.1.2
Date: 2024-03-18
Version: 0.1.3
Date: 2024-03-19
Authors@R: c(
person("Denis", "Cousineau", email = "[email protected]",
role = c("aut", "ctb", "cre")),
Expand Down
4 changes: 4 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
# ANOPA 0.1.3 (March 2023)

* removed some cats and a few `

# ANOPA 0.1.2 (March 2023)

* added \donttest{} to speed tests;
Expand Down
9 changes: 4 additions & 5 deletions R/ANOPA-anopa.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,8 @@
#'
#' @md
#'
#' @description The function `anopa()` performs an ANOPA for designs with up to 4 factors
#' according to the `ANOPA` framework. See \insertCite{lc23;textual}{ANOPA} for more.
#' @description The function 'anopa()' performs an ANOPA for designs with up to 4 factors
#' according to the 'ANOPA' framework. See \insertCite{lc23;textual}{ANOPA} for more.
#'
#'
#' @param formula A formula with the factors on the left-hand side. See below for writing the
Expand Down Expand Up @@ -371,10 +371,9 @@ getAfterNested <- function(frm) {
v1 <- f[[3]]
} else {
if (f[[3]][[1]] == "*") {
# cat("case frm2: ", f[[3]][[2]], "\n")
v1 <- f[[3]][[2]]
} else {
cat("ANOPA::internal (-1): Case Inexistant: ", "\n")
stop("ANOPA::internal(-1): Case non-existant: That should never happen")
}
}
return( paste(v1) )
Expand Down Expand Up @@ -402,7 +401,7 @@ getAroundNested <- function(frm) {
v2 <- f[[2]][[length(f[[2]])]]
}
} else {
cat("ANOPA::internal (-2): Case Inexistant: ", "\n")
stop("ANOPA::internal (-2): Case non-existant: That should never happen")
}
}
return( c( paste(v1), paste(v2)) )
Expand Down
53 changes: 27 additions & 26 deletions R/ANOPA-contrastProportions.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,8 @@
#'
#' @md
#'
#' @description The function `contrastProportions()` performs contrasts analyses
#' on proportion data after an omnibus analysis has been obtained with `anopa()`
#' @description The function 'contrastProportions()' performs contrasts analyses
#' on proportion data after an omnibus analysis has been obtained with 'anopa()'
#' according to the ANOPA framework. See \insertCite{lc23;textual}{ANOPA} for more.
#'
#' @param w An ANOPA object obtained from `anopa()` or `emProportions()`;
Expand Down Expand Up @@ -42,31 +42,31 @@
#' contrast1 = c(1, 1, -2)/2,
#' contrast2 = c(1, -1, 0) )
#' )
#' #summary(cw)
#' summary(cw)
#'
#' # Example using the Arrington et al. (2002) data, a 3 x 4 x 2 design involving
#' # Location (3 levels), Trophism (4 levels) and Diel (2 levels).
#' ArringtonEtAl2002
#'
#' # performs the omnibus analysis first (mandatory):
#' w <- anopa( {s;n} ~ Location * Trophism * Diel, ArringtonEtAl2002)
#' corrected(w)
#'
#' # execute the simple effect of Trophism for every levels of Diel and Location
#' e <- emProportions(w, ~ Trophism | Diel * Location)
#' #summary(e)
#'
#' # For each of these sub-cells, contrast the four tropisms, first
#' # by comparing the first two levels to the third (contrast1), second
#' # by comparing the first to the second level (contrast2), and finally by
#' # by comparing the first three to the last (contrast3) :
#' #f <- contrastProportions( e, list(
#' # contrast1 = c(1, 1, -2, 0)/2,
#' # contrast2 = c(1, -1, 0, 0),
#' # contrast3 = c(1, 1, 1, -3)/3
#' # )
#' # )
#' #summary(f)
# # Example using the Arrington et al. (2002) data, a 3 x 4 x 2 design involving
# # Location (3 levels), Trophism (4 levels) and Diel (2 levels).
# ArringtonEtAl2002
#
# # performs the omnibus analysis first (mandatory):
# w <- anopa( {s;n} ~ Location * Trophism * Diel, ArringtonEtAl2002)
# corrected(w)
#
# # execute the simple effect of Trophism for every levels of Diel and Location
# e <- emProportions(w, ~ Trophism | Diel * Location)
# summary(e)
#
# # For each of these sub-cells, contrast the four tropisms, first
# # by comparing the first two levels to the third (contrast1), second
# # by comparing the first to the second level (contrast2), and finally by
# # by comparing the first three to the last (contrast3) :
# f <- contrastProportions( e, list(
# contrast1 = c(1, 1, -2, 0)/2,
# contrast2 = c(1, -1, 0, 0),
# contrast3 = c(1, 1, 1, -3)/3
# )
# )
# summary(f)
#'
#'
######################################################################################
Expand Down Expand Up @@ -95,6 +95,7 @@ contrastProportions <- function(
} else {
stop("ANOPA::oups(1): This part not yet done. Exiting...")
}
print(relevantlevels)
if (!(all(unlist(lapply(contrasts, length)) == relevantlevels )))
stop("ANOPA::error(33): The contrats lengths does not match the number of levels. Exiting...")

Expand Down
2 changes: 1 addition & 1 deletion R/ANOPA-convert.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@
#'
#' @md
#'
#' @description The functions `toWide()`, `toLong()`, and `toCompiled()`
#' @description The functions 'toWide()', 'toLong()', and 'toCompiled()'
#' converts the data into various formats.
#'
#' @usage toWide(w)
Expand Down
13 changes: 3 additions & 10 deletions R/ANOPA-emProportions.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,8 @@
#'
#' @md
#'
#' @description The function `emProportions()` performs a _simple effect_ analyses
#' of proportions after an omnibus analysis has been obtained with `anopa()`
#' @description The function 'emProportions()' performs a _simple effect_ analyses
#' of proportions after an omnibus analysis has been obtained with 'anopa()'
#' according to the ANOPA framework. Alternatively, it is also called an
#' _expected marginal_ analysis of proportions. See \insertCite{lc23b;textual}{ANOPA} for more.
#'
Expand Down Expand Up @@ -52,12 +52,8 @@
#'
#' # Let's execute the simple effect of Difficulty for every levels of Class
#' e <- emProportions(w, ~ Difficulty | Class )
#' #summary(e)
#' summary(e)
#'
#' # As a check, you can verify that the _F_s are decomposed additively
#' #sum(e$results[,1])
#' #w$results[3,1]+w$results[4,1]
#'
#'
#' # -- SECOND EXAMPLE --
#' # Example using the Arrington et al. (2002) data, a 3 x 4 x 2 design involving
Expand All @@ -84,9 +80,6 @@
#' e <- emProportions(w, ~ Trophism | Diel )
#' summary(e)
#'
#' # Again, as a check, you can verify that the $F$s are decomposed additively
#' #w$results[4,1]+w$results[7,1] # B + B:C
#' #sum(e$results[,1])
#'
#' # You can ask easier outputs with
#' corrected(w) # or summary(w) for the ANOPA table only
Expand Down
9 changes: 4 additions & 5 deletions R/ANOPA-functions.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,10 +5,10 @@
#'
#' @md
#'
#' @description The transformation functions `A()` performs the
#' @description The transformation functions 'A()' performs the
#' Anscombe transformation on a pair \{number of success; number
#' of trials\} = \{s; n\} (where the symbol ";" is to be read "over".
#' The function `varA()` returns the theoretical variance from
#' The function 'varA()' returns the theoretical variance from
#' the pair \{s; n\}. Both functions are central to the ANOPA
#' \insertCite{lc23}{ANOPA}. It was originally proposed by
#' \insertCite{z35}{ANOPA} and formalized by \insertCite{a48}{ANOPA}.
Expand Down Expand Up @@ -102,7 +102,6 @@ SE.Atrans <- function(v) {

# its variance...
var.Atrans <- function(v) {
print(length(v))
1 / (4*(length(v)+1/2))
}

Expand All @@ -126,8 +125,8 @@ CI.prop <- function(v, gamma = 0.95) {
n <- length(v)
cilen <- CI.Atrans(v, gamma)
# the difference adjustment is done herein.
ylo <- y - sqrt(2) * cilen
yhi <- y + sqrt(2) * cilen
ylo <- max( y - sqrt(2) * cilen, 0)
yhi <- min( y + sqrt(2) * cilen, pi/2)
# reverse arc-sin transformation
xlo <- (n+3/4)*(sin(ylo)^2) - 3/8
xhi <- (n+3/4)*(sin(yhi)^2) - 3/8
Expand Down
6 changes: 3 additions & 3 deletions R/ANOPA-logicals.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,9 +7,9 @@
##
## @md
##
## @description The functions `is.formula()`, `is.one.sided()`,
## `has.nested.terms()`,
## `has.cbind.terms()`, `in.formula()` and `sub.formulas()`
## @description The functions 'is.formula()', 'is.one.sided()',
## 'has.nested.terms()',
## 'has.cbind.terms()', 'in.formula()' and 'sub.formulas()'
## performs checks or extract sub-formulas from a given formula.
##s
## @usage is.formula(frm)
Expand Down
19 changes: 9 additions & 10 deletions R/ANOPA-methods.R
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@
#' @md
#'
#' @description
#' `explain()` provides a human-readable, exhaustive, description of
#' 'explain()' provides a human-readable, exhaustive, description of
#' the results. It also provides references to the key results.
#'
#' @usage explain(object, ...)
Expand All @@ -47,8 +47,8 @@ explain.default <- function(object, ...) { print(object) }
#'
#' @md
#'
#' @description `summarize()` provides the statistics table an ANOPAobject.
#' It is synonym of `summary()` (but as actions are verbs, I used a verb).
#' @description 'summarize()' provides the statistics table an ANOPAobject.
#' It is synonym of 'summary()' (but as actions are verbs, I used a verb).
#'
#' @param object an object to summarize
#' @param ... ignored
Expand All @@ -75,8 +75,7 @@ summary.ANOPAobject <- function(object, ...) {
#' @method print ANOPAobject
#' @export
print.ANOPAobject <- function(x, ...) {
cat("ANOPA completed. My first advise is to use anopaPlot() now. \n")
cat("Use summary() or summarize() to obtain the ANOPA table.\n")
ANOPAmessage("ANOPA completed! My first advise is to use anopaPlot() now. \nUse summary() or summarize() to obtain the ANOPA table.")
y <- unclass(x)
class(y) <- "list"
print(y, digits = 5)
Expand All @@ -98,7 +97,7 @@ print.ANOPAtable <- function(x, ...) {
#' @export
summarize.ANOPAobject <- function(object, ...) {
if (length(object$omnibus) == 1)
cat(object$omnibus)
print(object$omnibus)
else {
u <- object$omnibus
class(u) <- c("ANOPAtable", class(u))
Expand All @@ -123,7 +122,7 @@ explain.ANOPAobject <- function(object, ...) {
#' @md
#'
#' @description
#' `corrected()` provides an ANOPA table with only the corrected
#' 'corrected()' provides an ANOPA table with only the corrected
#' statistics.
#'
#' @usage corrected(object, ...)
Expand All @@ -140,7 +139,7 @@ corrected.default <- function(object, ...) { print(object) }
#' @export
corrected.ANOPAobject <- function(object, ...) {
if (length(object$omnibus) == 1)
cat(object$omnibus)
print(object$omnibus)
else {
u <- object$omnibus[,c(1,2,3,5,6,7)]
class(u) <- c("ANOPAtable", class(u))
Expand All @@ -154,7 +153,7 @@ corrected.ANOPAobject <- function(object, ...) {
#' @md
#'
#' @description
#' `uncorrected()` provides an ANOPA table with only the uncorrected
#' 'uncorrected()' provides an ANOPA table with only the uncorrected
#' statistics.
#'
#' @usage uncorrected(object, ...)
Expand All @@ -172,7 +171,7 @@ uncorrected.default <- function(object, ...) { print(object) }
#' @export
uncorrected.ANOPAobject <- function(object, ...) {
if (length(object$omnibus) == 1)
cat(object$omnibus)
print(object$omnibus)
else {
u <- object$omnibus[,c(1,2,3,4)]
class(u) <- c("ANOPAtable", class(u))
Expand Down
10 changes: 5 additions & 5 deletions R/ANOPA-package.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
#'
#' @md
#'
#' @description `ANOPA` is a library to perform proportion analyses.
#' @description 'ANOPA' is a library to perform proportion analyses.
#' It is based on the F statistics (first developed by Fisher).
#' This statistics is fully additive and can be decomposed in
#' main effects and interaction effects, in simple effects in the
Expand All @@ -16,8 +16,8 @@
#'
#' The data supplied to an ANOPA can be in three formats: (i) long format,
#' (ii) wide format, (iii) compiled format, or (iv) raw format. Check
#' the `anopa` commands for more precision (in what follow, we assume
#' the compiled format where the proportions are given in a column name `Freq`)
#' the 'anopa' commands for more precision (in what follow, we assume
#' the compiled format where the proportions are given in a column name 'Freq')
#'
#' The main function is
#'
Expand Down Expand Up @@ -56,7 +56,7 @@
#' }
#'
#' The functions uses the following options: \itemize{
#' \item{\code{ANOPA.feedback}} ((currently unused));
#' \item{\code{ANOPA.feedback}} 'design', 'warnings', 'summary', 'all' or 'none';
#' \item{\code{ANOPA.zeros}} how are handled the zero trials to avoid 0 divided by 0 error;
#' \item{\code{ANOPA.digits}} for the number of digits displayed in the summary table.
#' }
Expand Down Expand Up @@ -96,7 +96,7 @@ ANOPA.env <- new.env(parent = emptyenv())
# summary is not used so far...
ANOPAwarning <- function( txt ) {
if ( ("all" %in% getOption("ANOPA.feedback"))|("warnings" %in% getOption("ANOPA.feedback"))) {
warning(txt)
warning(txt, call. = FALSE)
}
}
ANOPAmessage <- function( txt ) {
Expand Down
10 changes: 4 additions & 6 deletions R/ANOPA-plot.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,11 +5,11 @@
#'
#' @md
#'
#' @description The function `anopaPlot()` performs a plot of proportions for designs
#' @description The function 'anopaPlot()' performs a plot of proportions for designs
#' with up to 4 factors according to the
#' `ANOPA` framework. See \insertCite{lc23;textual}{ANOPA} for more. The plot is
#' realized using the `suberb` library; see \insertCite{cgh21;textual}{ANOPA}.
#' It uses the arc-sine transformation `A()`.
#' 'ANOPA' framework. See \insertCite{lc23;textual}{ANOPA} for more. The plot is
#' realized using the 'suberb' library; see \insertCite{cgh21;textual}{ANOPA}.
#' It uses the arc-sine transformation 'A()'.
#'
#'
#' @usage anopaPlot(w, formula, confidenceLevel = .95, allowImputing = FALSE,
Expand Down Expand Up @@ -134,11 +134,9 @@ anopa_asn_trans2 <- function(x) {
anopa_asn_trans <- function () {
scales::trans_new("asn2",
function(x) {
#cat("1:",x," = ", sapply(x, anopa_asn_trans1),"\n");
sapply(x, anopa_asn_trans1)
},
function(x) {
#cat("2:",x," = ", sapply(x, anopa_asn_trans2),"\n");
sapply(x, anopa_asn_trans2)
},
domain = c(0, 1)
Expand Down
Loading

0 comments on commit ac53156

Please sign in to comment.