diff --git a/DESCRIPTION b/DESCRIPTION index f52a98f..f32151b 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -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 = "denis.cousineau@uottawa.ca", role = c("aut", "ctb", "cre")), diff --git a/NEWS.md b/NEWS.md index 4f028d6..2fb3289 100644 --- a/NEWS.md +++ b/NEWS.md @@ -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; diff --git a/R/ANOPA-anopa.R b/R/ANOPA-anopa.R index 3dc9545..e5c2def 100644 --- a/R/ANOPA-anopa.R +++ b/R/ANOPA-anopa.R @@ -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 @@ -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) ) @@ -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)) ) diff --git a/R/ANOPA-contrastProportions.R b/R/ANOPA-contrastProportions.R index 271a19b..808fe58 100644 --- a/R/ANOPA-contrastProportions.R +++ b/R/ANOPA-contrastProportions.R @@ -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()`; @@ -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) #' #' ###################################################################################### @@ -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...") diff --git a/R/ANOPA-convert.R b/R/ANOPA-convert.R index 4554098..ca45dbf 100644 --- a/R/ANOPA-convert.R +++ b/R/ANOPA-convert.R @@ -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) diff --git a/R/ANOPA-emProportions.R b/R/ANOPA-emProportions.R index 1d51f8f..b8deb04 100644 --- a/R/ANOPA-emProportions.R +++ b/R/ANOPA-emProportions.R @@ -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. #' @@ -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 @@ -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 diff --git a/R/ANOPA-functions.R b/R/ANOPA-functions.R index 62aac63..87f5b20 100644 --- a/R/ANOPA-functions.R +++ b/R/ANOPA-functions.R @@ -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}. @@ -102,7 +102,6 @@ SE.Atrans <- function(v) { # its variance... var.Atrans <- function(v) { -print(length(v)) 1 / (4*(length(v)+1/2)) } @@ -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 diff --git a/R/ANOPA-logicals.R b/R/ANOPA-logicals.R index d3217df..aa1de6e 100644 --- a/R/ANOPA-logicals.R +++ b/R/ANOPA-logicals.R @@ -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) diff --git a/R/ANOPA-methods.R b/R/ANOPA-methods.R index 1673607..788c094 100644 --- a/R/ANOPA-methods.R +++ b/R/ANOPA-methods.R @@ -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, ...) @@ -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 @@ -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) @@ -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)) @@ -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, ...) @@ -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)) @@ -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, ...) @@ -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)) diff --git a/R/ANOPA-package.R b/R/ANOPA-package.R index fb9c61d..284df6c 100644 --- a/R/ANOPA-package.R +++ b/R/ANOPA-package.R @@ -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 @@ -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 #' @@ -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. #' } @@ -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 ) { diff --git a/R/ANOPA-plot.R b/R/ANOPA-plot.R index 118e7bc..5d4b5d5 100644 --- a/R/ANOPA-plot.R +++ b/R/ANOPA-plot.R @@ -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, @@ -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) diff --git a/R/ANOPA-posthocProportions.R b/R/ANOPA-posthocProportions.R index 5f7be23..d1ac8dd 100644 --- a/R/ANOPA-posthocProportions.R +++ b/R/ANOPA-posthocProportions.R @@ -3,8 +3,8 @@ #' #' @md #' -#' @description The function `posthocProportions()` performs post-hoc analyses -#' of proportions after an omnibus analysis has been obtained with `anopa()` +#' @description The function 'posthocProportions()' performs post-hoc analyses +#' of proportions after an omnibus analysis has been obtained with 'anopa()' #' according to the ANOPA framework. It is based on the tukey HSD test. #' See \insertCite{lc23b;textual}{ANOPA} for more. #' @@ -51,12 +51,8 @@ #' #' # Let's execute the post-hoc tests #' e <- posthocProportions(w, ~ Difficulty | Class ) -#' #summary(e) +#' summary(e) #' -#' # As a check, you can verify that the $F$s are decomposed additively -#' #sum(e$omnibus[,1]) -#' w$omnibus[3,1]+w$omnibus[4,1] -#' #' #' # -- SECOND EXAMPLE -- #' # Example using the Arrington et al. (2002) data, a 3 x 4 x 2 design involving @@ -80,12 +76,9 @@ #' #' # Let's analyse the simple effect of Tropism for every levels of Diel and Location #' e <- posthocProportions(w, ~ Tropism | Diel ) -#' #summary(e) +#' summary(e) +#' #' -#' # Again, as a check, you can verify that the $F$s are decomposed additively -#' w$omnibus[4,1]+w$omnibus[7,1] # B + B:C -#' #sum(e$omnibus[,1]) -#' #' # You can ask easier outputs with #' summarize(w) # or summary(w) for the ANOPA table only #' corrected(w) # or uncorrected(w) for an abbreviated ANOPA table @@ -102,5 +95,5 @@ posthocProportions <- function( w = NULL, formula = NULL ){ - print("Not yet programmed...") + ANOPAmessage("Not yet programmed...") } \ No newline at end of file diff --git a/R/ANOPA-power.R b/R/ANOPA-power.R index 867a878..94ee9a2 100644 --- a/R/ANOPA-power.R +++ b/R/ANOPA-power.R @@ -5,10 +5,10 @@ #' #' @md #' -#' @description The function `anopaN2Power()` performs an analysis of statistical power -#' according to the `ANOPA` framework. See \insertCite{lc23b;textual}{ANOPA} for more. -#' `anopaPower2N()` computes the sample size to reach a given power. -#' Finally, `anopaProp2fsq()` computes the f^2 effect size from a set of proportions. +#' @description The function 'anopaN2Power()' performs an analysis of statistical power +#' according to the 'ANOPA' framework. See \insertCite{lc23b;textual}{ANOPA} for more. +#' 'anopaPower2N()' computes the sample size to reach a given power. +#' Finally, 'anopaProp2fsq()' computes the f^2 effect size from a set of proportions. #' #' @usage anopaPower2N(power, P, f2, alpha) #' @usage anopaN2Power(N, P, f2, alpha) diff --git a/R/ANOPA-random.R b/R/ANOPA-random.R index fabef7a..2989a1e 100644 --- a/R/ANOPA-random.R +++ b/R/ANOPA-random.R @@ -5,10 +5,10 @@ #' #' @md #' -#' @description The function `GRP()` +#' @description The function 'GRP()' #' generates random proportions based on a design, i.e., #' a list giving the factors and the categories with each factor. -#' The data are returned in the `wide` format. +#' The data are returned in the 'wide' format. #' #' @usage GRP( props, n, BSDesign=NULL, WSDesign=NULL, sname = "s" ) #' @usage rBernoulli(n, p) @@ -57,15 +57,15 @@ #' #' # This last one has three factors, for a total of 3 x 2 x 2 = 12 cells #' design <- list( A=letters[1:3], B = c("low","high"), C = c("cat","dog")) -#' GRP( design, n = 100, props = rep(0.5,12) ) +#' GRP( design, n = 30, props = rep(0.5,12) ) #' #' # To specify unequal probabilities, use #' design <- list( A=letters[1:3], B = c("low","high")) #' expProp <- c(.05, .05, .35, .35, .10, .10 ) -#' GRP( design, n = 100, props=expProp ) +#' GRP( design, n = 30, props=expProp ) #' #' # The name of the column containing the proportions can be changed -#' GRP( design, n=100, props=expProp, sname="patate") +#' GRP( design, n=30, props=expProp, sname="patate") #' #' # Examples of use of rBernoulli #' t <- rBernoulli(50, 0.1) diff --git a/R/ANOPA-unitaryAlpha.R b/R/ANOPA-unitaryAlpha.R index 870dba8..f4683d7 100644 --- a/R/ANOPA-unitaryAlpha.R +++ b/R/ANOPA-unitaryAlpha.R @@ -3,12 +3,12 @@ #' #' @md #' -#' @description The function `unitaryAlpha()` computes +#' @description The function 'unitaryAlpha()' computes #' the unitary alpha (\insertCite{lc23}{ANOPA}). This #' quantity is a novel way to compute correlation in a matrix #' where each column is a measure and each line, a subject. #' This measure is based on Cronbach's alpha (which could be -#' labeled a `global alpha`). +#' labeled a 'global alpha'). #' #' @usage unitaryAlpha( m ) #' diff --git a/R/ArringtonEtAll2002.R b/R/ArringtonEtAll2002.R index 1c6680a..ed58307 100644 --- a/R/ArringtonEtAll2002.R +++ b/R/ArringtonEtAll2002.R @@ -3,9 +3,9 @@ #' The data, taken from \insertCite{a02;textual}{ANOPA}, is a dataset examining #' the distribution of fishes with empty stomachs, classified over #' three factors: -#' `Collection location` (3 levels: Africa, Central/South America, North America), -#' `Diel feeding behavior` (2 levels: diurnal, nocturnal), -#' `Trophic category` (4 levels: Detritivore, Invertivore, Omnivore, Piscivore). +#' 'Collection location' (3 levels: Africa, Central/South America, North America), +#' 'Diel feeding behavior' (2 levels: diurnal, nocturnal), +#' 'Trophic category' (4 levels: Detritivore, Invertivore, Omnivore, Piscivore). #' It is therefore a 3 × 2 × 4 design with 24 cells. #' The original data set also contains Order, Family and Species of the observed #' fishes and can be obtained from diff --git a/R/minimalExamples.R b/R/minimalExamples.R index 4aeac6c..d40e4cc 100644 --- a/R/minimalExamples.R +++ b/R/minimalExamples.R @@ -8,11 +8,11 @@ #' @description The datasets present minimal examples that are analyzed with an #' Analysis of Frequency Data method (described in \insertCite{lc23;textual}{ANOPA}. #' The five datasets are -#' - `minimalBSExample`: an example with a single factor (state of residency) -#' - `twoWayExample`: an example with two factors, Class and Difficulty -#' - `minimalWSExample`: an example with a within-subject design (three measurements) -#' - `twoWayWithinExample`: an example with two within-subject factors -#' - `minimalMxExample`: a mixed design having one within and one between-subject factors +#' - 'minimalBSExample': an example with a single factor (state of residency) +#' - 'twoWayExample': an example with two factors, Class and Difficulty +#' - 'minimalWSExample': an example with a within-subject design (three measurements) +#' - 'twoWayWithinExample': an example with two within-subject factors +#' - 'minimalMxExample': a mixed design having one within and one between-subject factors #' #' @docType data #' @@ -26,14 +26,14 @@ #' @examples #' library(ANOPA) #' -#' # the minimalBSExample data with proportions per state of residency for three states -#' minimalBSExample +#' # the twoWayExample data with proportions per Classes and Difficulty levels +#' twoWayExample #' #' # perform an anopa on this dataset -#' w <- anopa( {s;n} ~ state, minimalBSExample) +#' w <- anopa( {success;total} ~ Difficulty * Class, twoWayExample) #' -#' # We analyse the intensity by levels of pitch -#' # e <- emProportions(w, ~ Intensity | Pitch) +#' # We analyse the proportions by Difficulty for each Class +#' e <- emProportions(w, ~ Difficulty | Class) #' #' @rdname minimalExamples diff --git a/README.Rmd b/README.Rmd index d17edcc..c1c37b7 100644 --- a/README.Rmd +++ b/README.Rmd @@ -62,12 +62,7 @@ anopaPlot(w, ~ SES) ``` If the interaction had been significant, simple effects can be analyzed from the _expected marginal -frequencies_ with - -```{r, message=FALSE, warning=FALSE, echo=TRUE, eval=TRUE} -#e <- emProportions(w, ~ SES | MofDiagnostic ) -#summary(e) -``` +frequencies_ with `e <- emProportions(w, ~ SES | MofDiagnostic )`. Follow-up analyses include contrasts examinations with `contrastProportions()`; finally, post-hoc pairwise comparisons can be obtained with `posthocProportions()`. diff --git a/README.md b/README.md index ad3b856..92f0753 100644 --- a/README.md +++ b/README.md @@ -63,11 +63,7 @@ anopaPlot(w, ~ SES) If the interaction had been significant, simple effects can be analyzed from the *expected marginal frequencies* with - -``` r -#e <- emProportions(w, ~ SES | MofDiagnostic ) -#summary(e) -``` +`e <- emProportions(w, ~ SES | MofDiagnostic )`. Follow-up analyses include contrasts examinations with `contrastProportions()`; finally, post-hoc pairwise comparisons can be @@ -91,7 +87,7 @@ install.packages("ANOPA") library(ANOPA) ``` -The development version 0.1.1 can be accessed through GitHub: +The development version 0.1.3 can be accessed through GitHub: ``` r devtools::install_github("dcousin3/ANOPA") diff --git a/docs/404.html b/docs/404.html index 05eeb38..ec50a8d 100644 --- a/docs/404.html +++ b/docs/404.html @@ -32,7 +32,7 @@ ANOPA - 0.1.1 + 0.1.3 diff --git a/docs/articles/A-WhatIsANOPA.html b/docs/articles/A-WhatIsANOPA.html index dbc87f1..965ccf0 100644 --- a/docs/articles/A-WhatIsANOPA.html +++ b/docs/articles/A-WhatIsANOPA.html @@ -34,7 +34,7 @@ ANOPA - 0.1.1 + 0.1.3 diff --git a/docs/articles/B-DataFormatsForProportions.html b/docs/articles/B-DataFormatsForProportions.html index 6b11415..b7bfa67 100644 --- a/docs/articles/B-DataFormatsForProportions.html +++ b/docs/articles/B-DataFormatsForProportions.html @@ -34,7 +34,7 @@ ANOPA - 0.1.1 + 0.1.3 @@ -423,7 +423,9 @@

Multiple repeated-measure factors## r11 r12 r12.1 r21 r22 r23 Count uAlpha ## 1 14 6 6 14 16 14 30 0.1074324

A “fyi” message is shown which lets you see how the variables are -interpreted.

+interpreted. Such messages can be inhibited by changing the option

+
+options("ANOPA.feedback" = "none")

To know more about analyzing proportions with ANOPA, refer to Laurencelle & Cousineau (2023) or to What is an ANOPA?.

diff --git a/docs/articles/C-ConfidenceIntervals.html b/docs/articles/C-ConfidenceIntervals.html index 24ae360..f56b49d 100644 --- a/docs/articles/C-ConfidenceIntervals.html +++ b/docs/articles/C-ConfidenceIntervals.html @@ -34,7 +34,7 @@ ANOPA - 0.1.1 + 0.1.3 @@ -137,7 +137,7 @@

Theory behind Confid by \(\sqrt{2}\).

Also, in repeated measure designs, the correlation is beneficial to improve estimates. As such, the interval wide can be reduced when -correlation is positive by multiplying its length by \(1-\alpha_1\), where \(\alpha_1\) is a measure of correlation in a +correlation is positive by multiplying its length by \(\sqrt{1-\alpha_1}\), where \(\alpha_1\) is a measure of correlation in a matrix containing repeated measures (based on the unitary alpha measure).

Finally, the above returns confidence intervals for the @@ -180,7 +180,7 @@

Complicated?library(ggplot2) anopaPlot(w, ~ Difficulty) + theme_bw() + # change theme - scale_x_discrete(limits = c("Easy", "Moderate", "Difficult")) #changer order + scale_x_discrete(limits = c("Easy", "Moderate", "Difficult")) #change order
**Figure 3**. Same as Figure 2 with some visual improvements.

Figure 3. Same as Figure 2 with some visual @@ -188,7 +188,7 @@

Complicated? diff --git a/docs/articles/D-ArringtonExample.html b/docs/articles/D-ArringtonExample.html index b4cb22d..934bd1a 100644 --- a/docs/articles/D-ArringtonExample.html +++ b/docs/articles/D-ArringtonExample.html @@ -34,7 +34,7 @@ ANOPA - 0.1.1 + 0.1.3

@@ -162,14 +162,14 @@

Analyzing proportions with the Arrington et ## Africa Nocturnal Detritivore 0 0 ## Africa Nocturnal Omnivore 0 0 ## North America Nocturnal Detritivore 0 0 -
## Warning in ANOPAwarning("ANOPA::warning(1): Some cells have zero over zero
-## data. Imputing..."): ANOPA::warning(1): Some cells have zero over zero data.
-## Imputing...
+
## Warning: ANOPA::warning(1): Some cells have zero over zero data. Imputing...

The fyi message lets you know that cells are missing; the Warning message lets you know that these cells were -imputed.

-

To see the result (using the uncorrected results as the samples are -not small),

+imputed (you can suppress messages with +options("ANOPA.feedback"="none").

+

To see the result, use summary(w) (which shows the +corrected and uncorrected statistics) or uncorrected(w) (as +the sample is quite large, the correction will be immaterial…),

 uncorrected(w)
##                              MS  df        F   pvalue
diff --git a/docs/articles/E-ArcsineIsAsinine.html b/docs/articles/E-ArcsineIsAsinine.html
index 1aedf34..2cc477a 100644
--- a/docs/articles/E-ArcsineIsAsinine.html
+++ b/docs/articles/E-ArcsineIsAsinine.html
@@ -34,7 +34,7 @@
       
       
         ANOPA
-        0.1.1
+        0.1.3
       
     
 
diff --git a/docs/articles/E-ArcsineIsAsinine_files/figure-html/unnamed-chunk-4-1.png b/docs/articles/E-ArcsineIsAsinine_files/figure-html/unnamed-chunk-4-1.png
index 98e8e01..02bff2c 100644
Binary files a/docs/articles/E-ArcsineIsAsinine_files/figure-html/unnamed-chunk-4-1.png and b/docs/articles/E-ArcsineIsAsinine_files/figure-html/unnamed-chunk-4-1.png differ
diff --git a/docs/articles/E-ArcsineIsAsinine_files/figure-html/unnamed-chunk-7-1.png b/docs/articles/E-ArcsineIsAsinine_files/figure-html/unnamed-chunk-7-1.png
index 8d0b42c..5130b8f 100644
Binary files a/docs/articles/E-ArcsineIsAsinine_files/figure-html/unnamed-chunk-7-1.png and b/docs/articles/E-ArcsineIsAsinine_files/figure-html/unnamed-chunk-7-1.png differ
diff --git a/docs/articles/F-TestingTypeIError.html b/docs/articles/F-TestingTypeIError.html
index ad68304..f716dd5 100644
--- a/docs/articles/F-TestingTypeIError.html
+++ b/docs/articles/F-TestingTypeIError.html
@@ -34,7 +34,7 @@
       
       
         ANOPA
-        0.1.1
+        0.1.3
       
     
 
@@ -121,7 +121,7 @@ 

Testing type-I error rates

library(ANOPA) library(testthat) nsim <- 1000 # increase for more reliable simulations. -theN <- 20 # number of participants
+theN <- 20 # number of simulated participants

Note that the simulations are actually not run in this vignette, as they take times. We wished to provide code in case you wished to test type-I error rate by yourself. The present code is also not optimized diff --git a/docs/articles/index.html b/docs/articles/index.html index ea7856f..eb1c846 100644 --- a/docs/articles/index.html +++ b/docs/articles/index.html @@ -17,7 +17,7 @@ ANOPA - 0.1.1 + 0.1.3 diff --git a/docs/authors.html b/docs/authors.html index 3f2f3d3..5931332 100644 --- a/docs/authors.html +++ b/docs/authors.html @@ -17,7 +17,7 @@ ANOPA - 0.1.1 + 0.1.3 diff --git a/docs/index.html b/docs/index.html index 5057950..734ff83 100644 --- a/docs/index.html +++ b/docs/index.html @@ -46,7 +46,7 @@ ANOPA - 0.1.1 + 0.1.3 @@ -130,10 +130,7 @@

 anopaPlot(w, ~ SES)

-

If the interaction had been significant, simple effects can be analyzed from the expected marginal frequencies with

-
-#e <- emProportions(w, ~ SES | MofDiagnostic )
-#summary(e)
+

If the interaction had been significant, simple effects can be analyzed from the expected marginal frequencies with e <- emProportions(w, ~ SES | MofDiagnostic ).

Follow-up analyses include contrasts examinations with contrastProportions(); finally, post-hoc pairwise comparisons can be obtained with posthocProportions().

Prior to running an experiment, you might consider some statistical power planning on proportions using anopaPower2N() or anopaN2Power() as long as you can anticipate the expected proportions. A convenient effect size, the f-square and eta-square can be obtained with anopaPropTofsq().

Finally, toCompiled(), toLong() and toWide() can be used to present the proportion in other formats.

@@ -142,16 +139,16 @@

Installation

The official CRAN version can be installed with

-
+
-

The development version 0.1.1 can be accessed through GitHub:

-
+

The development version 0.1.3 can be accessed through GitHub:

+
 devtools::install_github("dcousin3/ANOPA")
 library(ANOPA)

Note that the package ANOPA is named using UPPERCASE letters whereas the main function anopa() is written using lowercase letters.

The library is loaded with

-
diff --git a/docs/news/index.html b/docs/news/index.html index 4ed73b7..e6c7985 100644 --- a/docs/news/index.html +++ b/docs/news/index.html @@ -17,7 +17,7 @@ ANOPA - 0.1.1 + 0.1.3
@@ -72,13 +72,22 @@

Changelog

Source: NEWS.md
+
+ +
  • removed some cats and a few `
  • +
+
+ +
  • added to speed tests;

  • +
  • moved difference-adjustments within the CI.Atrans function.

  • +
-
  • Beta release of ANOPA on CRAN
  • +
    • Beta release of ANOPA on CRAN.
-
  • Beta release of ANOPA on GitHub
  • +
    • Beta release of ANOPA on GitHub.
diff --git a/docs/pkgdown.yml b/docs/pkgdown.yml index eb89174..07bc87a 100644 --- a/docs/pkgdown.yml +++ b/docs/pkgdown.yml @@ -8,7 +8,7 @@ articles: D-ArringtonExample: D-ArringtonExample.html E-ArcsineIsAsinine: E-ArcsineIsAsinine.html F-TestingTypeIError: F-TestingTypeIError.html -last_built: 2024-03-17T18:07Z +last_built: 2024-03-19T21:22Z urls: reference: https://dcousin3.github.io/ANOPA/reference article: https://dcousin3.github.io/ANOPA/articles diff --git a/docs/reference/A.html b/docs/reference/A.html index 57c12c6..965ac65 100644 --- a/docs/reference/A.html +++ b/docs/reference/A.html @@ -1,14 +1,14 @@ -transformation functions — A • ANOPA @@ -26,7 +26,7 @@ ANOPA - 0.1.1 + 0.1.3 @@ -83,10 +83,10 @@

transformation functions

-

The transformation functions A() performs the +

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 (Laurencelle and Cousineau 2023) . It was originally proposed by @@ -185,7 +185,6 @@

Examples

#> [1] 0.7853982 var.Atrans( c(1,1,1,1,1,0,0,0,0,0) ) -#> [1] 10 #> [1] 0.02380952 diff --git a/docs/reference/ANOPA-package.html b/docs/reference/ANOPA-package.html index 83c55dd..d323963 100644 --- a/docs/reference/ANOPA-package.html +++ b/docs/reference/ANOPA-package.html @@ -1,5 +1,5 @@ -ANOPA: Analyses of Proportions using Anscombe Transform — ANOPA-package • ANOPA @@ -65,7 +65,7 @@ ANOPA - 0.1.1 + 0.1.3
@@ -122,7 +122,7 @@

ANOPA: Analyses of Proportions using Anscombe Transform

-

ANOPA is a library to perform proportion analyses. +

'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 @@ -134,8 +134,8 @@

ANOPA: Analyses of Proportions using Anscombe Transform

easy.

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

w <- anopa(formula, data)

where formula is a formula giving the factors, e.g., "Freq ~ A * B".

@@ -161,7 +161,7 @@

ANOPA: Analyses of Proportions using Anscombe Transform

  • ArticleExample1 illustrates a 4-way design;

  • ArticleExample2 illustrates a 2 x 3 design;

  • ArticleExample3 illustrates a (4) within-subject design;

  • -

    The functions uses the following options:

    The functions uses the following options:

    diff --git a/docs/reference/ArringtonEtAl2002.html b/docs/reference/ArringtonEtAl2002.html index 8189423..bc2c1d8 100644 --- a/docs/reference/ArringtonEtAl2002.html +++ b/docs/reference/ArringtonEtAl2002.html @@ -3,9 +3,9 @@ , is a dataset examining the distribution of fishes with empty stomachs, classified over three factors: -Collection location (3 levels: Africa, Central/South America, North America), -Diel feeding behavior (2 levels: diurnal, nocturnal), -Trophic category (4 levels: Detritivore, Invertivore, Omnivore, Piscivore). +'Collection location' (3 levels: Africa, Central/South America, North America), +'Diel feeding behavior' (2 levels: diurnal, nocturnal), +'Trophic category' (4 levels: Detritivore, Invertivore, Omnivore, Piscivore). It is therefore a 3 × 2 × 4 design with 24 cells. The original data set also contains Order, Family and Species of the observed fishes and can be obtained from @@ -29,7 +29,7 @@ ANOPA - 0.1.1 + 0.1.3 @@ -90,9 +90,9 @@

    Arrington et al. (2002) dataset

    , is a dataset examining the distribution of fishes with empty stomachs, classified over three factors: -Collection location (3 levels: Africa, Central/South America, North America), -Diel feeding behavior (2 levels: diurnal, nocturnal), -Trophic category (4 levels: Detritivore, Invertivore, Omnivore, Piscivore). +'Collection location' (3 levels: Africa, Central/South America, North America), +'Diel feeding behavior' (2 levels: diurnal, nocturnal), +'Trophic category' (4 levels: Detritivore, Invertivore, Omnivore, Piscivore). It is therefore a 3 × 2 × 4 design with 24 cells. The original data set also contains Order, Family and Species of the observed fishes and can be obtained from diff --git a/docs/reference/ArticleExample1.html b/docs/reference/ArticleExample1.html index fd91902..da453cf 100644 --- a/docs/reference/ArticleExample1.html +++ b/docs/reference/ArticleExample1.html @@ -21,7 +21,7 @@ ANOPA - 0.1.1 + 0.1.3 @@ -123,7 +123,7 @@

    Examples

    # We finish with post-hoc Tukey test e <- posthocProportions( w ) -#> [1] "Not yet programmed..." +#> Not yet programmed... # a small plot is *always* a good idea anopaPlot(w) diff --git a/docs/reference/ArticleExample2.html b/docs/reference/ArticleExample2.html index 168a1d9..6f9edd3 100644 --- a/docs/reference/ArticleExample2.html +++ b/docs/reference/ArticleExample2.html @@ -22,7 +22,7 @@ ANOPA - 0.1.1 + 0.1.3 diff --git a/docs/reference/ArticleExample3.html b/docs/reference/ArticleExample3.html index e479590..d85563d 100644 --- a/docs/reference/ArticleExample3.html +++ b/docs/reference/ArticleExample3.html @@ -23,7 +23,7 @@ ANOPA - 0.1.1 + 0.1.3 @@ -160,7 +160,7 @@

    Examples

    # We finish with post-hoc Tukey test e <- posthocProportions( w ) -#> [1] "Not yet programmed..." +#> Not yet programmed... # a small plot is *always* a good idea anopaPlot(w) diff --git a/docs/reference/anopa.html b/docs/reference/anopa.html index 462394a..c82a3de 100644 --- a/docs/reference/anopa.html +++ b/docs/reference/anopa.html @@ -1,6 +1,6 @@ -ANOPA: analysis of proportions using Anscombe transform. — anopa • ANOPAANOPA: analysis of proportions using Anscombe transform. — anopa • ANOPAComputing power within the ANOPA. — anopaN2Power • ANOPAComputing power within the ANOPA. — anopaN2Power • ANOPA @@ -21,7 +21,7 @@ ANOPA - 0.1.1 + 0.1.3 @@ -78,11 +78,11 @@

    Computing power within the ANOPA.

    -

    The function anopaN2Power() performs an analysis of statistical power -according to the ANOPA framework. See Laurencelle and Cousineau (2023) +

    The function 'anopaN2Power()' performs an analysis of statistical power +according to the 'ANOPA' framework. See Laurencelle and Cousineau (2023) for more. -anopaPower2N() computes the sample size to reach a given power. -Finally, anopaProp2fsq() computes the f^2 effect size from a set of proportions.

    +'anopaPower2N()' computes the sample size to reach a given power. +Finally, 'anopaProp2fsq()' computes the f^2 effect size from a set of proportions.

    diff --git a/docs/reference/anopa_asn_trans1.html b/docs/reference/anopa_asn_trans1.html index 1d315f6..d9c83d7 100644 --- a/docs/reference/anopa_asn_trans1.html +++ b/docs/reference/anopa_asn_trans1.html @@ -1,11 +1,11 @@ -anopaPlot: Easy plotting of proportions. — anopa_asn_trans1 • ANOPAanopaPlot: Easy plotting of proportions. — anopa_asn_trans1 • ANOPA @@ -23,7 +23,7 @@ ANOPA - 0.1.1 + 0.1.3
    @@ -80,13 +80,13 @@

    anopaPlot: Easy plotting of proportions.

    -

    The function anopaPlot() performs a plot of proportions for designs +

    The function 'anopaPlot()' performs a plot of proportions for designs with up to 4 factors according to the -ANOPA framework. See Laurencelle and Cousineau (2023) +'ANOPA' framework. See Laurencelle and Cousineau (2023) for more. The plot is -realized using the suberb library; see Cousineau et al. (2021) +realized using the 'suberb' library; see Cousineau et al. (2021) . -It uses the arc-sine transformation A().

    +It uses the arc-sine transformation 'A()'.

    diff --git a/docs/reference/contrastProportions.html b/docs/reference/contrastProportions.html index 43d41ec..eded29a 100644 --- a/docs/reference/contrastProportions.html +++ b/docs/reference/contrastProportions.html @@ -1,6 +1,6 @@ -contrastProportion: analysis of contrasts between proportions using Anscombe transform. — contrastProportions • ANOPAcontrastProportion: analysis of contrasts between proportions using Anscombe transform. — contrastProportions • ANOPAConverting between formats — conversion • ANOPAConverting between formats — conversion • ANOPAcorrected — corrected • ANOPAcorrected — corrected • ANOPAemProportions: simple effect analysis of proportions. — emProportions • ANOPAemProportions: simple effect analysis of proportions. — emProportions • ANOPAexplain — explain • ANOPAexplain — explain • ANOPAposthocProportions: post-hoc analysis of proportions. — posthocProportions • ANOPAposthocProportions: post-hoc analysis of proportions. — posthocProportions • ANOPAGenerating random proportions with GRP — rBernoulli • ANOPAGenerating random proportions with GRP — rBernoulli • ANOPA @@ -20,7 +20,7 @@ ANOPA - 0.1.1 + 0.1.3
    @@ -77,10 +77,10 @@

    Generating random proportions with GRP

    -

    The function GRP() +

    The function 'GRP()' generates random proportions based on a design, i.e., a list giving the factors and the categories with each factor. -The data are returned in the wide format.

    +The data are returned in the 'wide' format.

    @@ -510,1213 +510,373 @@

    Examples

    # This last one has three factors, for a total of 3 x 2 x 2 = 12 cells design <- list( A=letters[1:3], B = c("low","high"), C = c("cat","dog")) -GRP( design, n = 100, props = rep(0.5,12) ) -#> id A B C s -#> 1 1 a low cat 1 -#> 2 2 a low cat 1 -#> 3 3 a low cat 1 -#> 4 4 a low cat 1 -#> 5 5 a low cat 1 -#> 6 6 a low cat 1 -#> 7 7 a low cat 1 -#> 8 8 a low cat 0 -#> 9 9 a low cat 0 -#> 10 10 a low cat 1 -#> 11 11 a low cat 0 -#> 12 12 a low cat 0 -#> 13 13 a low cat 0 -#> 14 14 a low cat 1 -#> 15 15 a low cat 1 -#> 16 16 a low cat 0 -#> 17 17 a low cat 0 -#> 18 18 a low cat 1 -#> 19 19 a low cat 1 -#> 20 20 a low cat 1 -#> 21 21 a low cat 1 -#> 22 22 a low cat 1 -#> 23 23 a low cat 1 -#> 24 24 a low cat 1 -#> 25 25 a low cat 0 -#> 26 26 a low cat 0 -#> 27 27 a low cat 1 -#> 28 28 a low cat 0 -#> 29 29 a low cat 1 -#> 30 30 a low cat 1 -#> 31 31 a low cat 1 -#> 32 32 a low cat 0 -#> 33 33 a low cat 1 -#> 34 34 a low cat 1 -#> 35 35 a low cat 0 -#> 36 36 a low cat 0 -#> 37 37 a low cat 0 -#> 38 38 a low cat 1 -#> 39 39 a low cat 0 -#> 40 40 a low cat 1 -#> 41 41 a low cat 0 -#> 42 42 a low cat 0 -#> 43 43 a low cat 1 -#> 44 44 a low cat 0 -#> 45 45 a low cat 0 -#> 46 46 a low cat 0 -#> 47 47 a low cat 1 -#> 48 48 a low cat 1 -#> 49 49 a low cat 1 -#> 50 50 a low cat 0 -#> 51 51 a low cat 1 -#> 52 52 a low cat 1 -#> 53 53 a low cat 1 -#> 54 54 a low cat 1 -#> 55 55 a low cat 0 -#> 56 56 a low cat 1 -#> 57 57 a low cat 0 -#> 58 58 a low cat 1 -#> 59 59 a low cat 0 -#> 60 60 a low cat 1 -#> 61 61 a low cat 0 -#> 62 62 a low cat 1 -#> 63 63 a low cat 0 -#> 64 64 a low cat 0 -#> 65 65 a low cat 1 -#> 66 66 a low cat 0 -#> 67 67 a low cat 1 -#> 68 68 a low cat 1 -#> 69 69 a low cat 1 -#> 70 70 a low cat 1 -#> 71 71 a low cat 0 -#> 72 72 a low cat 1 -#> 73 73 a low cat 1 -#> 74 74 a low cat 0 -#> 75 75 a low cat 1 -#> 76 76 a low cat 0 -#> 77 77 a low cat 1 -#> 78 78 a low cat 1 -#> 79 79 a low cat 1 -#> 80 80 a low cat 0 -#> 81 81 a low cat 0 -#> 82 82 a low cat 0 -#> 83 83 a low cat 1 -#> 84 84 a low cat 0 -#> 85 85 a low cat 0 -#> 86 86 a low cat 0 -#> 87 87 a low cat 0 -#> 88 88 a low cat 0 -#> 89 89 a low cat 1 -#> 90 90 a low cat 0 -#> 91 91 a low cat 1 -#> 92 92 a low cat 1 -#> 93 93 a low cat 0 -#> 94 94 a low cat 0 -#> 95 95 a low cat 0 -#> 96 96 a low cat 0 -#> 97 97 a low cat 1 -#> 98 98 a low cat 0 -#> 99 99 a low cat 0 -#> 100 100 a low cat 1 -#> 101 101 b low cat 1 -#> 102 102 b low cat 1 -#> 103 103 b low cat 1 -#> 104 104 b low cat 1 -#> 105 105 b low cat 1 -#> 106 106 b low cat 0 -#> 107 107 b low cat 0 -#> 108 108 b low cat 1 -#> 109 109 b low cat 0 -#> 110 110 b low cat 1 -#> 111 111 b low cat 0 -#> 112 112 b low cat 1 -#> 113 113 b low cat 0 -#> 114 114 b low cat 1 -#> 115 115 b low cat 0 -#> 116 116 b low cat 0 -#> 117 117 b low cat 1 -#> 118 118 b low cat 0 -#> 119 119 b low cat 1 -#> 120 120 b low cat 0 -#> 121 121 b low cat 1 -#> 122 122 b low cat 1 -#> 123 123 b low cat 1 -#> 124 124 b low cat 1 -#> 125 125 b low cat 1 -#> 126 126 b low cat 0 -#> 127 127 b low cat 0 -#> 128 128 b low cat 1 -#> 129 129 b low cat 1 -#> 130 130 b low cat 0 -#> 131 131 b low cat 1 -#> 132 132 b low cat 0 -#> 133 133 b low cat 1 -#> 134 134 b low cat 1 -#> 135 135 b low cat 1 -#> 136 136 b low cat 1 -#> 137 137 b low cat 0 -#> 138 138 b low cat 1 -#> 139 139 b low cat 0 -#> 140 140 b low cat 0 -#> 141 141 b low cat 0 -#> 142 142 b low cat 0 -#> 143 143 b low cat 1 -#> 144 144 b low cat 0 -#> 145 145 b low cat 0 -#> 146 146 b low cat 1 -#> 147 147 b low cat 1 -#> 148 148 b low cat 1 -#> 149 149 b low cat 0 -#> 150 150 b low cat 1 -#> 151 151 b low cat 0 -#> 152 152 b low cat 0 -#> 153 153 b low cat 0 -#> 154 154 b low cat 1 -#> 155 155 b low cat 1 -#> 156 156 b low cat 1 -#> 157 157 b low cat 0 -#> 158 158 b low cat 1 -#> 159 159 b low cat 1 -#> 160 160 b low cat 0 -#> 161 161 b low cat 0 -#> 162 162 b low cat 0 -#> 163 163 b low cat 0 -#> 164 164 b low cat 0 -#> 165 165 b low cat 0 -#> 166 166 b low cat 0 -#> 167 167 b low cat 1 -#> 168 168 b low cat 1 -#> 169 169 b low cat 1 -#> 170 170 b low cat 0 -#> 171 171 b low cat 0 -#> 172 172 b low cat 0 -#> 173 173 b low cat 0 -#> 174 174 b low cat 1 -#> 175 175 b low cat 0 -#> 176 176 b low cat 1 -#> 177 177 b low cat 0 -#> 178 178 b low cat 0 -#> 179 179 b low cat 1 -#> 180 180 b low cat 1 -#> 181 181 b low cat 1 -#> 182 182 b low cat 0 -#> 183 183 b low cat 1 -#> 184 184 b low cat 0 -#> 185 185 b low cat 0 -#> 186 186 b low cat 0 -#> 187 187 b low cat 0 -#> 188 188 b low cat 1 -#> 189 189 b low cat 1 -#> 190 190 b low cat 0 -#> 191 191 b low cat 0 -#> 192 192 b low cat 1 -#> 193 193 b low cat 1 -#> 194 194 b low cat 0 -#> 195 195 b low cat 0 -#> 196 196 b low cat 1 -#> 197 197 b low cat 1 -#> 198 198 b low cat 1 -#> 199 199 b low cat 0 -#> 200 200 b low cat 0 -#> 201 201 c low cat 1 -#> 202 202 c low cat 1 -#> 203 203 c low cat 1 -#> 204 204 c low cat 1 -#> 205 205 c low cat 1 -#> 206 206 c low cat 1 -#> 207 207 c low cat 1 -#> 208 208 c low cat 0 -#> 209 209 c low cat 0 -#> 210 210 c low cat 1 -#> 211 211 c low cat 0 -#> 212 212 c low cat 0 -#> 213 213 c low cat 0 -#> 214 214 c low cat 1 -#> 215 215 c low cat 1 -#> 216 216 c low cat 0 -#> 217 217 c low cat 0 -#> 218 218 c low cat 0 -#> 219 219 c low cat 0 -#> 220 220 c low cat 1 -#> 221 221 c low cat 0 -#> 222 222 c low cat 1 -#> 223 223 c low cat 0 -#> 224 224 c low cat 1 -#> 225 225 c low cat 0 -#> 226 226 c low cat 0 -#> 227 227 c low cat 0 -#> 228 228 c low cat 1 -#> 229 229 c low cat 0 -#> 230 230 c low cat 0 -#> 231 231 c low cat 0 -#> 232 232 c low cat 0 -#> 233 233 c low cat 0 -#> 234 234 c low cat 0 -#> 235 235 c low cat 0 -#> 236 236 c low cat 0 -#> 237 237 c low cat 0 -#> 238 238 c low cat 0 -#> 239 239 c low cat 1 -#> 240 240 c low cat 0 -#> 241 241 c low cat 0 -#> 242 242 c low cat 1 -#> 243 243 c low cat 1 -#> 244 244 c low cat 0 -#> 245 245 c low cat 1 -#> 246 246 c low cat 0 -#> 247 247 c low cat 0 -#> 248 248 c low cat 0 -#> 249 249 c low cat 0 -#> 250 250 c low cat 1 -#> 251 251 c low cat 1 -#> 252 252 c low cat 0 -#> 253 253 c low cat 1 -#> 254 254 c low cat 1 -#> 255 255 c low cat 1 -#> 256 256 c low cat 0 -#> 257 257 c low cat 0 -#> 258 258 c low cat 0 -#> 259 259 c low cat 0 -#> 260 260 c low cat 1 -#> 261 261 c low cat 0 -#> 262 262 c low cat 0 -#> 263 263 c low cat 0 -#> 264 264 c low cat 0 -#> 265 265 c low cat 0 -#> 266 266 c low cat 1 -#> 267 267 c low cat 1 -#> 268 268 c low cat 1 -#> 269 269 c low cat 0 -#> 270 270 c low cat 1 -#> 271 271 c low cat 0 -#> 272 272 c low cat 0 -#> 273 273 c low cat 1 -#> 274 274 c low cat 1 -#> 275 275 c low cat 1 -#> 276 276 c low cat 0 -#> 277 277 c low cat 1 -#> 278 278 c low cat 0 -#> 279 279 c low cat 1 -#> 280 280 c low cat 1 -#> 281 281 c low cat 0 -#> 282 282 c low cat 0 -#> 283 283 c low cat 0 -#> 284 284 c low cat 0 -#> 285 285 c low cat 0 -#> 286 286 c low cat 1 -#> 287 287 c low cat 1 -#> 288 288 c low cat 0 -#> 289 289 c low cat 1 -#> 290 290 c low cat 1 -#> 291 291 c low cat 1 -#> 292 292 c low cat 1 -#> 293 293 c low cat 0 -#> 294 294 c low cat 1 -#> 295 295 c low cat 0 -#> 296 296 c low cat 0 -#> 297 297 c low cat 1 -#> 298 298 c low cat 1 -#> 299 299 c low cat 0 -#> 300 300 c low cat 1 -#> 301 301 a high cat 0 -#> 302 302 a high cat 0 -#> 303 303 a high cat 0 -#> 304 304 a high cat 0 -#> 305 305 a high cat 0 -#> 306 306 a high cat 1 -#> 307 307 a high cat 1 -#> 308 308 a high cat 1 -#> 309 309 a high cat 1 -#> 310 310 a high cat 1 -#> 311 311 a high cat 0 -#> 312 312 a high cat 1 -#> 313 313 a high cat 1 -#> 314 314 a high cat 1 -#> 315 315 a high cat 1 -#> 316 316 a high cat 1 -#> 317 317 a high cat 0 -#> 318 318 a high cat 1 -#> 319 319 a high cat 1 -#> 320 320 a high cat 0 -#> 321 321 a high cat 1 -#> 322 322 a high cat 1 -#> 323 323 a high cat 0 -#> 324 324 a high cat 1 -#> 325 325 a high cat 1 -#> 326 326 a high cat 1 -#> 327 327 a high cat 1 -#> 328 328 a high cat 1 -#> 329 329 a high cat 0 -#> 330 330 a high cat 0 -#> 331 331 a high cat 0 -#> 332 332 a high cat 0 -#> 333 333 a high cat 1 -#> 334 334 a high cat 0 -#> 335 335 a high cat 0 -#> 336 336 a high cat 0 -#> 337 337 a high cat 0 -#> 338 338 a high cat 1 -#> 339 339 a high cat 1 -#> 340 340 a high cat 0 -#> 341 341 a high cat 0 -#> 342 342 a high cat 1 -#> 343 343 a high cat 0 -#> 344 344 a high cat 1 -#> 345 345 a high cat 1 -#> 346 346 a high cat 0 -#> 347 347 a high cat 1 -#> 348 348 a high cat 0 -#> 349 349 a high cat 1 -#> 350 350 a high cat 1 -#> 351 351 a high cat 1 -#> 352 352 a high cat 1 -#> 353 353 a high cat 1 -#> 354 354 a high cat 1 -#> 355 355 a high cat 0 -#> 356 356 a high cat 1 -#> 357 357 a high cat 1 -#> 358 358 a high cat 0 -#> 359 359 a high cat 0 -#> 360 360 a high cat 0 -#> 361 361 a high cat 1 -#> 362 362 a high cat 0 -#> 363 363 a high cat 1 -#> 364 364 a high cat 1 -#> 365 365 a high cat 1 -#> 366 366 a high cat 1 -#> 367 367 a high cat 1 -#> 368 368 a high cat 1 -#> 369 369 a high cat 1 -#> 370 370 a high cat 1 -#> 371 371 a high cat 1 -#> 372 372 a high cat 0 -#> 373 373 a high cat 1 -#> 374 374 a high cat 1 -#> 375 375 a high cat 1 -#> 376 376 a high cat 0 -#> 377 377 a high cat 0 -#> 378 378 a high cat 1 -#> 379 379 a high cat 0 -#> 380 380 a high cat 0 -#> 381 381 a high cat 0 -#> 382 382 a high cat 0 -#> 383 383 a high cat 0 -#> 384 384 a high cat 0 -#> 385 385 a high cat 1 -#> 386 386 a high cat 0 -#> 387 387 a high cat 1 -#> 388 388 a high cat 1 -#> 389 389 a high cat 1 -#> 390 390 a high cat 1 -#> 391 391 a high cat 1 -#> 392 392 a high cat 0 -#> 393 393 a high cat 0 -#> 394 394 a high cat 1 -#> 395 395 a high cat 1 -#> 396 396 a high cat 0 -#> 397 397 a high cat 1 -#> 398 398 a high cat 1 -#> 399 399 a high cat 1 -#> 400 400 a high cat 0 -#> 401 401 b high cat 0 -#> 402 402 b high cat 1 -#> 403 403 b high cat 0 -#> 404 404 b high cat 1 -#> 405 405 b high cat 0 -#> 406 406 b high cat 1 -#> 407 407 b high cat 0 -#> 408 408 b high cat 0 -#> 409 409 b high cat 1 -#> 410 410 b high cat 0 -#> 411 411 b high cat 0 -#> 412 412 b high cat 0 -#> 413 413 b high cat 1 -#> 414 414 b high cat 0 -#> 415 415 b high cat 0 -#> 416 416 b high cat 0 -#> 417 417 b high cat 0 -#> 418 418 b high cat 0 -#> 419 419 b high cat 1 -#> 420 420 b high cat 1 -#> 421 421 b high cat 0 -#> 422 422 b high cat 1 -#> 423 423 b high cat 0 -#> 424 424 b high cat 1 -#> 425 425 b high cat 1 -#> 426 426 b high cat 1 -#> 427 427 b high cat 0 -#> 428 428 b high cat 1 -#> 429 429 b high cat 1 -#> 430 430 b high cat 1 -#> 431 431 b high cat 1 -#> 432 432 b high cat 0 -#> 433 433 b high cat 1 -#> 434 434 b high cat 1 -#> 435 435 b high cat 1 -#> 436 436 b high cat 0 -#> 437 437 b high cat 1 -#> 438 438 b high cat 0 -#> 439 439 b high cat 1 -#> 440 440 b high cat 1 -#> 441 441 b high cat 0 -#> 442 442 b high cat 0 -#> 443 443 b high cat 0 -#> 444 444 b high cat 1 -#> 445 445 b high cat 0 -#> 446 446 b high cat 1 -#> 447 447 b high cat 1 -#> 448 448 b high cat 1 -#> 449 449 b high cat 1 -#> 450 450 b high cat 0 -#> 451 451 b high cat 0 -#> 452 452 b high cat 1 -#> 453 453 b high cat 1 -#> 454 454 b high cat 0 -#> 455 455 b high cat 0 -#> 456 456 b high cat 1 -#> 457 457 b high cat 0 -#> 458 458 b high cat 1 -#> 459 459 b high cat 0 -#> 460 460 b high cat 1 -#> 461 461 b high cat 1 -#> 462 462 b high cat 1 -#> 463 463 b high cat 0 -#> 464 464 b high cat 1 -#> 465 465 b high cat 0 -#> 466 466 b high cat 0 -#> 467 467 b high cat 1 -#> 468 468 b high cat 0 -#> 469 469 b high cat 0 -#> 470 470 b high cat 0 -#> 471 471 b high cat 0 -#> 472 472 b high cat 1 -#> 473 473 b high cat 0 -#> 474 474 b high cat 1 -#> 475 475 b high cat 1 -#> 476 476 b high cat 1 -#> 477 477 b high cat 1 -#> 478 478 b high cat 0 -#> 479 479 b high cat 0 -#> 480 480 b high cat 0 -#> 481 481 b high cat 1 -#> 482 482 b high cat 0 -#> 483 483 b high cat 0 -#> 484 484 b high cat 0 -#> 485 485 b high cat 0 -#> 486 486 b high cat 1 -#> 487 487 b high cat 0 -#> 488 488 b high cat 0 -#> 489 489 b high cat 1 -#> 490 490 b high cat 0 -#> 491 491 b high cat 1 -#> 492 492 b high cat 1 -#> 493 493 b high cat 1 -#> 494 494 b high cat 1 -#> 495 495 b high cat 1 -#> 496 496 b high cat 1 -#> 497 497 b high cat 1 -#> 498 498 b high cat 0 -#> 499 499 b high cat 1 -#> 500 500 b high cat 1 -#> 501 501 c high cat 0 -#> 502 502 c high cat 0 -#> 503 503 c high cat 0 -#> 504 504 c high cat 0 -#> 505 505 c high cat 0 -#> 506 506 c high cat 1 -#> 507 507 c high cat 1 -#> 508 508 c high cat 1 -#> 509 509 c high cat 0 -#> 510 510 c high cat 0 -#> 511 511 c high cat 0 -#> 512 512 c high cat 0 -#> 513 513 c high cat 1 -#> 514 514 c high cat 0 -#> 515 515 c high cat 0 -#> 516 516 c high cat 0 -#> 517 517 c high cat 0 -#> 518 518 c high cat 1 -#> 519 519 c high cat 0 -#> 520 520 c high cat 1 -#> 521 521 c high cat 1 -#> 522 522 c high cat 1 -#> 523 523 c high cat 1 -#> 524 524 c high cat 0 -#> 525 525 c high cat 1 -#> 526 526 c high cat 1 -#> 527 527 c high cat 1 -#> 528 528 c high cat 0 -#> 529 529 c high cat 0 -#> 530 530 c high cat 0 -#> 531 531 c high cat 0 -#> 532 532 c high cat 0 -#> 533 533 c high cat 0 -#> 534 534 c high cat 1 -#> 535 535 c high cat 0 -#> 536 536 c high cat 0 -#> 537 537 c high cat 0 -#> 538 538 c high cat 0 -#> 539 539 c high cat 1 -#> 540 540 c high cat 0 -#> 541 541 c high cat 1 -#> 542 542 c high cat 0 -#> 543 543 c high cat 0 -#> 544 544 c high cat 1 -#> 545 545 c high cat 0 -#> 546 546 c high cat 0 -#> 547 547 c high cat 0 -#> 548 548 c high cat 1 -#> 549 549 c high cat 0 -#> 550 550 c high cat 0 -#> 551 551 c high cat 0 -#> 552 552 c high cat 1 -#> 553 553 c high cat 0 -#> 554 554 c high cat 0 -#> 555 555 c high cat 0 -#> 556 556 c high cat 1 -#> 557 557 c high cat 0 -#> 558 558 c high cat 1 -#> 559 559 c high cat 0 -#> 560 560 c high cat 0 -#> 561 561 c high cat 1 -#> 562 562 c high cat 1 -#> 563 563 c high cat 1 -#> 564 564 c high cat 1 -#> 565 565 c high cat 0 -#> 566 566 c high cat 0 -#> 567 567 c high cat 0 -#> 568 568 c high cat 0 -#> 569 569 c high cat 1 -#> 570 570 c high cat 1 -#> 571 571 c high cat 1 -#> 572 572 c high cat 1 -#> 573 573 c high cat 1 -#> 574 574 c high cat 0 -#> 575 575 c high cat 0 -#> 576 576 c high cat 1 -#> 577 577 c high cat 0 -#> 578 578 c high cat 1 -#> 579 579 c high cat 0 -#> 580 580 c high cat 1 -#> 581 581 c high cat 1 -#> 582 582 c high cat 0 -#> 583 583 c high cat 0 -#> 584 584 c high cat 0 -#> 585 585 c high cat 1 -#> 586 586 c high cat 0 -#> 587 587 c high cat 0 -#> 588 588 c high cat 0 -#> 589 589 c high cat 0 -#> 590 590 c high cat 1 -#> 591 591 c high cat 1 -#> 592 592 c high cat 0 -#> 593 593 c high cat 1 -#> 594 594 c high cat 1 -#> 595 595 c high cat 0 -#> 596 596 c high cat 0 -#> 597 597 c high cat 0 -#> 598 598 c high cat 0 -#> 599 599 c high cat 0 -#> 600 600 c high cat 0 -#> 601 601 a low dog 1 -#> 602 602 a low dog 1 -#> 603 603 a low dog 0 -#> 604 604 a low dog 0 -#> 605 605 a low dog 0 -#> 606 606 a low dog 0 -#> 607 607 a low dog 1 -#> 608 608 a low dog 1 -#> 609 609 a low dog 0 -#> 610 610 a low dog 1 -#> 611 611 a low dog 1 -#> 612 612 a low dog 1 -#> 613 613 a low dog 0 -#> 614 614 a low dog 1 -#> 615 615 a low dog 0 -#> 616 616 a low dog 0 -#> 617 617 a low dog 1 -#> 618 618 a low dog 0 -#> 619 619 a low dog 0 -#> 620 620 a low dog 1 -#> 621 621 a low dog 0 -#> 622 622 a low dog 0 -#> 623 623 a low dog 0 -#> 624 624 a low dog 1 -#> 625 625 a low dog 1 -#> 626 626 a low dog 1 -#> 627 627 a low dog 1 -#> 628 628 a low dog 1 -#> 629 629 a low dog 1 -#> 630 630 a low dog 1 -#> 631 631 a low dog 0 -#> 632 632 a low dog 1 -#> 633 633 a low dog 0 -#> 634 634 a low dog 0 -#> 635 635 a low dog 0 -#> 636 636 a low dog 1 -#> 637 637 a low dog 1 -#> 638 638 a low dog 0 -#> 639 639 a low dog 1 -#> 640 640 a low dog 0 -#> 641 641 a low dog 1 -#> 642 642 a low dog 0 -#> 643 643 a low dog 1 -#> 644 644 a low dog 1 -#> 645 645 a low dog 0 -#> 646 646 a low dog 1 -#> 647 647 a low dog 1 -#> 648 648 a low dog 0 -#> 649 649 a low dog 1 -#> 650 650 a low dog 1 -#> 651 651 a low dog 1 -#> 652 652 a low dog 1 -#> 653 653 a low dog 0 -#> 654 654 a low dog 0 -#> 655 655 a low dog 1 -#> 656 656 a low dog 1 -#> 657 657 a low dog 0 -#> 658 658 a low dog 1 -#> 659 659 a low dog 1 -#> 660 660 a low dog 1 -#> 661 661 a low dog 1 -#> 662 662 a low dog 1 -#> 663 663 a low dog 0 -#> 664 664 a low dog 1 -#> 665 665 a low dog 0 -#> 666 666 a low dog 0 -#> 667 667 a low dog 0 -#> 668 668 a low dog 1 -#> 669 669 a low dog 0 -#> 670 670 a low dog 1 -#> 671 671 a low dog 1 -#> 672 672 a low dog 0 -#> 673 673 a low dog 1 -#> 674 674 a low dog 0 -#> 675 675 a low dog 0 -#> 676 676 a low dog 1 -#> 677 677 a low dog 1 -#> 678 678 a low dog 0 -#> 679 679 a low dog 1 -#> 680 680 a low dog 1 -#> 681 681 a low dog 1 -#> 682 682 a low dog 1 -#> 683 683 a low dog 0 -#> 684 684 a low dog 0 -#> 685 685 a low dog 1 -#> 686 686 a low dog 0 -#> 687 687 a low dog 1 -#> 688 688 a low dog 0 -#> 689 689 a low dog 0 -#> 690 690 a low dog 1 -#> 691 691 a low dog 0 -#> 692 692 a low dog 0 -#> 693 693 a low dog 0 -#> 694 694 a low dog 1 -#> 695 695 a low dog 1 -#> 696 696 a low dog 1 -#> 697 697 a low dog 1 -#> 698 698 a low dog 0 -#> 699 699 a low dog 0 -#> 700 700 a low dog 1 -#> 701 701 b low dog 0 -#> 702 702 b low dog 0 -#> 703 703 b low dog 1 -#> 704 704 b low dog 1 -#> 705 705 b low dog 1 -#> 706 706 b low dog 0 -#> 707 707 b low dog 1 -#> 708 708 b low dog 1 -#> 709 709 b low dog 0 -#> 710 710 b low dog 0 -#> 711 711 b low dog 1 -#> 712 712 b low dog 0 -#> 713 713 b low dog 0 -#> 714 714 b low dog 0 -#> 715 715 b low dog 1 -#> 716 716 b low dog 0 -#> 717 717 b low dog 1 -#> 718 718 b low dog 1 -#> 719 719 b low dog 1 -#> 720 720 b low dog 1 -#> 721 721 b low dog 1 -#> 722 722 b low dog 0 -#> 723 723 b low dog 0 -#> 724 724 b low dog 1 -#> 725 725 b low dog 1 -#> 726 726 b low dog 1 -#> 727 727 b low dog 0 -#> 728 728 b low dog 0 -#> 729 729 b low dog 0 -#> 730 730 b low dog 0 -#> 731 731 b low dog 0 -#> 732 732 b low dog 1 -#> 733 733 b low dog 0 -#> 734 734 b low dog 0 -#> 735 735 b low dog 0 -#> 736 736 b low dog 0 -#> 737 737 b low dog 1 -#> 738 738 b low dog 1 -#> 739 739 b low dog 1 -#> 740 740 b low dog 1 -#> 741 741 b low dog 0 -#> 742 742 b low dog 0 -#> 743 743 b low dog 0 -#> 744 744 b low dog 0 -#> 745 745 b low dog 1 -#> 746 746 b low dog 0 -#> 747 747 b low dog 0 -#> 748 748 b low dog 0 -#> 749 749 b low dog 1 -#> 750 750 b low dog 1 -#> 751 751 b low dog 1 -#> 752 752 b low dog 0 -#> 753 753 b low dog 0 -#> 754 754 b low dog 0 -#> 755 755 b low dog 1 -#> 756 756 b low dog 1 -#> 757 757 b low dog 1 -#> 758 758 b low dog 1 -#> 759 759 b low dog 1 -#> 760 760 b low dog 1 -#> 761 761 b low dog 0 -#> 762 762 b low dog 1 -#> 763 763 b low dog 1 -#> 764 764 b low dog 0 -#> 765 765 b low dog 0 -#> 766 766 b low dog 0 -#> 767 767 b low dog 0 -#> 768 768 b low dog 1 -#> 769 769 b low dog 1 -#> 770 770 b low dog 0 -#> 771 771 b low dog 1 -#> 772 772 b low dog 1 -#> 773 773 b low dog 1 -#> 774 774 b low dog 0 -#> 775 775 b low dog 1 -#> 776 776 b low dog 1 -#> 777 777 b low dog 0 -#> 778 778 b low dog 1 -#> 779 779 b low dog 1 -#> 780 780 b low dog 1 -#> 781 781 b low dog 0 -#> 782 782 b low dog 0 -#> 783 783 b low dog 0 -#> 784 784 b low dog 1 -#> 785 785 b low dog 0 -#> 786 786 b low dog 0 -#> 787 787 b low dog 1 -#> 788 788 b low dog 0 -#> 789 789 b low dog 1 -#> 790 790 b low dog 0 -#> 791 791 b low dog 0 -#> 792 792 b low dog 0 -#> 793 793 b low dog 1 -#> 794 794 b low dog 1 -#> 795 795 b low dog 1 -#> 796 796 b low dog 0 -#> 797 797 b low dog 1 -#> 798 798 b low dog 0 -#> 799 799 b low dog 1 -#> 800 800 b low dog 0 -#> 801 801 c low dog 1 -#> 802 802 c low dog 1 -#> 803 803 c low dog 0 -#> 804 804 c low dog 1 -#> 805 805 c low dog 1 -#> 806 806 c low dog 0 -#> 807 807 c low dog 1 -#> 808 808 c low dog 1 -#> 809 809 c low dog 1 -#> 810 810 c low dog 0 -#> 811 811 c low dog 1 -#> 812 812 c low dog 1 -#> 813 813 c low dog 1 -#> 814 814 c low dog 0 -#> 815 815 c low dog 1 -#> 816 816 c low dog 0 -#> 817 817 c low dog 1 -#> 818 818 c low dog 0 -#> 819 819 c low dog 1 -#> 820 820 c low dog 1 -#> 821 821 c low dog 1 -#> 822 822 c low dog 0 -#> 823 823 c low dog 0 -#> 824 824 c low dog 1 -#> 825 825 c low dog 0 -#> 826 826 c low dog 0 -#> 827 827 c low dog 0 -#> 828 828 c low dog 0 -#> 829 829 c low dog 0 -#> 830 830 c low dog 1 -#> 831 831 c low dog 1 -#> 832 832 c low dog 1 -#> 833 833 c low dog 1 -#> 834 834 c low dog 1 -#> 835 835 c low dog 1 -#> 836 836 c low dog 0 -#> 837 837 c low dog 0 -#> 838 838 c low dog 0 -#> 839 839 c low dog 0 -#> 840 840 c low dog 0 -#> 841 841 c low dog 1 -#> 842 842 c low dog 0 -#> 843 843 c low dog 1 -#> 844 844 c low dog 0 -#> 845 845 c low dog 1 -#> 846 846 c low dog 0 -#> 847 847 c low dog 1 -#> 848 848 c low dog 1 -#> 849 849 c low dog 1 -#> 850 850 c low dog 0 -#> 851 851 c low dog 1 -#> 852 852 c low dog 0 -#> 853 853 c low dog 1 -#> 854 854 c low dog 1 -#> 855 855 c low dog 1 -#> 856 856 c low dog 1 -#> 857 857 c low dog 0 -#> 858 858 c low dog 0 -#> 859 859 c low dog 0 -#> 860 860 c low dog 1 -#> 861 861 c low dog 0 -#> 862 862 c low dog 0 -#> 863 863 c low dog 1 -#> 864 864 c low dog 0 -#> 865 865 c low dog 0 -#> 866 866 c low dog 1 -#> 867 867 c low dog 1 -#> 868 868 c low dog 1 -#> 869 869 c low dog 1 -#> 870 870 c low dog 0 -#> 871 871 c low dog 1 -#> 872 872 c low dog 1 -#> 873 873 c low dog 1 -#> 874 874 c low dog 1 -#> 875 875 c low dog 0 -#> 876 876 c low dog 1 -#> 877 877 c low dog 0 -#> 878 878 c low dog 0 -#> 879 879 c low dog 1 -#> 880 880 c low dog 0 -#> 881 881 c low dog 1 -#> 882 882 c low dog 1 -#> 883 883 c low dog 0 -#> 884 884 c low dog 1 -#> 885 885 c low dog 1 -#> 886 886 c low dog 1 -#> 887 887 c low dog 1 -#> 888 888 c low dog 1 -#> 889 889 c low dog 1 -#> 890 890 c low dog 0 -#> 891 891 c low dog 1 -#> 892 892 c low dog 1 -#> 893 893 c low dog 0 -#> 894 894 c low dog 1 -#> 895 895 c low dog 0 -#> 896 896 c low dog 0 -#> 897 897 c low dog 1 -#> 898 898 c low dog 0 -#> 899 899 c low dog 0 -#> 900 900 c low dog 1 -#> 901 901 a high dog 1 -#> 902 902 a high dog 0 -#> 903 903 a high dog 1 -#> 904 904 a high dog 0 -#> 905 905 a high dog 0 -#> 906 906 a high dog 0 -#> 907 907 a high dog 0 -#> 908 908 a high dog 0 -#> 909 909 a high dog 1 -#> 910 910 a high dog 1 -#> 911 911 a high dog 1 -#> 912 912 a high dog 1 -#> 913 913 a high dog 1 -#> 914 914 a high dog 0 -#> 915 915 a high dog 1 -#> 916 916 a high dog 1 -#> 917 917 a high dog 0 -#> 918 918 a high dog 1 -#> 919 919 a high dog 1 -#> 920 920 a high dog 0 -#> 921 921 a high dog 1 -#> 922 922 a high dog 0 -#> 923 923 a high dog 0 -#> 924 924 a high dog 0 -#> 925 925 a high dog 0 -#> 926 926 a high dog 1 -#> 927 927 a high dog 1 -#> 928 928 a high dog 0 -#> 929 929 a high dog 0 -#> 930 930 a high dog 1 -#> 931 931 a high dog 1 -#> 932 932 a high dog 1 -#> 933 933 a high dog 0 -#> 934 934 a high dog 0 -#> 935 935 a high dog 0 -#> 936 936 a high dog 1 -#> 937 937 a high dog 1 -#> 938 938 a high dog 1 -#> 939 939 a high dog 1 -#> 940 940 a high dog 1 -#> 941 941 a high dog 1 -#> 942 942 a high dog 0 -#> 943 943 a high dog 1 -#> 944 944 a high dog 0 -#> 945 945 a high dog 0 -#> 946 946 a high dog 0 -#> 947 947 a high dog 1 -#> 948 948 a high dog 1 -#> 949 949 a high dog 0 -#> 950 950 a high dog 1 -#> 951 951 a high dog 1 -#> 952 952 a high dog 1 -#> 953 953 a high dog 1 -#> 954 954 a high dog 1 -#> 955 955 a high dog 0 -#> 956 956 a high dog 1 -#> 957 957 a high dog 1 -#> 958 958 a high dog 1 -#> 959 959 a high dog 1 -#> 960 960 a high dog 0 -#> 961 961 a high dog 1 -#> 962 962 a high dog 0 -#> 963 963 a high dog 0 -#> 964 964 a high dog 0 -#> 965 965 a high dog 1 -#> 966 966 a high dog 1 -#> 967 967 a high dog 0 -#> 968 968 a high dog 1 -#> 969 969 a high dog 0 -#> 970 970 a high dog 0 -#> 971 971 a high dog 0 -#> 972 972 a high dog 1 -#> 973 973 a high dog 1 -#> 974 974 a high dog 0 -#> 975 975 a high dog 0 -#> 976 976 a high dog 0 -#> 977 977 a high dog 1 -#> 978 978 a high dog 0 -#> 979 979 a high dog 0 -#> 980 980 a high dog 1 -#> 981 981 a high dog 0 -#> 982 982 a high dog 1 -#> 983 983 a high dog 1 -#> 984 984 a high dog 0 -#> 985 985 a high dog 1 -#> 986 986 a high dog 0 -#> 987 987 a high dog 1 -#> 988 988 a high dog 0 -#> 989 989 a high dog 0 -#> 990 990 a high dog 1 -#> 991 991 a high dog 1 -#> 992 992 a high dog 1 -#> 993 993 a high dog 1 -#> 994 994 a high dog 1 -#> 995 995 a high dog 0 -#> 996 996 a high dog 0 -#> 997 997 a high dog 1 -#> 998 998 a high dog 0 -#> 999 999 a high dog 1 -#> 1000 1000 a high dog 1 -#> 1001 1001 b high dog 1 -#> 1002 1002 b high dog 1 -#> 1003 1003 b high dog 1 -#> 1004 1004 b high dog 0 -#> 1005 1005 b high dog 1 -#> 1006 1006 b high dog 0 -#> 1007 1007 b high dog 1 -#> 1008 1008 b high dog 1 -#> 1009 1009 b high dog 1 -#> 1010 1010 b high dog 0 -#> 1011 1011 b high dog 0 -#> 1012 1012 b high dog 1 -#> 1013 1013 b high dog 1 -#> 1014 1014 b high dog 1 -#> 1015 1015 b high dog 0 -#> 1016 1016 b high dog 1 -#> 1017 1017 b high dog 1 -#> 1018 1018 b high dog 0 -#> 1019 1019 b high dog 1 -#> 1020 1020 b high dog 0 -#> 1021 1021 b high dog 1 -#> 1022 1022 b high dog 1 -#> 1023 1023 b high dog 0 -#> 1024 1024 b high dog 1 -#> 1025 1025 b high dog 1 -#> 1026 1026 b high dog 1 -#> 1027 1027 b high dog 1 -#> 1028 1028 b high dog 1 -#> 1029 1029 b high dog 1 -#> 1030 1030 b high dog 0 -#> 1031 1031 b high dog 1 -#> 1032 1032 b high dog 1 -#> 1033 1033 b high dog 1 -#> 1034 1034 b high dog 0 -#> 1035 1035 b high dog 0 -#> 1036 1036 b high dog 0 -#> 1037 1037 b high dog 0 -#> 1038 1038 b high dog 1 -#> 1039 1039 b high dog 1 -#> 1040 1040 b high dog 0 -#> 1041 1041 b high dog 1 -#> 1042 1042 b high dog 0 -#> 1043 1043 b high dog 0 -#> 1044 1044 b high dog 0 -#> 1045 1045 b high dog 1 -#> 1046 1046 b high dog 1 -#> 1047 1047 b high dog 1 -#> 1048 1048 b high dog 0 -#> 1049 1049 b high dog 1 -#> 1050 1050 b high dog 1 -#> 1051 1051 b high dog 0 -#> 1052 1052 b high dog 0 -#> 1053 1053 b high dog 1 -#> 1054 1054 b high dog 0 -#> 1055 1055 b high dog 0 -#> 1056 1056 b high dog 1 -#> 1057 1057 b high dog 0 -#> 1058 1058 b high dog 0 -#> 1059 1059 b high dog 1 -#> 1060 1060 b high dog 1 -#> 1061 1061 b high dog 0 -#> 1062 1062 b high dog 0 -#> 1063 1063 b high dog 0 -#> 1064 1064 b high dog 0 -#> 1065 1065 b high dog 0 -#> 1066 1066 b high dog 1 -#> 1067 1067 b high dog 0 -#> 1068 1068 b high dog 1 -#> 1069 1069 b high dog 1 -#> 1070 1070 b high dog 0 -#> 1071 1071 b high dog 0 -#> 1072 1072 b high dog 0 -#> 1073 1073 b high dog 1 -#> 1074 1074 b high dog 0 -#> 1075 1075 b high dog 1 -#> 1076 1076 b high dog 0 -#> 1077 1077 b high dog 0 -#> 1078 1078 b high dog 0 -#> 1079 1079 b high dog 1 -#> 1080 1080 b high dog 0 -#> 1081 1081 b high dog 0 -#> 1082 1082 b high dog 0 -#> 1083 1083 b high dog 1 -#> 1084 1084 b high dog 0 -#> 1085 1085 b high dog 0 -#> 1086 1086 b high dog 0 -#> 1087 1087 b high dog 0 -#> 1088 1088 b high dog 0 -#> 1089 1089 b high dog 0 -#> 1090 1090 b high dog 1 -#> 1091 1091 b high dog 0 -#> 1092 1092 b high dog 1 -#> 1093 1093 b high dog 0 -#> 1094 1094 b high dog 1 -#> 1095 1095 b high dog 0 -#> 1096 1096 b high dog 0 -#> 1097 1097 b high dog 0 -#> 1098 1098 b high dog 1 -#> 1099 1099 b high dog 1 -#> 1100 1100 b high dog 1 -#> 1101 1101 c high dog 1 -#> 1102 1102 c high dog 0 -#> 1103 1103 c high dog 0 -#> 1104 1104 c high dog 1 -#> 1105 1105 c high dog 1 -#> 1106 1106 c high dog 1 -#> 1107 1107 c high dog 0 -#> 1108 1108 c high dog 0 -#> 1109 1109 c high dog 0 -#> 1110 1110 c high dog 0 -#> 1111 1111 c high dog 1 -#> 1112 1112 c high dog 0 -#> 1113 1113 c high dog 0 -#> 1114 1114 c high dog 0 -#> 1115 1115 c high dog 0 -#> 1116 1116 c high dog 0 -#> 1117 1117 c high dog 1 -#> 1118 1118 c high dog 1 -#> 1119 1119 c high dog 1 -#> 1120 1120 c high dog 0 -#> 1121 1121 c high dog 1 -#> 1122 1122 c high dog 1 -#> 1123 1123 c high dog 0 -#> 1124 1124 c high dog 0 -#> 1125 1125 c high dog 1 -#> 1126 1126 c high dog 1 -#> 1127 1127 c high dog 1 -#> 1128 1128 c high dog 0 -#> 1129 1129 c high dog 1 -#> 1130 1130 c high dog 1 -#> 1131 1131 c high dog 0 -#> 1132 1132 c high dog 1 -#> 1133 1133 c high dog 1 -#> 1134 1134 c high dog 1 -#> 1135 1135 c high dog 0 -#> 1136 1136 c high dog 1 -#> 1137 1137 c high dog 1 -#> 1138 1138 c high dog 1 -#> 1139 1139 c high dog 1 -#> 1140 1140 c high dog 0 -#> 1141 1141 c high dog 0 -#> 1142 1142 c high dog 1 -#> 1143 1143 c high dog 1 -#> 1144 1144 c high dog 1 -#> 1145 1145 c high dog 1 -#> 1146 1146 c high dog 0 -#> 1147 1147 c high dog 1 -#> 1148 1148 c high dog 1 -#> 1149 1149 c high dog 1 -#> 1150 1150 c high dog 1 -#> 1151 1151 c high dog 1 -#> 1152 1152 c high dog 1 -#> 1153 1153 c high dog 1 -#> 1154 1154 c high dog 1 -#> 1155 1155 c high dog 1 -#> 1156 1156 c high dog 1 -#> 1157 1157 c high dog 1 -#> 1158 1158 c high dog 0 -#> 1159 1159 c high dog 0 -#> 1160 1160 c high dog 0 -#> 1161 1161 c high dog 1 -#> 1162 1162 c high dog 1 -#> 1163 1163 c high dog 1 -#> 1164 1164 c high dog 1 -#> 1165 1165 c high dog 1 -#> 1166 1166 c high dog 0 -#> 1167 1167 c high dog 1 -#> 1168 1168 c high dog 0 -#> 1169 1169 c high dog 1 -#> 1170 1170 c high dog 0 -#> 1171 1171 c high dog 1 -#> 1172 1172 c high dog 1 -#> 1173 1173 c high dog 0 -#> 1174 1174 c high dog 0 -#> 1175 1175 c high dog 1 -#> 1176 1176 c high dog 0 -#> 1177 1177 c high dog 1 -#> 1178 1178 c high dog 0 -#> 1179 1179 c high dog 0 -#> 1180 1180 c high dog 1 -#> 1181 1181 c high dog 1 -#> 1182 1182 c high dog 1 -#> 1183 1183 c high dog 1 -#> 1184 1184 c high dog 1 -#> 1185 1185 c high dog 0 -#> 1186 1186 c high dog 1 -#> 1187 1187 c high dog 0 -#> 1188 1188 c high dog 1 -#> 1189 1189 c high dog 1 -#> 1190 1190 c high dog 1 -#> 1191 1191 c high dog 0 -#> 1192 1192 c high dog 1 -#> 1193 1193 c high dog 0 -#> 1194 1194 c high dog 0 -#> 1195 1195 c high dog 1 -#> 1196 1196 c high dog 1 -#> 1197 1197 c high dog 1 -#> 1198 1198 c high dog 1 -#> 1199 1199 c high dog 0 -#> 1200 1200 c high dog 0 +GRP( design, n = 30, props = rep(0.5,12) ) +#> id A B C s +#> 1 1 a low cat 1 +#> 2 2 a low cat 1 +#> 3 3 a low cat 1 +#> 4 4 a low cat 1 +#> 5 5 a low cat 1 +#> 6 6 a low cat 1 +#> 7 7 a low cat 1 +#> 8 8 a low cat 0 +#> 9 9 a low cat 0 +#> 10 10 a low cat 1 +#> 11 11 a low cat 0 +#> 12 12 a low cat 0 +#> 13 13 a low cat 0 +#> 14 14 a low cat 1 +#> 15 15 a low cat 1 +#> 16 16 a low cat 0 +#> 17 17 a low cat 0 +#> 18 18 a low cat 1 +#> 19 19 a low cat 1 +#> 20 20 a low cat 1 +#> 21 21 a low cat 1 +#> 22 22 a low cat 1 +#> 23 23 a low cat 1 +#> 24 24 a low cat 1 +#> 25 25 a low cat 0 +#> 26 26 a low cat 0 +#> 27 27 a low cat 1 +#> 28 28 a low cat 0 +#> 29 29 a low cat 1 +#> 30 30 a low cat 1 +#> 31 31 b low cat 1 +#> 32 32 b low cat 0 +#> 33 33 b low cat 1 +#> 34 34 b low cat 1 +#> 35 35 b low cat 0 +#> 36 36 b low cat 0 +#> 37 37 b low cat 0 +#> 38 38 b low cat 1 +#> 39 39 b low cat 0 +#> 40 40 b low cat 1 +#> 41 41 b low cat 0 +#> 42 42 b low cat 0 +#> 43 43 b low cat 1 +#> 44 44 b low cat 0 +#> 45 45 b low cat 0 +#> 46 46 b low cat 0 +#> 47 47 b low cat 1 +#> 48 48 b low cat 1 +#> 49 49 b low cat 1 +#> 50 50 b low cat 0 +#> 51 51 b low cat 1 +#> 52 52 b low cat 1 +#> 53 53 b low cat 1 +#> 54 54 b low cat 1 +#> 55 55 b low cat 0 +#> 56 56 b low cat 1 +#> 57 57 b low cat 0 +#> 58 58 b low cat 1 +#> 59 59 b low cat 0 +#> 60 60 b low cat 1 +#> 61 61 c low cat 0 +#> 62 62 c low cat 1 +#> 63 63 c low cat 0 +#> 64 64 c low cat 0 +#> 65 65 c low cat 1 +#> 66 66 c low cat 0 +#> 67 67 c low cat 1 +#> 68 68 c low cat 1 +#> 69 69 c low cat 1 +#> 70 70 c low cat 1 +#> 71 71 c low cat 0 +#> 72 72 c low cat 1 +#> 73 73 c low cat 1 +#> 74 74 c low cat 0 +#> 75 75 c low cat 1 +#> 76 76 c low cat 0 +#> 77 77 c low cat 1 +#> 78 78 c low cat 1 +#> 79 79 c low cat 1 +#> 80 80 c low cat 0 +#> 81 81 c low cat 0 +#> 82 82 c low cat 0 +#> 83 83 c low cat 1 +#> 84 84 c low cat 0 +#> 85 85 c low cat 0 +#> 86 86 c low cat 0 +#> 87 87 c low cat 0 +#> 88 88 c low cat 0 +#> 89 89 c low cat 1 +#> 90 90 c low cat 0 +#> 91 91 a high cat 1 +#> 92 92 a high cat 1 +#> 93 93 a high cat 0 +#> 94 94 a high cat 0 +#> 95 95 a high cat 0 +#> 96 96 a high cat 0 +#> 97 97 a high cat 1 +#> 98 98 a high cat 0 +#> 99 99 a high cat 0 +#> 100 100 a high cat 1 +#> 101 101 a high cat 1 +#> 102 102 a high cat 1 +#> 103 103 a high cat 1 +#> 104 104 a high cat 1 +#> 105 105 a high cat 1 +#> 106 106 a high cat 0 +#> 107 107 a high cat 0 +#> 108 108 a high cat 1 +#> 109 109 a high cat 0 +#> 110 110 a high cat 1 +#> 111 111 a high cat 0 +#> 112 112 a high cat 1 +#> 113 113 a high cat 0 +#> 114 114 a high cat 1 +#> 115 115 a high cat 0 +#> 116 116 a high cat 0 +#> 117 117 a high cat 1 +#> 118 118 a high cat 0 +#> 119 119 a high cat 1 +#> 120 120 a high cat 0 +#> 121 121 b high cat 1 +#> 122 122 b high cat 1 +#> 123 123 b high cat 1 +#> 124 124 b high cat 1 +#> 125 125 b high cat 1 +#> 126 126 b high cat 0 +#> 127 127 b high cat 0 +#> 128 128 b high cat 1 +#> 129 129 b high cat 1 +#> 130 130 b high cat 0 +#> 131 131 b high cat 1 +#> 132 132 b high cat 0 +#> 133 133 b high cat 1 +#> 134 134 b high cat 1 +#> 135 135 b high cat 1 +#> 136 136 b high cat 1 +#> 137 137 b high cat 0 +#> 138 138 b high cat 1 +#> 139 139 b high cat 0 +#> 140 140 b high cat 0 +#> 141 141 b high cat 0 +#> 142 142 b high cat 0 +#> 143 143 b high cat 1 +#> 144 144 b high cat 0 +#> 145 145 b high cat 0 +#> 146 146 b high cat 1 +#> 147 147 b high cat 1 +#> 148 148 b high cat 1 +#> 149 149 b high cat 0 +#> 150 150 b high cat 1 +#> 151 151 c high cat 0 +#> 152 152 c high cat 0 +#> 153 153 c high cat 0 +#> 154 154 c high cat 1 +#> 155 155 c high cat 1 +#> 156 156 c high cat 1 +#> 157 157 c high cat 0 +#> 158 158 c high cat 1 +#> 159 159 c high cat 1 +#> 160 160 c high cat 0 +#> 161 161 c high cat 0 +#> 162 162 c high cat 0 +#> 163 163 c high cat 0 +#> 164 164 c high cat 0 +#> 165 165 c high cat 0 +#> 166 166 c high cat 0 +#> 167 167 c high cat 1 +#> 168 168 c high cat 1 +#> 169 169 c high cat 1 +#> 170 170 c high cat 0 +#> 171 171 c high cat 0 +#> 172 172 c high cat 0 +#> 173 173 c high cat 0 +#> 174 174 c high cat 1 +#> 175 175 c high cat 0 +#> 176 176 c high cat 1 +#> 177 177 c high cat 0 +#> 178 178 c high cat 0 +#> 179 179 c high cat 1 +#> 180 180 c high cat 1 +#> 181 181 a low dog 1 +#> 182 182 a low dog 0 +#> 183 183 a low dog 1 +#> 184 184 a low dog 0 +#> 185 185 a low dog 0 +#> 186 186 a low dog 0 +#> 187 187 a low dog 0 +#> 188 188 a low dog 1 +#> 189 189 a low dog 1 +#> 190 190 a low dog 0 +#> 191 191 a low dog 0 +#> 192 192 a low dog 1 +#> 193 193 a low dog 1 +#> 194 194 a low dog 0 +#> 195 195 a low dog 0 +#> 196 196 a low dog 1 +#> 197 197 a low dog 1 +#> 198 198 a low dog 1 +#> 199 199 a low dog 0 +#> 200 200 a low dog 0 +#> 201 201 a low dog 1 +#> 202 202 a low dog 1 +#> 203 203 a low dog 1 +#> 204 204 a low dog 1 +#> 205 205 a low dog 1 +#> 206 206 a low dog 1 +#> 207 207 a low dog 1 +#> 208 208 a low dog 0 +#> 209 209 a low dog 0 +#> 210 210 a low dog 1 +#> 211 211 b low dog 0 +#> 212 212 b low dog 0 +#> 213 213 b low dog 0 +#> 214 214 b low dog 1 +#> 215 215 b low dog 1 +#> 216 216 b low dog 0 +#> 217 217 b low dog 0 +#> 218 218 b low dog 0 +#> 219 219 b low dog 0 +#> 220 220 b low dog 1 +#> 221 221 b low dog 0 +#> 222 222 b low dog 1 +#> 223 223 b low dog 0 +#> 224 224 b low dog 1 +#> 225 225 b low dog 0 +#> 226 226 b low dog 0 +#> 227 227 b low dog 0 +#> 228 228 b low dog 1 +#> 229 229 b low dog 0 +#> 230 230 b low dog 0 +#> 231 231 b low dog 0 +#> 232 232 b low dog 0 +#> 233 233 b low dog 0 +#> 234 234 b low dog 0 +#> 235 235 b low dog 0 +#> 236 236 b low dog 0 +#> 237 237 b low dog 0 +#> 238 238 b low dog 0 +#> 239 239 b low dog 1 +#> 240 240 b low dog 0 +#> 241 241 c low dog 0 +#> 242 242 c low dog 1 +#> 243 243 c low dog 1 +#> 244 244 c low dog 0 +#> 245 245 c low dog 1 +#> 246 246 c low dog 0 +#> 247 247 c low dog 0 +#> 248 248 c low dog 0 +#> 249 249 c low dog 0 +#> 250 250 c low dog 1 +#> 251 251 c low dog 1 +#> 252 252 c low dog 0 +#> 253 253 c low dog 1 +#> 254 254 c low dog 1 +#> 255 255 c low dog 1 +#> 256 256 c low dog 0 +#> 257 257 c low dog 0 +#> 258 258 c low dog 0 +#> 259 259 c low dog 0 +#> 260 260 c low dog 1 +#> 261 261 c low dog 0 +#> 262 262 c low dog 0 +#> 263 263 c low dog 0 +#> 264 264 c low dog 0 +#> 265 265 c low dog 0 +#> 266 266 c low dog 1 +#> 267 267 c low dog 1 +#> 268 268 c low dog 1 +#> 269 269 c low dog 0 +#> 270 270 c low dog 1 +#> 271 271 a high dog 0 +#> 272 272 a high dog 0 +#> 273 273 a high dog 1 +#> 274 274 a high dog 1 +#> 275 275 a high dog 1 +#> 276 276 a high dog 0 +#> 277 277 a high dog 1 +#> 278 278 a high dog 0 +#> 279 279 a high dog 1 +#> 280 280 a high dog 1 +#> 281 281 a high dog 0 +#> 282 282 a high dog 0 +#> 283 283 a high dog 0 +#> 284 284 a high dog 0 +#> 285 285 a high dog 0 +#> 286 286 a high dog 1 +#> 287 287 a high dog 1 +#> 288 288 a high dog 0 +#> 289 289 a high dog 1 +#> 290 290 a high dog 1 +#> 291 291 a high dog 1 +#> 292 292 a high dog 1 +#> 293 293 a high dog 0 +#> 294 294 a high dog 1 +#> 295 295 a high dog 0 +#> 296 296 a high dog 0 +#> 297 297 a high dog 1 +#> 298 298 a high dog 1 +#> 299 299 a high dog 0 +#> 300 300 a high dog 1 +#> 301 301 b high dog 0 +#> 302 302 b high dog 0 +#> 303 303 b high dog 0 +#> 304 304 b high dog 0 +#> 305 305 b high dog 0 +#> 306 306 b high dog 1 +#> 307 307 b high dog 1 +#> 308 308 b high dog 1 +#> 309 309 b high dog 1 +#> 310 310 b high dog 1 +#> 311 311 b high dog 0 +#> 312 312 b high dog 1 +#> 313 313 b high dog 1 +#> 314 314 b high dog 1 +#> 315 315 b high dog 1 +#> 316 316 b high dog 1 +#> 317 317 b high dog 0 +#> 318 318 b high dog 1 +#> 319 319 b high dog 1 +#> 320 320 b high dog 0 +#> 321 321 b high dog 1 +#> 322 322 b high dog 1 +#> 323 323 b high dog 0 +#> 324 324 b high dog 1 +#> 325 325 b high dog 1 +#> 326 326 b high dog 1 +#> 327 327 b high dog 1 +#> 328 328 b high dog 1 +#> 329 329 b high dog 0 +#> 330 330 b high dog 0 +#> 331 331 c high dog 0 +#> 332 332 c high dog 0 +#> 333 333 c high dog 1 +#> 334 334 c high dog 0 +#> 335 335 c high dog 0 +#> 336 336 c high dog 0 +#> 337 337 c high dog 0 +#> 338 338 c high dog 1 +#> 339 339 c high dog 1 +#> 340 340 c high dog 0 +#> 341 341 c high dog 0 +#> 342 342 c high dog 1 +#> 343 343 c high dog 0 +#> 344 344 c high dog 1 +#> 345 345 c high dog 1 +#> 346 346 c high dog 0 +#> 347 347 c high dog 1 +#> 348 348 c high dog 0 +#> 349 349 c high dog 1 +#> 350 350 c high dog 1 +#> 351 351 c high dog 1 +#> 352 352 c high dog 1 +#> 353 353 c high dog 1 +#> 354 354 c high dog 1 +#> 355 355 c high dog 0 +#> 356 356 c high dog 1 +#> 357 357 c high dog 1 +#> 358 358 c high dog 0 +#> 359 359 c high dog 0 +#> 360 360 c high dog 0 # To specify unequal probabilities, use design <- list( A=letters[1:3], B = c("low","high")) expProp <- c(.05, .05, .35, .35, .10, .10 ) -GRP( design, n = 100, props=expProp ) +GRP( design, n = 30, props=expProp ) #> id A B s #> 1 1 a low 0 #> 2 2 a low 0 @@ -1727,7 +887,7 @@

    Examples

    #> 7 7 a low 0 #> 8 8 a low 0 #> 9 9 a low 0 -#> 10 10 a low 0 +#> 10 10 a low 1 #> 11 11 a low 0 #> 12 12 a low 0 #> 13 13 a low 0 @@ -1748,579 +908,159 @@

    Examples

    #> 28 28 a low 0 #> 29 29 a low 0 #> 30 30 a low 0 -#> 31 31 a low 0 -#> 32 32 a low 0 -#> 33 33 a low 0 -#> 34 34 a low 0 -#> 35 35 a low 0 -#> 36 36 a low 0 -#> 37 37 a low 0 -#> 38 38 a low 0 -#> 39 39 a low 0 -#> 40 40 a low 0 -#> 41 41 a low 0 -#> 42 42 a low 0 -#> 43 43 a low 0 -#> 44 44 a low 0 -#> 45 45 a low 0 -#> 46 46 a low 0 -#> 47 47 a low 0 -#> 48 48 a low 0 -#> 49 49 a low 0 -#> 50 50 a low 0 -#> 51 51 a low 0 -#> 52 52 a low 0 -#> 53 53 a low 0 -#> 54 54 a low 0 -#> 55 55 a low 0 -#> 56 56 a low 0 -#> 57 57 a low 0 -#> 58 58 a low 0 -#> 59 59 a low 0 -#> 60 60 a low 0 -#> 61 61 a low 0 -#> 62 62 a low 0 -#> 63 63 a low 0 -#> 64 64 a low 0 -#> 65 65 a low 0 -#> 66 66 a low 0 -#> 67 67 a low 0 -#> 68 68 a low 0 -#> 69 69 a low 0 -#> 70 70 a low 0 -#> 71 71 a low 0 -#> 72 72 a low 0 -#> 73 73 a low 0 -#> 74 74 a low 0 -#> 75 75 a low 0 -#> 76 76 a low 0 -#> 77 77 a low 0 -#> 78 78 a low 0 -#> 79 79 a low 0 -#> 80 80 a low 0 -#> 81 81 a low 0 -#> 82 82 a low 0 -#> 83 83 a low 0 -#> 84 84 a low 0 -#> 85 85 a low 0 -#> 86 86 a low 0 -#> 87 87 a low 0 -#> 88 88 a low 0 -#> 89 89 a low 0 -#> 90 90 a low 0 -#> 91 91 a low 0 -#> 92 92 a low 1 -#> 93 93 a low 0 -#> 94 94 a low 0 -#> 95 95 a low 0 -#> 96 96 a low 0 -#> 97 97 a low 0 -#> 98 98 a low 0 -#> 99 99 a low 0 -#> 100 100 a low 0 -#> 101 101 b low 0 -#> 102 102 b low 0 -#> 103 103 b low 0 -#> 104 104 b low 0 -#> 105 105 b low 0 -#> 106 106 b low 0 -#> 107 107 b low 0 -#> 108 108 b low 0 -#> 109 109 b low 1 -#> 110 110 b low 0 -#> 111 111 b low 0 -#> 112 112 b low 0 -#> 113 113 b low 0 -#> 114 114 b low 0 -#> 115 115 b low 0 -#> 116 116 b low 0 -#> 117 117 b low 0 -#> 118 118 b low 0 -#> 119 119 b low 0 -#> 120 120 b low 0 -#> 121 121 b low 0 -#> 122 122 b low 0 -#> 123 123 b low 0 -#> 124 124 b low 0 -#> 125 125 b low 0 -#> 126 126 b low 0 -#> 127 127 b low 0 -#> 128 128 b low 0 -#> 129 129 b low 0 -#> 130 130 b low 0 -#> 131 131 b low 0 -#> 132 132 b low 0 -#> 133 133 b low 0 -#> 134 134 b low 0 -#> 135 135 b low 0 -#> 136 136 b low 0 -#> 137 137 b low 0 -#> 138 138 b low 0 -#> 139 139 b low 0 -#> 140 140 b low 0 -#> 141 141 b low 0 -#> 142 142 b low 0 -#> 143 143 b low 0 -#> 144 144 b low 0 -#> 145 145 b low 0 -#> 146 146 b low 0 -#> 147 147 b low 0 -#> 148 148 b low 0 -#> 149 149 b low 0 -#> 150 150 b low 0 -#> 151 151 b low 0 -#> 152 152 b low 0 -#> 153 153 b low 0 -#> 154 154 b low 0 -#> 155 155 b low 0 -#> 156 156 b low 0 -#> 157 157 b low 0 -#> 158 158 b low 0 -#> 159 159 b low 0 -#> 160 160 b low 0 -#> 161 161 b low 0 -#> 162 162 b low 0 -#> 163 163 b low 0 -#> 164 164 b low 0 -#> 165 165 b low 0 -#> 166 166 b low 0 -#> 167 167 b low 0 -#> 168 168 b low 0 -#> 169 169 b low 0 -#> 170 170 b low 0 -#> 171 171 b low 0 -#> 172 172 b low 0 -#> 173 173 b low 0 -#> 174 174 b low 1 -#> 175 175 b low 0 -#> 176 176 b low 0 -#> 177 177 b low 0 -#> 178 178 b low 0 -#> 179 179 b low 0 -#> 180 180 b low 0 -#> 181 181 b low 0 -#> 182 182 b low 0 -#> 183 183 b low 0 -#> 184 184 b low 0 -#> 185 185 b low 0 -#> 186 186 b low 0 -#> 187 187 b low 0 -#> 188 188 b low 0 -#> 189 189 b low 0 -#> 190 190 b low 0 -#> 191 191 b low 0 -#> 192 192 b low 0 -#> 193 193 b low 0 -#> 194 194 b low 0 -#> 195 195 b low 0 -#> 196 196 b low 0 -#> 197 197 b low 0 -#> 198 198 b low 0 -#> 199 199 b low 0 -#> 200 200 b low 0 -#> 201 201 c low 1 -#> 202 202 c low 0 -#> 203 203 c low 0 -#> 204 204 c low 0 -#> 205 205 c low 1 -#> 206 206 c low 1 -#> 207 207 c low 0 -#> 208 208 c low 0 -#> 209 209 c low 0 -#> 210 210 c low 0 -#> 211 211 c low 0 -#> 212 212 c low 0 -#> 213 213 c low 0 -#> 214 214 c low 0 -#> 215 215 c low 0 -#> 216 216 c low 1 -#> 217 217 c low 1 -#> 218 218 c low 0 -#> 219 219 c low 0 -#> 220 220 c low 1 -#> 221 221 c low 0 -#> 222 222 c low 0 -#> 223 223 c low 1 -#> 224 224 c low 0 -#> 225 225 c low 0 -#> 226 226 c low 0 -#> 227 227 c low 0 -#> 228 228 c low 0 -#> 229 229 c low 0 -#> 230 230 c low 0 -#> 231 231 c low 0 -#> 232 232 c low 0 -#> 233 233 c low 0 -#> 234 234 c low 0 -#> 235 235 c low 0 -#> 236 236 c low 1 -#> 237 237 c low 1 -#> 238 238 c low 1 -#> 239 239 c low 0 -#> 240 240 c low 1 -#> 241 241 c low 0 -#> 242 242 c low 0 -#> 243 243 c low 1 -#> 244 244 c low 0 -#> 245 245 c low 0 -#> 246 246 c low 1 -#> 247 247 c low 0 -#> 248 248 c low 0 -#> 249 249 c low 0 -#> 250 250 c low 0 -#> 251 251 c low 0 -#> 252 252 c low 0 -#> 253 253 c low 0 -#> 254 254 c low 1 -#> 255 255 c low 0 -#> 256 256 c low 0 -#> 257 257 c low 0 -#> 258 258 c low 1 -#> 259 259 c low 1 -#> 260 260 c low 0 -#> 261 261 c low 0 -#> 262 262 c low 0 -#> 263 263 c low 1 -#> 264 264 c low 0 -#> 265 265 c low 0 -#> 266 266 c low 0 -#> 267 267 c low 0 -#> 268 268 c low 0 -#> 269 269 c low 0 -#> 270 270 c low 0 -#> 271 271 c low 1 -#> 272 272 c low 1 -#> 273 273 c low 1 -#> 274 274 c low 1 -#> 275 275 c low 0 -#> 276 276 c low 0 -#> 277 277 c low 1 -#> 278 278 c low 1 -#> 279 279 c low 0 -#> 280 280 c low 0 -#> 281 281 c low 1 -#> 282 282 c low 0 -#> 283 283 c low 0 -#> 284 284 c low 1 -#> 285 285 c low 0 -#> 286 286 c low 1 -#> 287 287 c low 0 -#> 288 288 c low 0 -#> 289 289 c low 0 -#> 290 290 c low 0 -#> 291 291 c low 0 -#> 292 292 c low 0 -#> 293 293 c low 1 -#> 294 294 c low 0 -#> 295 295 c low 1 -#> 296 296 c low 1 -#> 297 297 c low 1 -#> 298 298 c low 0 -#> 299 299 c low 1 -#> 300 300 c low 0 -#> 301 301 a high 0 -#> 302 302 a high 1 -#> 303 303 a high 1 -#> 304 304 a high 1 -#> 305 305 a high 0 -#> 306 306 a high 0 -#> 307 307 a high 1 -#> 308 308 a high 1 -#> 309 309 a high 0 -#> 310 310 a high 0 -#> 311 311 a high 0 -#> 312 312 a high 0 -#> 313 313 a high 1 -#> 314 314 a high 1 -#> 315 315 a high 0 -#> 316 316 a high 1 -#> 317 317 a high 0 -#> 318 318 a high 0 -#> 319 319 a high 0 -#> 320 320 a high 0 -#> 321 321 a high 0 -#> 322 322 a high 0 -#> 323 323 a high 0 -#> 324 324 a high 0 -#> 325 325 a high 1 -#> 326 326 a high 1 -#> 327 327 a high 1 -#> 328 328 a high 0 -#> 329 329 a high 0 -#> 330 330 a high 0 -#> 331 331 a high 0 -#> 332 332 a high 0 -#> 333 333 a high 0 -#> 334 334 a high 1 -#> 335 335 a high 0 -#> 336 336 a high 0 -#> 337 337 a high 0 -#> 338 338 a high 1 -#> 339 339 a high 0 -#> 340 340 a high 0 -#> 341 341 a high 0 -#> 342 342 a high 0 -#> 343 343 a high 0 -#> 344 344 a high 0 -#> 345 345 a high 0 -#> 346 346 a high 1 -#> 347 347 a high 0 -#> 348 348 a high 0 -#> 349 349 a high 0 -#> 350 350 a high 0 -#> 351 351 a high 0 -#> 352 352 a high 0 -#> 353 353 a high 1 -#> 354 354 a high 0 -#> 355 355 a high 0 -#> 356 356 a high 1 -#> 357 357 a high 1 -#> 358 358 a high 0 -#> 359 359 a high 0 -#> 360 360 a high 0 -#> 361 361 a high 1 -#> 362 362 a high 0 -#> 363 363 a high 0 -#> 364 364 a high 0 -#> 365 365 a high 1 -#> 366 366 a high 0 -#> 367 367 a high 0 -#> 368 368 a high 0 -#> 369 369 a high 1 -#> 370 370 a high 1 -#> 371 371 a high 1 -#> 372 372 a high 0 -#> 373 373 a high 0 -#> 374 374 a high 0 -#> 375 375 a high 0 -#> 376 376 a high 1 -#> 377 377 a high 0 -#> 378 378 a high 1 -#> 379 379 a high 0 -#> 380 380 a high 1 -#> 381 381 a high 1 -#> 382 382 a high 0 -#> 383 383 a high 1 -#> 384 384 a high 0 -#> 385 385 a high 0 -#> 386 386 a high 0 -#> 387 387 a high 0 -#> 388 388 a high 0 -#> 389 389 a high 1 -#> 390 390 a high 0 -#> 391 391 a high 0 -#> 392 392 a high 1 -#> 393 393 a high 1 -#> 394 394 a high 1 -#> 395 395 a high 0 -#> 396 396 a high 1 -#> 397 397 a high 0 -#> 398 398 a high 0 -#> 399 399 a high 0 -#> 400 400 a high 1 -#> 401 401 b high 0 -#> 402 402 b high 0 -#> 403 403 b high 0 -#> 404 404 b high 0 -#> 405 405 b high 0 -#> 406 406 b high 0 -#> 407 407 b high 0 -#> 408 408 b high 0 -#> 409 409 b high 0 -#> 410 410 b high 0 -#> 411 411 b high 1 -#> 412 412 b high 0 -#> 413 413 b high 0 -#> 414 414 b high 0 -#> 415 415 b high 0 -#> 416 416 b high 0 -#> 417 417 b high 0 -#> 418 418 b high 0 -#> 419 419 b high 0 -#> 420 420 b high 0 -#> 421 421 b high 0 -#> 422 422 b high 0 -#> 423 423 b high 0 -#> 424 424 b high 0 -#> 425 425 b high 0 -#> 426 426 b high 0 -#> 427 427 b high 0 -#> 428 428 b high 1 -#> 429 429 b high 0 -#> 430 430 b high 0 -#> 431 431 b high 0 -#> 432 432 b high 0 -#> 433 433 b high 0 -#> 434 434 b high 0 -#> 435 435 b high 0 -#> 436 436 b high 0 -#> 437 437 b high 0 -#> 438 438 b high 0 -#> 439 439 b high 0 -#> 440 440 b high 0 -#> 441 441 b high 0 -#> 442 442 b high 0 -#> 443 443 b high 0 -#> 444 444 b high 0 -#> 445 445 b high 0 -#> 446 446 b high 0 -#> 447 447 b high 0 -#> 448 448 b high 0 -#> 449 449 b high 0 -#> 450 450 b high 0 -#> 451 451 b high 0 -#> 452 452 b high 0 -#> 453 453 b high 1 -#> 454 454 b high 0 -#> 455 455 b high 0 -#> 456 456 b high 0 -#> 457 457 b high 0 -#> 458 458 b high 0 -#> 459 459 b high 0 -#> 460 460 b high 0 -#> 461 461 b high 0 -#> 462 462 b high 0 -#> 463 463 b high 0 -#> 464 464 b high 0 -#> 465 465 b high 0 -#> 466 466 b high 0 -#> 467 467 b high 0 -#> 468 468 b high 0 -#> 469 469 b high 0 -#> 470 470 b high 0 -#> 471 471 b high 0 -#> 472 472 b high 0 -#> 473 473 b high 0 -#> 474 474 b high 0 -#> 475 475 b high 0 -#> 476 476 b high 0 -#> 477 477 b high 0 -#> 478 478 b high 0 -#> 479 479 b high 0 -#> 480 480 b high 0 -#> 481 481 b high 0 -#> 482 482 b high 0 -#> 483 483 b high 0 -#> 484 484 b high 0 -#> 485 485 b high 0 -#> 486 486 b high 0 -#> 487 487 b high 0 -#> 488 488 b high 0 -#> 489 489 b high 0 -#> 490 490 b high 0 -#> 491 491 b high 0 -#> 492 492 b high 0 -#> 493 493 b high 0 -#> 494 494 b high 0 -#> 495 495 b high 0 -#> 496 496 b high 0 -#> 497 497 b high 0 -#> 498 498 b high 0 -#> 499 499 b high 0 -#> 500 500 b high 0 -#> 501 501 c high 0 -#> 502 502 c high 0 -#> 503 503 c high 0 -#> 504 504 c high 0 -#> 505 505 c high 0 -#> 506 506 c high 0 -#> 507 507 c high 0 -#> 508 508 c high 0 -#> 509 509 c high 0 -#> 510 510 c high 0 -#> 511 511 c high 0 -#> 512 512 c high 0 -#> 513 513 c high 0 -#> 514 514 c high 0 -#> 515 515 c high 0 -#> 516 516 c high 0 -#> 517 517 c high 0 -#> 518 518 c high 0 -#> 519 519 c high 0 -#> 520 520 c high 0 -#> 521 521 c high 1 -#> 522 522 c high 0 -#> 523 523 c high 0 -#> 524 524 c high 0 -#> 525 525 c high 0 -#> 526 526 c high 0 -#> 527 527 c high 0 -#> 528 528 c high 0 -#> 529 529 c high 0 -#> 530 530 c high 0 -#> 531 531 c high 0 -#> 532 532 c high 0 -#> 533 533 c high 0 -#> 534 534 c high 0 -#> 535 535 c high 0 -#> 536 536 c high 0 -#> 537 537 c high 0 -#> 538 538 c high 0 -#> 539 539 c high 0 -#> 540 540 c high 0 -#> 541 541 c high 0 -#> 542 542 c high 0 -#> 543 543 c high 0 -#> 544 544 c high 0 -#> 545 545 c high 0 -#> 546 546 c high 0 -#> 547 547 c high 0 -#> 548 548 c high 0 -#> 549 549 c high 1 -#> 550 550 c high 1 -#> 551 551 c high 0 -#> 552 552 c high 0 -#> 553 553 c high 0 -#> 554 554 c high 0 -#> 555 555 c high 0 -#> 556 556 c high 0 -#> 557 557 c high 0 -#> 558 558 c high 1 -#> 559 559 c high 0 -#> 560 560 c high 0 -#> 561 561 c high 0 -#> 562 562 c high 0 -#> 563 563 c high 0 -#> 564 564 c high 0 -#> 565 565 c high 0 -#> 566 566 c high 0 -#> 567 567 c high 0 -#> 568 568 c high 0 -#> 569 569 c high 0 -#> 570 570 c high 0 -#> 571 571 c high 0 -#> 572 572 c high 0 -#> 573 573 c high 1 -#> 574 574 c high 0 -#> 575 575 c high 0 -#> 576 576 c high 0 -#> 577 577 c high 0 -#> 578 578 c high 0 -#> 579 579 c high 0 -#> 580 580 c high 1 -#> 581 581 c high 0 -#> 582 582 c high 0 -#> 583 583 c high 0 -#> 584 584 c high 0 -#> 585 585 c high 0 -#> 586 586 c high 0 -#> 587 587 c high 0 -#> 588 588 c high 0 -#> 589 589 c high 1 -#> 590 590 c high 0 -#> 591 591 c high 0 -#> 592 592 c high 0 -#> 593 593 c high 0 -#> 594 594 c high 0 -#> 595 595 c high 0 -#> 596 596 c high 0 -#> 597 597 c high 0 -#> 598 598 c high 0 -#> 599 599 c high 0 -#> 600 600 c high 0 +#> 31 31 b low 0 +#> 32 32 b low 0 +#> 33 33 b low 0 +#> 34 34 b low 0 +#> 35 35 b low 0 +#> 36 36 b low 0 +#> 37 37 b low 1 +#> 38 38 b low 0 +#> 39 39 b low 0 +#> 40 40 b low 0 +#> 41 41 b low 0 +#> 42 42 b low 0 +#> 43 43 b low 0 +#> 44 44 b low 0 +#> 45 45 b low 0 +#> 46 46 b low 0 +#> 47 47 b low 0 +#> 48 48 b low 0 +#> 49 49 b low 0 +#> 50 50 b low 0 +#> 51 51 b low 0 +#> 52 52 b low 0 +#> 53 53 b low 0 +#> 54 54 b low 1 +#> 55 55 b low 0 +#> 56 56 b low 0 +#> 57 57 b low 0 +#> 58 58 b low 0 +#> 59 59 b low 0 +#> 60 60 b low 0 +#> 61 61 c low 1 +#> 62 62 c low 0 +#> 63 63 c low 0 +#> 64 64 c low 1 +#> 65 65 c low 0 +#> 66 66 c low 1 +#> 67 67 c low 0 +#> 68 68 c low 0 +#> 69 69 c low 0 +#> 70 70 c low 1 +#> 71 71 c low 1 +#> 72 72 c low 0 +#> 73 73 c low 0 +#> 74 74 c low 0 +#> 75 75 c low 0 +#> 76 76 c low 0 +#> 77 77 c low 1 +#> 78 78 c low 0 +#> 79 79 c low 0 +#> 80 80 c low 0 +#> 81 81 c low 0 +#> 82 82 c low 0 +#> 83 83 c low 0 +#> 84 84 c low 0 +#> 85 85 c low 1 +#> 86 86 c low 0 +#> 87 87 c low 1 +#> 88 88 c low 0 +#> 89 89 c low 0 +#> 90 90 c low 0 +#> 91 91 a high 0 +#> 92 92 a high 0 +#> 93 93 a high 1 +#> 94 94 a high 0 +#> 95 95 a high 0 +#> 96 96 a high 0 +#> 97 97 a high 0 +#> 98 98 a high 0 +#> 99 99 a high 0 +#> 100 100 a high 0 +#> 101 101 a high 1 +#> 102 102 a high 0 +#> 103 103 a high 0 +#> 104 104 a high 1 +#> 105 105 a high 1 +#> 106 106 a high 0 +#> 107 107 a high 0 +#> 108 108 a high 1 +#> 109 109 a high 0 +#> 110 110 a high 1 +#> 111 111 a high 0 +#> 112 112 a high 0 +#> 113 113 a high 0 +#> 114 114 a high 1 +#> 115 115 a high 1 +#> 116 116 a high 0 +#> 117 117 a high 1 +#> 118 118 a high 0 +#> 119 119 a high 0 +#> 120 120 a high 0 +#> 121 121 b high 0 +#> 122 122 b high 0 +#> 123 123 b high 0 +#> 124 124 b high 0 +#> 125 125 b high 0 +#> 126 126 b high 0 +#> 127 127 b high 0 +#> 128 128 b high 0 +#> 129 129 b high 0 +#> 130 130 b high 0 +#> 131 131 b high 0 +#> 132 132 b high 1 +#> 133 133 b high 0 +#> 134 134 b high 0 +#> 135 135 b high 0 +#> 136 136 b high 0 +#> 137 137 b high 0 +#> 138 138 b high 0 +#> 139 139 b high 0 +#> 140 140 b high 1 +#> 141 141 b high 0 +#> 142 142 b high 0 +#> 143 143 b high 0 +#> 144 144 b high 1 +#> 145 145 b high 0 +#> 146 146 b high 0 +#> 147 147 b high 0 +#> 148 148 b high 0 +#> 149 149 b high 0 +#> 150 150 b high 0 +#> 151 151 c high 0 +#> 152 152 c high 0 +#> 153 153 c high 0 +#> 154 154 c high 0 +#> 155 155 c high 0 +#> 156 156 c high 0 +#> 157 157 c high 0 +#> 158 158 c high 0 +#> 159 159 c high 0 +#> 160 160 c high 0 +#> 161 161 c high 0 +#> 162 162 c high 1 +#> 163 163 c high 0 +#> 164 164 c high 0 +#> 165 165 c high 0 +#> 166 166 c high 1 +#> 167 167 c high 0 +#> 168 168 c high 0 +#> 169 169 c high 0 +#> 170 170 c high 0 +#> 171 171 c high 0 +#> 172 172 c high 0 +#> 173 173 c high 0 +#> 174 174 c high 0 +#> 175 175 c high 0 +#> 176 176 c high 0 +#> 177 177 c high 0 +#> 178 178 c high 0 +#> 179 179 c high 0 +#> 180 180 c high 0 # The name of the column containing the proportions can be changed -GRP( design, n=100, props=expProp, sname="patate") +GRP( design, n=30, props=expProp, sname="patate") #> id A B patate #> 1 1 a low 0 #> 2 2 a low 0 @@ -2332,7 +1072,7 @@

    Examples

    #> 8 8 a low 0 #> 9 9 a low 0 #> 10 10 a low 0 -#> 11 11 a low 1 +#> 11 11 a low 0 #> 12 12 a low 0 #> 13 13 a low 0 #> 14 14 a low 0 @@ -2341,10 +1081,10 @@

    Examples

    #> 17 17 a low 0 #> 18 18 a low 0 #> 19 19 a low 0 -#> 20 20 a low 0 +#> 20 20 a low 1 #> 21 21 a low 0 #> 22 22 a low 0 -#> 23 23 a low 0 +#> 23 23 a low 1 #> 24 24 a low 0 #> 25 25 a low 0 #> 26 26 a low 0 @@ -2352,581 +1092,161 @@

    Examples

    #> 28 28 a low 0 #> 29 29 a low 0 #> 30 30 a low 0 -#> 31 31 a low 0 -#> 32 32 a low 0 -#> 33 33 a low 0 -#> 34 34 a low 0 -#> 35 35 a low 0 -#> 36 36 a low 0 -#> 37 37 a low 0 -#> 38 38 a low 1 -#> 39 39 a low 0 -#> 40 40 a low 0 -#> 41 41 a low 0 -#> 42 42 a low 0 -#> 43 43 a low 0 -#> 44 44 a low 0 -#> 45 45 a low 0 -#> 46 46 a low 0 -#> 47 47 a low 0 -#> 48 48 a low 0 -#> 49 49 a low 0 -#> 50 50 a low 0 -#> 51 51 a low 0 -#> 52 52 a low 0 -#> 53 53 a low 0 -#> 54 54 a low 0 -#> 55 55 a low 0 -#> 56 56 a low 1 -#> 57 57 a low 1 -#> 58 58 a low 0 -#> 59 59 a low 0 -#> 60 60 a low 0 -#> 61 61 a low 0 -#> 62 62 a low 0 -#> 63 63 a low 0 -#> 64 64 a low 0 -#> 65 65 a low 0 -#> 66 66 a low 0 -#> 67 67 a low 0 -#> 68 68 a low 0 -#> 69 69 a low 0 -#> 70 70 a low 0 -#> 71 71 a low 0 -#> 72 72 a low 0 -#> 73 73 a low 0 -#> 74 74 a low 0 -#> 75 75 a low 0 -#> 76 76 a low 0 -#> 77 77 a low 0 -#> 78 78 a low 1 -#> 79 79 a low 0 -#> 80 80 a low 0 -#> 81 81 a low 0 -#> 82 82 a low 0 -#> 83 83 a low 0 -#> 84 84 a low 0 -#> 85 85 a low 0 -#> 86 86 a low 0 -#> 87 87 a low 0 -#> 88 88 a low 0 -#> 89 89 a low 0 -#> 90 90 a low 1 -#> 91 91 a low 0 -#> 92 92 a low 0 -#> 93 93 a low 0 -#> 94 94 a low 0 -#> 95 95 a low 0 -#> 96 96 a low 0 -#> 97 97 a low 0 -#> 98 98 a low 0 -#> 99 99 a low 0 -#> 100 100 a low 0 -#> 101 101 b low 0 -#> 102 102 b low 0 -#> 103 103 b low 0 -#> 104 104 b low 1 -#> 105 105 b low 0 -#> 106 106 b low 0 -#> 107 107 b low 0 -#> 108 108 b low 0 -#> 109 109 b low 0 -#> 110 110 b low 0 -#> 111 111 b low 0 -#> 112 112 b low 0 -#> 113 113 b low 0 -#> 114 114 b low 0 -#> 115 115 b low 0 -#> 116 116 b low 0 -#> 117 117 b low 0 -#> 118 118 b low 0 -#> 119 119 b low 0 -#> 120 120 b low 0 -#> 121 121 b low 0 -#> 122 122 b low 0 -#> 123 123 b low 0 -#> 124 124 b low 0 -#> 125 125 b low 0 -#> 126 126 b low 0 -#> 127 127 b low 0 -#> 128 128 b low 0 -#> 129 129 b low 0 -#> 130 130 b low 0 -#> 131 131 b low 0 -#> 132 132 b low 0 -#> 133 133 b low 0 -#> 134 134 b low 0 -#> 135 135 b low 0 -#> 136 136 b low 0 -#> 137 137 b low 0 -#> 138 138 b low 0 -#> 139 139 b low 0 -#> 140 140 b low 0 -#> 141 141 b low 0 -#> 142 142 b low 0 -#> 143 143 b low 0 -#> 144 144 b low 0 -#> 145 145 b low 0 -#> 146 146 b low 0 -#> 147 147 b low 0 -#> 148 148 b low 0 -#> 149 149 b low 0 -#> 150 150 b low 0 -#> 151 151 b low 0 -#> 152 152 b low 0 -#> 153 153 b low 0 -#> 154 154 b low 0 -#> 155 155 b low 0 -#> 156 156 b low 0 -#> 157 157 b low 0 -#> 158 158 b low 0 -#> 159 159 b low 1 -#> 160 160 b low 0 -#> 161 161 b low 0 -#> 162 162 b low 1 -#> 163 163 b low 0 -#> 164 164 b low 0 -#> 165 165 b low 0 -#> 166 166 b low 0 -#> 167 167 b low 1 -#> 168 168 b low 0 -#> 169 169 b low 0 -#> 170 170 b low 0 -#> 171 171 b low 0 -#> 172 172 b low 0 -#> 173 173 b low 0 -#> 174 174 b low 0 -#> 175 175 b low 0 -#> 176 176 b low 0 -#> 177 177 b low 0 -#> 178 178 b low 0 -#> 179 179 b low 0 -#> 180 180 b low 0 -#> 181 181 b low 0 -#> 182 182 b low 0 -#> 183 183 b low 0 -#> 184 184 b low 0 -#> 185 185 b low 0 -#> 186 186 b low 0 -#> 187 187 b low 1 -#> 188 188 b low 1 -#> 189 189 b low 0 -#> 190 190 b low 0 -#> 191 191 b low 0 -#> 192 192 b low 0 -#> 193 193 b low 0 -#> 194 194 b low 0 -#> 195 195 b low 0 -#> 196 196 b low 0 -#> 197 197 b low 0 -#> 198 198 b low 0 -#> 199 199 b low 0 -#> 200 200 b low 0 -#> 201 201 c low 0 -#> 202 202 c low 0 -#> 203 203 c low 1 -#> 204 204 c low 0 -#> 205 205 c low 0 -#> 206 206 c low 1 -#> 207 207 c low 1 -#> 208 208 c low 1 -#> 209 209 c low 0 -#> 210 210 c low 1 -#> 211 211 c low 0 -#> 212 212 c low 1 -#> 213 213 c low 0 -#> 214 214 c low 0 -#> 215 215 c low 0 -#> 216 216 c low 0 -#> 217 217 c low 0 -#> 218 218 c low 0 -#> 219 219 c low 0 -#> 220 220 c low 1 -#> 221 221 c low 0 -#> 222 222 c low 0 -#> 223 223 c low 1 -#> 224 224 c low 0 -#> 225 225 c low 0 -#> 226 226 c low 1 -#> 227 227 c low 1 -#> 228 228 c low 0 -#> 229 229 c low 1 -#> 230 230 c low 1 -#> 231 231 c low 0 -#> 232 232 c low 1 -#> 233 233 c low 0 -#> 234 234 c low 1 -#> 235 235 c low 1 -#> 236 236 c low 1 -#> 237 237 c low 0 -#> 238 238 c low 0 -#> 239 239 c low 1 -#> 240 240 c low 0 -#> 241 241 c low 0 -#> 242 242 c low 0 -#> 243 243 c low 0 -#> 244 244 c low 0 -#> 245 245 c low 1 -#> 246 246 c low 0 -#> 247 247 c low 0 -#> 248 248 c low 0 -#> 249 249 c low 0 -#> 250 250 c low 1 -#> 251 251 c low 0 -#> 252 252 c low 0 -#> 253 253 c low 1 -#> 254 254 c low 0 -#> 255 255 c low 1 -#> 256 256 c low 0 -#> 257 257 c low 0 -#> 258 258 c low 1 -#> 259 259 c low 0 -#> 260 260 c low 1 -#> 261 261 c low 0 -#> 262 262 c low 1 -#> 263 263 c low 0 -#> 264 264 c low 0 -#> 265 265 c low 1 -#> 266 266 c low 1 -#> 267 267 c low 0 -#> 268 268 c low 0 -#> 269 269 c low 1 -#> 270 270 c low 1 -#> 271 271 c low 0 -#> 272 272 c low 0 -#> 273 273 c low 1 -#> 274 274 c low 1 -#> 275 275 c low 1 -#> 276 276 c low 0 -#> 277 277 c low 1 -#> 278 278 c low 0 -#> 279 279 c low 0 -#> 280 280 c low 1 -#> 281 281 c low 0 -#> 282 282 c low 0 -#> 283 283 c low 1 -#> 284 284 c low 0 -#> 285 285 c low 0 -#> 286 286 c low 1 -#> 287 287 c low 1 -#> 288 288 c low 1 -#> 289 289 c low 1 -#> 290 290 c low 0 -#> 291 291 c low 0 -#> 292 292 c low 0 -#> 293 293 c low 0 -#> 294 294 c low 0 -#> 295 295 c low 1 -#> 296 296 c low 1 -#> 297 297 c low 0 -#> 298 298 c low 1 -#> 299 299 c low 1 -#> 300 300 c low 0 -#> 301 301 a high 0 -#> 302 302 a high 0 -#> 303 303 a high 0 -#> 304 304 a high 0 -#> 305 305 a high 0 -#> 306 306 a high 0 -#> 307 307 a high 0 -#> 308 308 a high 0 -#> 309 309 a high 1 -#> 310 310 a high 0 -#> 311 311 a high 1 -#> 312 312 a high 0 -#> 313 313 a high 0 -#> 314 314 a high 0 -#> 315 315 a high 1 -#> 316 316 a high 0 -#> 317 317 a high 0 -#> 318 318 a high 0 -#> 319 319 a high 1 -#> 320 320 a high 0 -#> 321 321 a high 1 -#> 322 322 a high 0 -#> 323 323 a high 0 -#> 324 324 a high 1 -#> 325 325 a high 0 -#> 326 326 a high 1 -#> 327 327 a high 0 -#> 328 328 a high 0 -#> 329 329 a high 0 -#> 330 330 a high 0 -#> 331 331 a high 0 -#> 332 332 a high 0 -#> 333 333 a high 0 -#> 334 334 a high 0 -#> 335 335 a high 0 -#> 336 336 a high 1 -#> 337 337 a high 1 -#> 338 338 a high 1 -#> 339 339 a high 0 -#> 340 340 a high 1 -#> 341 341 a high 1 -#> 342 342 a high 1 -#> 343 343 a high 0 -#> 344 344 a high 1 -#> 345 345 a high 1 -#> 346 346 a high 1 -#> 347 347 a high 1 -#> 348 348 a high 0 -#> 349 349 a high 0 -#> 350 350 a high 0 -#> 351 351 a high 1 -#> 352 352 a high 1 -#> 353 353 a high 0 -#> 354 354 a high 1 -#> 355 355 a high 0 -#> 356 356 a high 1 -#> 357 357 a high 1 -#> 358 358 a high 0 -#> 359 359 a high 1 -#> 360 360 a high 0 -#> 361 361 a high 0 -#> 362 362 a high 1 -#> 363 363 a high 1 -#> 364 364 a high 0 -#> 365 365 a high 1 -#> 366 366 a high 0 -#> 367 367 a high 0 -#> 368 368 a high 0 -#> 369 369 a high 1 -#> 370 370 a high 0 -#> 371 371 a high 1 -#> 372 372 a high 1 -#> 373 373 a high 0 -#> 374 374 a high 1 -#> 375 375 a high 0 -#> 376 376 a high 0 -#> 377 377 a high 0 -#> 378 378 a high 0 -#> 379 379 a high 0 -#> 380 380 a high 0 -#> 381 381 a high 0 -#> 382 382 a high 1 -#> 383 383 a high 0 -#> 384 384 a high 1 -#> 385 385 a high 0 -#> 386 386 a high 0 -#> 387 387 a high 0 -#> 388 388 a high 0 -#> 389 389 a high 1 -#> 390 390 a high 0 -#> 391 391 a high 1 -#> 392 392 a high 1 -#> 393 393 a high 0 -#> 394 394 a high 0 -#> 395 395 a high 1 -#> 396 396 a high 0 -#> 397 397 a high 1 -#> 398 398 a high 0 -#> 399 399 a high 0 -#> 400 400 a high 1 -#> 401 401 b high 0 -#> 402 402 b high 0 -#> 403 403 b high 0 -#> 404 404 b high 0 -#> 405 405 b high 0 -#> 406 406 b high 0 -#> 407 407 b high 0 -#> 408 408 b high 0 -#> 409 409 b high 0 -#> 410 410 b high 0 -#> 411 411 b high 0 -#> 412 412 b high 0 -#> 413 413 b high 0 -#> 414 414 b high 0 -#> 415 415 b high 0 -#> 416 416 b high 0 -#> 417 417 b high 0 -#> 418 418 b high 0 -#> 419 419 b high 0 -#> 420 420 b high 0 -#> 421 421 b high 1 -#> 422 422 b high 0 -#> 423 423 b high 0 -#> 424 424 b high 1 -#> 425 425 b high 0 -#> 426 426 b high 0 -#> 427 427 b high 0 -#> 428 428 b high 0 -#> 429 429 b high 0 -#> 430 430 b high 1 -#> 431 431 b high 0 -#> 432 432 b high 0 -#> 433 433 b high 0 -#> 434 434 b high 0 -#> 435 435 b high 0 -#> 436 436 b high 0 -#> 437 437 b high 1 -#> 438 438 b high 0 -#> 439 439 b high 1 -#> 440 440 b high 0 -#> 441 441 b high 0 -#> 442 442 b high 0 -#> 443 443 b high 1 -#> 444 444 b high 0 -#> 445 445 b high 0 -#> 446 446 b high 0 -#> 447 447 b high 0 -#> 448 448 b high 0 -#> 449 449 b high 0 -#> 450 450 b high 0 -#> 451 451 b high 1 -#> 452 452 b high 0 -#> 453 453 b high 1 -#> 454 454 b high 0 -#> 455 455 b high 0 -#> 456 456 b high 0 -#> 457 457 b high 0 -#> 458 458 b high 0 -#> 459 459 b high 1 -#> 460 460 b high 1 -#> 461 461 b high 0 -#> 462 462 b high 0 -#> 463 463 b high 0 -#> 464 464 b high 0 -#> 465 465 b high 0 -#> 466 466 b high 0 -#> 467 467 b high 0 -#> 468 468 b high 0 -#> 469 469 b high 0 -#> 470 470 b high 0 -#> 471 471 b high 0 -#> 472 472 b high 0 -#> 473 473 b high 0 -#> 474 474 b high 0 -#> 475 475 b high 0 -#> 476 476 b high 0 -#> 477 477 b high 0 -#> 478 478 b high 0 -#> 479 479 b high 0 -#> 480 480 b high 0 -#> 481 481 b high 0 -#> 482 482 b high 0 -#> 483 483 b high 0 -#> 484 484 b high 0 -#> 485 485 b high 0 -#> 486 486 b high 1 -#> 487 487 b high 0 -#> 488 488 b high 0 -#> 489 489 b high 1 -#> 490 490 b high 0 -#> 491 491 b high 0 -#> 492 492 b high 1 -#> 493 493 b high 0 -#> 494 494 b high 0 -#> 495 495 b high 0 -#> 496 496 b high 0 -#> 497 497 b high 0 -#> 498 498 b high 0 -#> 499 499 b high 0 -#> 500 500 b high 0 -#> 501 501 c high 0 -#> 502 502 c high 1 -#> 503 503 c high 0 -#> 504 504 c high 0 -#> 505 505 c high 1 -#> 506 506 c high 0 -#> 507 507 c high 0 -#> 508 508 c high 0 -#> 509 509 c high 0 -#> 510 510 c high 0 -#> 511 511 c high 0 -#> 512 512 c high 0 -#> 513 513 c high 1 -#> 514 514 c high 0 -#> 515 515 c high 0 -#> 516 516 c high 0 -#> 517 517 c high 0 -#> 518 518 c high 0 -#> 519 519 c high 0 -#> 520 520 c high 0 -#> 521 521 c high 0 -#> 522 522 c high 0 -#> 523 523 c high 1 -#> 524 524 c high 0 -#> 525 525 c high 0 -#> 526 526 c high 0 -#> 527 527 c high 0 -#> 528 528 c high 0 -#> 529 529 c high 0 -#> 530 530 c high 0 -#> 531 531 c high 0 -#> 532 532 c high 0 -#> 533 533 c high 0 -#> 534 534 c high 0 -#> 535 535 c high 0 -#> 536 536 c high 0 -#> 537 537 c high 0 -#> 538 538 c high 0 -#> 539 539 c high 0 -#> 540 540 c high 0 -#> 541 541 c high 0 -#> 542 542 c high 0 -#> 543 543 c high 0 -#> 544 544 c high 0 -#> 545 545 c high 0 -#> 546 546 c high 0 -#> 547 547 c high 0 -#> 548 548 c high 0 -#> 549 549 c high 0 -#> 550 550 c high 0 -#> 551 551 c high 0 -#> 552 552 c high 0 -#> 553 553 c high 0 -#> 554 554 c high 0 -#> 555 555 c high 0 -#> 556 556 c high 0 -#> 557 557 c high 0 -#> 558 558 c high 1 -#> 559 559 c high 0 -#> 560 560 c high 0 -#> 561 561 c high 0 -#> 562 562 c high 0 -#> 563 563 c high 0 -#> 564 564 c high 0 -#> 565 565 c high 0 -#> 566 566 c high 0 -#> 567 567 c high 0 -#> 568 568 c high 0 -#> 569 569 c high 0 -#> 570 570 c high 0 -#> 571 571 c high 0 -#> 572 572 c high 0 -#> 573 573 c high 0 -#> 574 574 c high 0 -#> 575 575 c high 0 -#> 576 576 c high 0 -#> 577 577 c high 0 -#> 578 578 c high 0 -#> 579 579 c high 0 -#> 580 580 c high 0 -#> 581 581 c high 0 -#> 582 582 c high 0 -#> 583 583 c high 1 -#> 584 584 c high 0 -#> 585 585 c high 0 -#> 586 586 c high 0 -#> 587 587 c high 0 -#> 588 588 c high 1 -#> 589 589 c high 0 -#> 590 590 c high 0 -#> 591 591 c high 0 -#> 592 592 c high 0 -#> 593 593 c high 0 -#> 594 594 c high 0 -#> 595 595 c high 0 -#> 596 596 c high 0 -#> 597 597 c high 0 -#> 598 598 c high 0 -#> 599 599 c high 0 -#> 600 600 c high 1 +#> 31 31 b low 0 +#> 32 32 b low 0 +#> 33 33 b low 0 +#> 34 34 b low 0 +#> 35 35 b low 0 +#> 36 36 b low 0 +#> 37 37 b low 0 +#> 38 38 b low 0 +#> 39 39 b low 0 +#> 40 40 b low 0 +#> 41 41 b low 0 +#> 42 42 b low 1 +#> 43 43 b low 0 +#> 44 44 b low 0 +#> 45 45 b low 0 +#> 46 46 b low 0 +#> 47 47 b low 1 +#> 48 48 b low 0 +#> 49 49 b low 0 +#> 50 50 b low 0 +#> 51 51 b low 0 +#> 52 52 b low 0 +#> 53 53 b low 0 +#> 54 54 b low 0 +#> 55 55 b low 0 +#> 56 56 b low 0 +#> 57 57 b low 0 +#> 58 58 b low 0 +#> 59 59 b low 0 +#> 60 60 b low 0 +#> 61 61 c low 0 +#> 62 62 c low 0 +#> 63 63 c low 0 +#> 64 64 c low 1 +#> 65 65 c low 1 +#> 66 66 c low 1 +#> 67 67 c low 1 +#> 68 68 c low 0 +#> 69 69 c low 1 +#> 70 70 c low 0 +#> 71 71 c low 1 +#> 72 72 c low 0 +#> 73 73 c low 0 +#> 74 74 c low 0 +#> 75 75 c low 1 +#> 76 76 c low 0 +#> 77 77 c low 0 +#> 78 78 c low 0 +#> 79 79 c low 0 +#> 80 80 c low 0 +#> 81 81 c low 0 +#> 82 82 c low 1 +#> 83 83 c low 0 +#> 84 84 c low 0 +#> 85 85 c low 0 +#> 86 86 c low 0 +#> 87 87 c low 0 +#> 88 88 c low 1 +#> 89 89 c low 0 +#> 90 90 c low 0 +#> 91 91 a high 0 +#> 92 92 a high 0 +#> 93 93 a high 0 +#> 94 94 a high 0 +#> 95 95 a high 0 +#> 96 96 a high 1 +#> 97 97 a high 1 +#> 98 98 a high 0 +#> 99 99 a high 1 +#> 100 100 a high 0 +#> 101 101 a high 1 +#> 102 102 a high 0 +#> 103 103 a high 1 +#> 104 104 a high 1 +#> 105 105 a high 1 +#> 106 106 a high 0 +#> 107 107 a high 0 +#> 108 108 a high 0 +#> 109 109 a high 0 +#> 110 110 a high 1 +#> 111 111 a high 1 +#> 112 112 a high 0 +#> 113 113 a high 0 +#> 114 114 a high 0 +#> 115 115 a high 1 +#> 116 116 a high 0 +#> 117 117 a high 0 +#> 118 118 a high 0 +#> 119 119 a high 0 +#> 120 120 a high 1 +#> 121 121 b high 1 +#> 122 122 b high 0 +#> 123 123 b high 0 +#> 124 124 b high 1 +#> 125 125 b high 0 +#> 126 126 b high 0 +#> 127 127 b high 0 +#> 128 128 b high 0 +#> 129 129 b high 0 +#> 130 130 b high 0 +#> 131 131 b high 0 +#> 132 132 b high 0 +#> 133 133 b high 0 +#> 134 134 b high 0 +#> 135 135 b high 1 +#> 136 136 b high 0 +#> 137 137 b high 0 +#> 138 138 b high 0 +#> 139 139 b high 0 +#> 140 140 b high 0 +#> 141 141 b high 0 +#> 142 142 b high 0 +#> 143 143 b high 0 +#> 144 144 b high 0 +#> 145 145 b high 0 +#> 146 146 b high 0 +#> 147 147 b high 0 +#> 148 148 b high 0 +#> 149 149 b high 0 +#> 150 150 b high 0 +#> 151 151 c high 0 +#> 152 152 c high 0 +#> 153 153 c high 1 +#> 154 154 c high 0 +#> 155 155 c high 0 +#> 156 156 c high 0 +#> 157 157 c high 1 +#> 158 158 c high 0 +#> 159 159 c high 0 +#> 160 160 c high 0 +#> 161 161 c high 0 +#> 162 162 c high 0 +#> 163 163 c high 1 +#> 164 164 c high 0 +#> 165 165 c high 0 +#> 166 166 c high 0 +#> 167 167 c high 0 +#> 168 168 c high 0 +#> 169 169 c high 0 +#> 170 170 c high 0 +#> 171 171 c high 0 +#> 172 172 c high 0 +#> 173 173 c high 0 +#> 174 174 c high 0 +#> 175 175 c high 0 +#> 176 176 c high 0 +#> 177 177 c high 0 +#> 178 178 c high 0 +#> 179 179 c high 0 +#> 180 180 c high 0 # Examples of use of rBernoulli t <- rBernoulli(50, 0.1) mean(t) -#> [1] 0.06 +#> [1] 0.14 diff --git a/docs/reference/summarize.html b/docs/reference/summarize.html index 3a7ff82..72e525d 100644 --- a/docs/reference/summarize.html +++ b/docs/reference/summarize.html @@ -1,6 +1,6 @@ -summarize — summarize • ANOPAsummarize — summarize • ANOPA @@ -18,7 +18,7 @@ ANOPA - 0.1.1 + 0.1.3
    @@ -75,8 +75,8 @@

    summarize

    -

    summarize() provides the statistics table an ANOPAobject. -It is synonym of summary() (but as actions are verbs, I used a verb).

    +

    'summarize()' provides the statistics table an ANOPAobject. +It is synonym of 'summary()' (but as actions are verbs, I used a verb).

    diff --git a/docs/reference/uncorrected.html b/docs/reference/uncorrected.html index ac8f8cd..b1a730b 100644 --- a/docs/reference/uncorrected.html +++ b/docs/reference/uncorrected.html @@ -1,5 +1,5 @@ -uncorrected — uncorrected • ANOPAuncorrected — uncorrected • ANOPAunitary alpha — unitaryAlpha • ANOPAunitary alpha — unitaryAlpha • ANOPA @@ -23,7 +23,7 @@ ANOPA - 0.1.1 + 0.1.3
    @@ -80,13 +80,13 @@

    unitary alpha

    -

    The function unitaryAlpha() computes +

    The function 'unitaryAlpha()' computes the unitary alpha ((Laurencelle and Cousineau 2023) ). This quantity is a novel way to compute correlation in a matrix where each column is a measure and each line, a subject. This measure is based on Cronbach's alpha (which could be -labeled a global alpha).

    +labeled a 'global alpha').

    diff --git a/man/A.Rd b/man/A.Rd index bdf8cec..f7878fb 100644 --- a/man/A.Rd +++ b/man/A.Rd @@ -49,10 +49,10 @@ when \code{n} is small. Therefore, a test based on this transform is either exac or conservative. } \description{ -The transformation functions \code{A()} performs the +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 \code{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}. diff --git a/man/ANOPA-package.Rd b/man/ANOPA-package.Rd index 66e0d64..a11d9d3 100644 --- a/man/ANOPA-package.Rd +++ b/man/ANOPA-package.Rd @@ -6,7 +6,7 @@ \alias{ANOPA-package} \title{ANOPA: Analyses of Proportions using Anscombe Transform} \description{ -\code{ANOPA} is a library to perform proportion analyses. +'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 @@ -19,8 +19,8 @@ easy. 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 \code{anopa} commands for more precision (in what follow, we assume -the compiled format where the proportions are given in a column name \code{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 @@ -59,7 +59,7 @@ and example datasets, some described in the article: \itemize{ } 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. } diff --git a/man/ArringtonEtAl2002.Rd b/man/ArringtonEtAl2002.Rd index 20fe28a..8f53b0d 100644 --- a/man/ArringtonEtAl2002.Rd +++ b/man/ArringtonEtAl2002.Rd @@ -17,9 +17,9 @@ ArringtonEtAl2002 The data, taken from \insertCite{a02;textual}{ANOPA}, is a dataset examining the distribution of fishes with empty stomachs, classified over three factors: -\verb{Collection location} (3 levels: Africa, Central/South America, North America), -\verb{Diel feeding behavior} (2 levels: diurnal, nocturnal), -\verb{Trophic category} (4 levels: Detritivore, Invertivore, Omnivore, Piscivore). +'Collection location' (3 levels: Africa, Central/South America, North America), +'Diel feeding behavior' (2 levels: diurnal, nocturnal), +'Trophic category' (4 levels: Detritivore, Invertivore, Omnivore, Piscivore). It is therefore a 3 × 2 × 4 design with 24 cells. The original data set also contains Order, Family and Species of the observed fishes and can be obtained from diff --git a/man/anopa.Rd b/man/anopa.Rd index 494f04e..8379ec4 100644 --- a/man/anopa.Rd +++ b/man/anopa.Rd @@ -22,8 +22,8 @@ decomposition of the main analyses, follow the analysis with \code{emProportions \code{contrastProportions()}, or \code{posthocProportions()}) } \description{ -The function \code{anopa()} performs an ANOPA for designs with up to 4 factors -according to the \code{ANOPA} framework. See \insertCite{lc23;textual}{ANOPA} for more. +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. } \details{ Note the following limitations: diff --git a/man/anopaN2Power.Rd b/man/anopaN2Power.Rd index b309ca7..ccef861 100644 --- a/man/anopaN2Power.Rd +++ b/man/anopaN2Power.Rd @@ -39,10 +39,10 @@ across measurements.} and sample sizes. } \description{ -The function \code{anopaN2Power()} performs an analysis of statistical power -according to the \code{ANOPA} framework. See \insertCite{lc23b;textual}{ANOPA} for more. -\code{anopaPower2N()} computes the sample size to reach a given power. -Finally, \code{anopaProp2fsq()} computes the f^2 effect size from a set of proportions. +The function 'anopaN2Power()' performs an analysis of statistical power +according to the 'ANOPA' framework. See \insertCite{lc23b;textual}{ANOPA} for more. +'anopaPower2N()' computes the sample size to reach a given power. +Finally, 'anopaProp2fsq()' computes the f^2 effect size from a set of proportions. } \details{ Note that for \code{anopaProp2fsq()}, the expected effect size $f^2$ diff --git a/man/anopa_asn_trans1.Rd b/man/anopa_asn_trans1.Rd index 31ee235..780ffa3 100644 --- a/man/anopa_asn_trans1.Rd +++ b/man/anopa_asn_trans1.Rd @@ -43,11 +43,11 @@ a list of attributes used to plot the error bars. See superb for more.} a ggplot2 object of the given proportions. } \description{ -The function \code{anopaPlot()} performs a plot of proportions for designs +The function 'anopaPlot()' performs a plot of proportions for designs with up to 4 factors according to the -\code{ANOPA} framework. See \insertCite{lc23;textual}{ANOPA} for more. The plot is -realized using the \code{suberb} library; see \insertCite{cgh21;textual}{ANOPA}. -It uses the arc-sine transformation \code{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()'. } \details{ The plot shows the proportions on the vertical axis as a diff --git a/man/contrastProportions.Rd b/man/contrastProportions.Rd index 189e82e..f3c9812 100644 --- a/man/contrastProportions.Rd +++ b/man/contrastProportions.Rd @@ -18,8 +18,8 @@ as well.} A table of significance of the different contrasts. } \description{ -The function \code{contrastProportions()} performs contrasts analyses -on proportion data after an omnibus analysis has been obtained with \code{anopa()} +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. } \details{ @@ -46,31 +46,8 @@ cw <- contrastProportions( w, list( 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) diff --git a/man/conversion.Rd b/man/conversion.Rd index eab65b5..2331e09 100644 --- a/man/conversion.Rd +++ b/man/conversion.Rd @@ -20,7 +20,7 @@ toCompiled(w) A data frame in the requested format. } \description{ -The functions \code{toWide()}, \code{toLong()}, and \code{toCompiled()} +The functions 'toWide()', 'toLong()', and 'toCompiled()' converts the data into various formats. } \details{ diff --git a/man/corrected.Rd b/man/corrected.Rd index a743740..c3303dd 100644 --- a/man/corrected.Rd +++ b/man/corrected.Rd @@ -15,6 +15,6 @@ corrected(object, ...) An ANOPA table with the corrected test statistics. } \description{ -\code{corrected()} provides an ANOPA table with only the corrected +'corrected()' provides an ANOPA table with only the corrected statistics. } diff --git a/man/emProportions.Rd b/man/emProportions.Rd index 19b82b2..525607d 100644 --- a/man/emProportions.Rd +++ b/man/emProportions.Rd @@ -19,8 +19,8 @@ An ANOPA table of the various simple main effets and if relevant, of the simple interaction effets. } \description{ -The function \code{emProportions()} performs a \emph{simple effect} analyses -of proportions after an omnibus analysis has been obtained with \code{anopa()} +The function 'emProportions()' performs a \emph{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 \emph{expected marginal} analysis of proportions. See \insertCite{lc23b;textual}{ANOPA} for more. } @@ -54,11 +54,7 @@ anopaPlot(w) # Let's execute the simple effect of Difficulty for every levels of Class e <- emProportions(w, ~ Difficulty | Class ) -#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] +summary(e) # -- SECOND EXAMPLE -- @@ -86,9 +82,6 @@ anopaPlot(w, ~ Trophism * Diel ) 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 diff --git a/man/explain.Rd b/man/explain.Rd index 0003b69..4e250c8 100644 --- a/man/explain.Rd +++ b/man/explain.Rd @@ -15,6 +15,6 @@ explain(object, ...) a human-readable output with details of computations. } \description{ -\code{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. } diff --git a/man/minimalExamples.Rd b/man/minimalExamples.Rd index f05f315..e1a6768 100644 --- a/man/minimalExamples.Rd +++ b/man/minimalExamples.Rd @@ -36,24 +36,24 @@ The datasets present minimal examples that are analyzed with an Analysis of Frequency Data method (described in \insertCite{lc23;textual}{ANOPA}. The five datasets are \itemize{ -\item \code{minimalBSExample}: an example with a single factor (state of residency) -\item \code{twoWayExample}: an example with two factors, Class and Difficulty -\item \code{minimalWSExample}: an example with a within-subject design (three measurements) -\item \code{twoWayWithinExample}: an example with two within-subject factors -\item \code{minimalMxExample}: a mixed design having one within and one between-subject factors +\item 'minimalBSExample': an example with a single factor (state of residency) +\item 'twoWayExample': an example with two factors, Class and Difficulty +\item 'minimalWSExample': an example with a within-subject design (three measurements) +\item 'twoWayWithinExample': an example with two within-subject factors +\item 'minimalMxExample': a mixed design having one within and one between-subject factors } } \examples{ library(ANOPA) -# the minimalBSExample data with proportions per state of residency for three states -minimalBSExample +# the twoWayExample data with proportions per Classes and Difficulty levels +twoWayExample # perform an anopa on this dataset -w <- anopa( {s;n} ~ state, minimalBSExample) +w <- anopa( {success;total} ~ Difficulty * Class, twoWayExample) -# We analyse the intensity by levels of pitch -# e <- emProportions(w, ~ Intensity | Pitch) +# We analyse the proportions by Difficulty for each Class +e <- emProportions(w, ~ Difficulty | Class) } \references{ diff --git a/man/posthocProportions.Rd b/man/posthocProportions.Rd index 0b2bd10..c23c43a 100644 --- a/man/posthocProportions.Rd +++ b/man/posthocProportions.Rd @@ -18,8 +18,8 @@ the effect of Factor A within every level of the Factor B.} a model fit of the simple effect. } \description{ -The function \code{posthocProportions()} performs post-hoc analyses -of proportions after an omnibus analysis has been obtained with \code{anopa()} +The function 'posthocProportions()' performs post-hoc analyses +of proportions after an omnibus analysis has been obtained with 'anopa()' according to the ANOPA framework. It is based on the tukey HSD test. See \insertCite{lc23b;textual}{ANOPA} for more. } @@ -53,11 +53,7 @@ anopaPlot(w) # Let's execute the post-hoc tests e <- posthocProportions(w, ~ Difficulty | Class ) -#summary(e) - -# As a check, you can verify that the $F$s are decomposed additively -#sum(e$omnibus[,1]) -w$omnibus[3,1]+w$omnibus[4,1] +summary(e) # -- SECOND EXAMPLE -- @@ -82,11 +78,8 @@ anopaPlot(w, ~ Trophism * Diel ) # Let's analyse the simple effect of Tropism for every levels of Diel and Location e <- posthocProportions(w, ~ Tropism | Diel ) -#summary(e) +summary(e) -# Again, as a check, you can verify that the $F$s are decomposed additively -w$omnibus[4,1]+w$omnibus[7,1] # B + B:C -#sum(e$omnibus[,1]) # You can ask easier outputs with summarize(w) # or summary(w) for the ANOPA table only diff --git a/man/rBernoulli.Rd b/man/rBernoulli.Rd index 53e642c..c43c046 100644 --- a/man/rBernoulli.Rd +++ b/man/rBernoulli.Rd @@ -30,10 +30,10 @@ scores cannot be generated by \code{GRP()}; see \insertCite{ld98}{ANOPA}. \code{rBernoulli()} returns a sequence of n success (1) or failures (0) } \description{ -The function \code{GRP()} +The function 'GRP()' generates random proportions based on a design, i.e., a list giving the factors and the categories with each factor. -The data are returned in the \code{wide} format. +The data are returned in the 'wide' format. } \details{ The name of the function \code{GRP()} is derived from \code{GRD()}, @@ -65,15 +65,15 @@ GRP( WSDesign=wsDesign, props = c(0.1, 0.9), n = 10 ) # This last one has three factors, for a total of 3 x 2 x 2 = 12 cells design <- list( A=letters[1:3], B = c("low","high"), C = c("cat","dog")) -GRP( design, n = 100, props = rep(0.5,12) ) +GRP( design, n = 30, props = rep(0.5,12) ) # To specify unequal probabilities, use design <- list( A=letters[1:3], B = c("low","high")) expProp <- c(.05, .05, .35, .35, .10, .10 ) -GRP( design, n = 100, props=expProp ) +GRP( design, n = 30, props=expProp ) # The name of the column containing the proportions can be changed -GRP( design, n=100, props=expProp, sname="patate") +GRP( design, n=30, props=expProp, sname="patate") # Examples of use of rBernoulli t <- rBernoulli(50, 0.1) diff --git a/man/summarize.Rd b/man/summarize.Rd index 1d83265..659706e 100644 --- a/man/summarize.Rd +++ b/man/summarize.Rd @@ -15,6 +15,6 @@ summarize(object, ...) an ANOPA table as per articles. } \description{ -\code{summarize()} provides the statistics table an ANOPAobject. -It is synonym of \code{summary()} (but as actions are verbs, I used a verb). +'summarize()' provides the statistics table an ANOPAobject. +It is synonym of 'summary()' (but as actions are verbs, I used a verb). } diff --git a/man/uncorrected.Rd b/man/uncorrected.Rd index c91e7b2..432af35 100644 --- a/man/uncorrected.Rd +++ b/man/uncorrected.Rd @@ -16,6 +16,6 @@ An ANOPA table with the un-corrected test statistics. That should be avoided, more so if your sample is rather small. } \description{ -\code{uncorrected()} provides an ANOPA table with only the uncorrected +'uncorrected()' provides an ANOPA table with only the uncorrected statistics. } diff --git a/man/unitaryAlpha.Rd b/man/unitaryAlpha.Rd index 659985d..8b61080 100644 --- a/man/unitaryAlpha.Rd +++ b/man/unitaryAlpha.Rd @@ -13,12 +13,12 @@ unitaryAlpha( m ) A measure of correlation between -1 and +1. } \description{ -The function \code{unitaryAlpha()} computes +The function 'unitaryAlpha()' computes the unitary alpha (\insertCite{lc23}{ANOPA}). This quantity is a novel way to compute correlation in a matrix where each column is a measure and each line, a subject. This measure is based on Cronbach's alpha (which could be -labeled a \verb{global alpha}). +labeled a 'global alpha'). } \details{ This measure is derived from Cronbach' measure of diff --git a/vignettes/B-DataFormatsForProportions.Rmd b/vignettes/B-DataFormatsForProportions.Rmd index 10b245f..b0e1f45 100644 --- a/vignettes/B-DataFormatsForProportions.Rmd +++ b/vignettes/B-DataFormatsForProportions.Rmd @@ -241,8 +241,12 @@ w3 <- anopa( cbind(r11,r12,r12,r21,r22,r23) ~ . , toCompiled(w3) ``` -A "fyi" message is shown which lets you see how the variables are interpreted. +A "fyi" message is shown which lets you see how the variables are interpreted. Such +messages can be inhibited by changing the option +```{r, message=TRUE, warning=FALSE, echo=TRUE, eval=TRUE} +options("ANOPA.feedback" = "none") +``` To know more about analyzing proportions with ANOPA, refer to @lc23 or to [What is an ANOPA?](../articles/A-WhatIsANOPA.html). diff --git a/vignettes/C-ConfidenceIntervals.Rmd b/vignettes/C-ConfidenceIntervals.Rmd index 4369f1c..d644c7c 100644 --- a/vignettes/C-ConfidenceIntervals.Rmd +++ b/vignettes/C-ConfidenceIntervals.Rmd @@ -52,7 +52,7 @@ increasing the wide of the intervals by $\sqrt{2}$. Also, in repeated measure designs, the correlation is beneficial to improve estimates. As such, the interval wide can be reduced when correlation is -positive by multiplying its length by $1-\alpha_1$, where $\alpha_1$ is +positive by multiplying its length by $\sqrt{1-\alpha_1}$, where $\alpha_1$ is a measure of correlation in a matrix containing repeated measures (based on the unitary alpha measure). @@ -89,11 +89,11 @@ For example, library(ggplot2) anopaPlot(w, ~ Difficulty) + theme_bw() + # change theme - scale_x_discrete(limits = c("Easy", "Moderate", "Difficult")) #changer order + scale_x_discrete(limits = c("Easy", "Moderate", "Difficult")) #change order ``` As you can see from this plot, Difficulty is very significant, and the most different -conditions are Moderate vs. Difficult. +conditions are Easy vs. Difficult. Here you go. diff --git a/vignettes/D-ArringtonExample.Rmd b/vignettes/D-ArringtonExample.Rmd index 2f0f7c7..0e2cb11 100644 --- a/vignettes/D-ArringtonExample.Rmd +++ b/vignettes/D-ArringtonExample.Rmd @@ -57,9 +57,11 @@ w <- anopa( {s; n} ~ Location * Diel * Trophism, ArringtonEtAl2002) ``` The `fyi` message lets you know that cells are missing; the `Warning` message lets you -know that these cells were imputed. +know that these cells were imputed (you can suppress messages with +`options("ANOPA.feedback"="none")`. -To see the result (using the uncorrected results as the samples are not small), +To see the result, use `summary(w)` (which shows the corrected and uncorrected statistics) +or `uncorrected(w)` (as the sample is quite large, the correction will be immaterial...), ```{r} uncorrected(w) diff --git a/vignettes/F-TestingTypeIError.Rmd b/vignettes/F-TestingTypeIError.Rmd index fb5ef7d..b7a6c46 100644 --- a/vignettes/F-TestingTypeIError.Rmd +++ b/vignettes/F-TestingTypeIError.Rmd @@ -38,7 +38,7 @@ options("ANOPA.feedback" = 'none') library(ANOPA) library(testthat) nsim <- 1000 # increase for more reliable simulations. -theN <- 20 # number of participants +theN <- 20 # number of simulated participants ``` Note that the simulations are actually not run in this vignette, as