diff --git a/.Rbuildignore b/.Rbuildignore index ec2fc7f29ce71c3f0c6b5784d6a84a13e21bb913..731e3ca5e58ab25f9d6793631aba9c8bfcd6c3c8 100644 --- a/.Rbuildignore +++ b/.Rbuildignore @@ -2,6 +2,7 @@ README.md Rplots.pdf contributing.md buildPkg.R +legTools.bmk .#buildPkg.R .gitignore .Rprofile diff --git a/DESCRIPTION b/DESCRIPTION index bfcf1c9c2e6f9e65a0f0a5bb70334beffa763107..1431460bf315b4f8dfda64bd4c8641c6b96b69a4 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -9,21 +9,19 @@ Description: legTools is a collection of R functions and datasets used for of them from books. It is maintained by the LEG group (Statistics and Geoinformation Laboratory). Please visit http://www.leg.ufpr.br. Depends: - R (>= 3.2.1), - gWidgets, - gWidgetstcltk, - knitr, - markdown, - RWordPress -Imports: + R (>= 3.2.1) +Imports: lattice, latticeExtra Suggests: + gWidgets, + gWidgetstcltk, knitr, - rmarkdown + markdown, + RWordPress, + multcomp License: GPL-3 | file LICENSE URL: http://git.leg.ufpr.br/leg/legTools BugReports: http://git.leg.ufpr.br/leg/legTools/issues LazyData: true Encoding: UTF-8 -VignetteBuilder: knitr diff --git a/NAMESPACE b/NAMESPACE index e7def8d305e7fdaea655ca4109a1d38fb49c49ea..e642272b0865c1350fd5c2a31fd2a334e127de27 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -10,11 +10,6 @@ export(polyGui) export(runAllChunks) export(subsetDropAll) export(twoStripCombined) -export(yscale.component.right) -import(RWordPress) -import(gWidgets) -import(gWidgetstcltk) -import(knitr) +export(yscale.components.right) import(lattice) import(latticeExtra) -import(markdown) diff --git a/R/knit2wpCrayon.R b/R/knit2wpCrayon.R index bb4c0b344e4df29b9ce3ad830c7999e9667540b5..6c4f45c99d27418628154967abf61e9c0054dc8b 100644 --- a/R/knit2wpCrayon.R +++ b/R/knit2wpCrayon.R @@ -25,7 +25,6 @@ #' #' @author Walmes Zeviani, \email{walmes@@ufpr.br} #' -#' @import knitr markdown RWordPress #' @export #' @examples #' \donttest{ @@ -66,17 +65,33 @@ knit2wpCrayon <- function(input, title="A post from knitr", ..., stop("`markdown` needed for this function to work. Please install it.", call.=FALSE) } - if (!requireNamespace("RWordPress", quietly=TRUE)){ + if (!requireNamespace("RWordPress", quietly=TRUE)){ stop("`RWordPress` needed for this function to work. Please install it.", call.=FALSE) } - out <- knit(input, encoding=encoding) + ## + ##------------------------------------------- + ## knitr:::native_encode(). + ## + native_encode <- function (x, to = ""){ + idx = Encoding(x) == "UTF-8" + x2 = iconv(x, if (any(idx)) "UTF-8" else "", to) + if (!any(is.na(x2))) + return(x2) + warning("some characters may not work under the current locale") + x + } + ## + ##------------------------------------------- + ## Modifed body of the knit2wp(). + ## + out <- knitr::knit(input, encoding=encoding) on.exit(unlink(out)) con <- file(out, encoding=encoding) on.exit(close(con), add=TRUE) content <- native_encode(readLines(con, warn=FALSE)) content <- paste(content, collapse="\n") - content <- markdownToHTML(text=content, fragment.only=TRUE) + content <- markdown::markdownToHTML(text=content, fragment.only=TRUE) content <- gsub( pattern="<pre><code class=\"([[:alpha:]]+)\">(.+?)</code></pre>", replacement="<pre class=\"lang:\\1 decode:true\">\\2</pre>", @@ -97,3 +112,7 @@ knit2wpCrayon <- function(input, title="A post from knitr", ..., print(do.call(action, args=WPargs)) } } + + +library(knitr) +knitr:::native_encode diff --git a/R/legTools.R b/R/legTools.R index 75be3eb232c6eb00f09c70e15b3831d0ca9ade74..3915d62dbdbc5ae792d711610242a2124206d3b1 100644 --- a/R/legTools.R +++ b/R/legTools.R @@ -7,7 +7,7 @@ ##' @name legTools NULL -#' @name wgpigs +#' @name wgPigs #' #' @title Feeding type in pig weight gain #' @@ -29,7 +29,7 @@ NULL #' #' @keywords datasets #' -#' @usage data(wgpigs) +#' @usage data(wgPigs) #' #' @format a \code{data.frame} with 20 records and 2 variables. #' @@ -39,15 +39,15 @@ NULL #' @examples #' #' library(lattice) -#' data(wgpigs) +#' data(wgPigs) #' -#' xyplot(wg~ft, data=wgpigs, +#' xyplot(wg~ft, data=wgPigs, #' ylab="Weight gain (kg)", #' xlab="Feeding type") #' NULL -#' @name potatoyield +#' @name potatoYield #' #' @title Potato variety competition experiment #' @@ -67,7 +67,7 @@ NULL #' #' @keywords datasets #' -#' @usage data(potatoyield) +#' @usage data(potatoYield) #' #' @format a \code{data.frame} with 32 records and 3 variables. #' @@ -75,10 +75,11 @@ NULL #' ed.). Piracicaba, São Paulo: FEALQ. (page 76) #' #' @examples +#' #' library(lattice) -#' data(potatoyield) +#' data(potatoYield) #' -#' plot(yield~variety, data=potatoyield, +#' plot(yield~variety, data=potatoYield, #' groups=block, type="o", #' ylab=expression(Yield~(t~ha^{-1})), #' xlab="Variety") @@ -115,8 +116,9 @@ NULL #' ed.). Piracicaba, São Paulo: FEALQ. (page 91) #' #' @examples +#' #' library(lattice) -#' data(potatoyield) +#' data(plowing) #' #' xyplot(yield~plow|block, data=plowing, type=c("p", "a"), #' ylab=expression(Yield~(t~ha^{-1})), @@ -353,19 +355,19 @@ NULL #' experimental unit. #' #' \itemize{ -#' \item \code{row} the rows of the latin square that controls in +#' \item \code{row} the rows of the latin square that controls in #' one dimention. A categorical unordered factor with 6 levels. -#' \item \code{col} the columns of the latin square that controls in +#' \item \code{col} the columns of the latin square that controls in #' one dimention perpendicular to the previus. A categorical #' unordered factor with 6 levels. -#' \item \code{fertil} a categorical unordered factor with 6 +#' \item \code{fertil} a categorical unordered factor with 6 #' levels that is the fertilization strategy applied. These levels #' are a result of treatment cells in a three incomplete factorial #' arrangrment. See detais for more information. -#' \item \code{yield} sugarcane yield (kg/plot). +#' \item \code{yield} sugarcane yield (kg/plot). #' } #' -#' @details The levels of fetilization are in fact a combination of a +#' @details The levels of fertilization are in fact a combination of a #' \eqn{3^2} factorial experiment but not all cells are present, so #' this is a (intentional) incomplete three factorial #' experiment. The factors used were limestone (A: present, a: @@ -419,3 +421,347 @@ NULL #' aggregate(yield~A+B+C, data=sugarcaneYield3, FUN=mean) #' NULL + +#' @name wgPigs2 +#' +#' @title Age of castration in pig weight gain +#' +#' @description This is an artifial dataset corresponding a experiment +#' to study the effect of feeding type (factor with 4 categorical +#' nominal levels) in pig weight gain. The experiment was a +#' randomized complete design with five experimental units per +#' treatment level. The experimental unit was a pig. The response +#' measured was weight gain from the beggining to the end of the +#' experiment. +#' +#' \itemize{ +#' \item \code{litter} a categorical factor with 4 levels that +#' represents the rows of the lattin square design and control for +#' the differences among litters. +#' \item code{size} a categorical ordered variable that represents the +#' columns of latin square desing and control for the weight of the +#' animals at the beggining of the experiment. +#' \item \code{age} age of the animal (days) when castration was +#' done. \code{controls} are the animals without castration. +#' \item \code{wg} weight gain (kg) after 252 days. +#' } +#' +#' @docType data +#' +#' @keywords datasets +#' +#' @usage data(wgPigs2) +#' +#' @format a \code{data.frame} with 16 records and 4 variables. +#' +#' @source Frederico, P. (2009). Curso de EstatÃstica Experimental (15th +#' ed.). Piracicaba, São Paulo: FEALQ. (page 110) +#' +#' @examples +#' +#' library(lattice) +#' +#' data(wgPigs2) +#' str(wgPigs2) +#' +#' xyplot(wg~age, data=wgPigs2, groups=litter, +#' ylab="Weight gain (kg)", +#' xlab="Age at castration (days)") +#' +NULL + +#' @name cornYield +#' +#' @title Corn yield as function of fertilization with NPK +#' +#' @description These data are from an \eqn{2^3} factorial experiment +#' studing the effect of Nitrogen (N), Phosporus (P) and Potassium +#' (K) on corn yield in a randomized block design. +#' +#' \itemize{ +#' \item \code{block} a factor with 4 levels. +#' \item \code{N} low (-1) and high (+1) levels of nitrogen. +#' \item \code{P} low (-1) and high (+1) levels of phosporus. +#' \item \code{K} low (-1) and high (+1) levels of potassium. +#' \item \code{yield} corn yield (ton/ha). +#' } +#' +#' @docType data +#' +#' @keywords datasets +#' +#' @usage data(cornYield) +#' +#' @format a \code{data.frame} with 32 records and 4 variables. +#' +#' @source Frederico, P. (2009). Curso de EstatÃstica Experimental (15th +#' ed.). Piracicaba, São Paulo: FEALQ. (page 115) +#' +#' @examples +#' +#' library(lattice) +#' library(latticeExtra) +#' +#' data(cornYield) +#' str(cornYield) +#' +#' xyplot(yield~N|P, groups=K, +#' data=cornYield, type=c("p", "a"), +#' ylab=expression(Yield~(ton~ha^{-1})), +#' xlab="Nutrient level") +#' +#' xyplot(yield~N, groups=interaction(P, K), +#' data=cornYield, type=c("p", "a"), +#' auto.key=list(columns=2), +#' ylab=expression(Yield~(ton~ha^{-1})), +#' xlab="Nutrient level") +#' +NULL + +#' @name vinasseFert +#' +#' @title Fertilization with vinasse and mineral +#' +#' @description These data are from an \eqn{2^2} factorial experiment +#' studing the effect of fertilizaton with vinasse (a residual from +#' industrial processing of sugar cane) and complete mineral +#' fertilization. +#' +#' \itemize{ +#' \item \code{block} a factor with 4 levels. +#' \item \code{mineral} low (-1) and high (+1) levels of mineral +#' fertilization. +#' \item \code{vinasse} low (-1) and high (+1) levels of fetilization +#' with vinasse. +#' \item \code{y} some response variable. The text book doesn't give +#' any information. +#' } +#' +#' @docType data +#' +#' @keywords datasets +#' +#' @usage data(vinasseFert) +#' +#' @format a \code{data.frame} with 16 records and 4 variables. +#' +#' @source Frederico, P. (2009). Curso de EstatÃstica Experimental (15th +#' ed.). Piracicaba, São Paulo: FEALQ. (page 119) +#' +#' @examples +#' +#' library(lattice) +#' library(latticeExtra) +#' +#' data(vinasseFert) +#' str(vinasseFert) +#' +#' xyplot(y~vinasse, groups=mineral, +#' auto.key=list(title="Mineral", columns=2), +#' data=vinasseFert, type=c("p", "a"), +#' ylab="y", +#' xlab="Vinasse level") +#' +NULL + +#' @name filterCake +#' +#' @title Fertilization with filter cake and mineral +#' +#' @description These data are from an \eqn{2^2} factorial experiment +#' studing the effect of fertilizaton with filter cake (a residual +#' from industrial processing of sugar cane) and traditional mineral +#' fertilization. +#' +#' \itemize{ +#' \item \code{block} a factor with 4 levels. +#' \item \code{mineral} low (-1) and high (+1) levels of mineral +#' fertilization. +#' \item \code{cake} low (-1) and high (+1) levels of fetilization +#' with filter cake. +#' \item \code{y} some response variable. The text book doesn't give +#' any information. +#' } +#' +#' @docType data +#' +#' @keywords datasets +#' +#' @usage data(filterCake) +#' +#' @format a \code{data.frame} with 16 records and 4 variables. +#' +#' @source Frederico, P. (2009). Curso de EstatÃstica Experimental (15th +#' ed.). Piracicaba, São Paulo: FEALQ. (page 120) +#' +#' @examples +#' +#' library(lattice) +#' library(latticeExtra) +#' +#' data(filterCake) +#' str(filterCake) +#' +#' xyplot(y~cake, groups=mineral, +#' auto.key=list(title="Mineral", columns=2), +#' data=filterCake, type=c("p", "a"), +#' ylab="y", +#' xlab="Filter cake level") +#' +#' +NULL + +#' @name sugarcaneYield4 +#' +#' @title Triple factorial NPK fertilization on sugar cane yield +#' +#' @description These data are from an \eqn{3^3} factorial experiment +#' studing the effect of NPK on the yield of sugar cane. +#' +#' \itemize{ +#' \item \code{block} a local control factor with 3 levels. +#' \item \code{rept} factor with 2 levels. +#' \item \code{N} integer coded nitrogen levels (0, 1, 2). +#' \item \code{P} integer coded phosphorus levels (0, 1, 2). +#' \item \code{K} integer coded potassium levels (0, 1, 2). +#' \item \code{yield} sugar cane yield (ton/ha). +#' } +#' +#' @details There is a missprint in the book for the 9th entry, which +#' has yield 59.0, that is coded as 202 istead of 220. +#' +#' @docType data +#' +#' @keywords datasets +#' +#' @usage data(sugarcaneYield4) +#' +#' @format a \code{data.frame} with 54 records and 6 variables. +#' +#' @source Frederico, P. (2009). Curso de EstatÃstica Experimental (15th +#' ed.). Piracicaba, São Paulo: FEALQ. (page 126) +#' +#' @examples +#' +#' library(lattice) +#' library(latticeExtra) +#' +#' data(sugarcaneYield4) +#' str(sugarcaneYield4) +#' +#' xyplot(yield~N|P, groups=K, +#' auto.key=list(title="Potassim level", columns=3), +#' strip=strip.custom(var.name="Phosphorus", strip.names=TRUE, +#' strip.levels=TRUE, sep=": "), +#' data=sugarcaneYield4, type=c("p", "a"), +#' ylab=expression(Yield~(ton~ha^{-1})), +#' xlab="Nitrogen level level") +#' +NULL + +#' @name mangoAcidity +#' +#' @title Acidity of mango fruits by varieties, years and months +#' +#' @description These data are from an observational study along 3 years +#' where acidity in fruits of 6 varieties of mango was determined in +#' Novermber, December and January. +#' +#' \itemize{ +#' \item \code{variety} a categorical variable with 6 levels that +#' represents mango varieties studied. +#' \item \code{year} the year of harvesting. +#' \item \code{month} the month of harvesting. +#' \item \code{acid} mean of the acidity determined in 3 fruits. +#' } +#' +#' @docType data +#' +#' @keywords datasets +#' +#' @usage data(sugarcaneYield4) +#' +#' @format a \code{data.frame} with 54 records and 6 variables. +#' +#' @source Frederico, P. (2009). Curso de EstatÃstica Experimental (15th +#' ed.). Piracicaba, São Paulo: FEALQ. (page 132) +#' +#' Simão, S. (1960). Estudo da planta e dos frutos da mangueira +#' (\emph{Manginifera indica} L.). Piracicaba, 1960. Thesis. +#' +#' @examples +#' +#' library(lattice) +#' library(latticeExtra) +#' +#' data(mangoAcidity) +#' str(mangoAcidity) +#' +#' ## reshape::cast() can also be used. +#' with(mangoAcidity, +#' ftable(tapply(acid, +#' list(variety, year, month), +#' FUN=identity))) +#' +#' xyplot(acid~month|variety, groups=year, +#' data=mangoAcidity, type=c("p", "a"), +#' auto.key=TRUE, +#' ylab="Acidity", +#' xlab="Month") +#' +NULL + +#' @name cornYield2 +#' +#' @title Axial factorial NPK experiment with added treatments +#' +#' @description These data are from an axial 3 factorial experiment +#' studing NPK in the yield of corn. Tow controls were added, one is +#' zer control (no NPK) and the other is central factorial point +#' plus presence of limestone. +#' +#' \itemize{ +#' \item \code{N} content of nitrogen in the fertilizer. +#' \item \code{P} content of phosphorus in the fertilizer. +#' \item \code{K} content of potassium in the fertilizer. +#' \item \code{limestone} presence (1) or absence of limestone (0). +#' \item \code{acid} mean of corn yield in 16 locations (ton/ha). +#' } +#' +#' @details The experiment was caried out in 16 different locations but +#' only the mean by cell combinations were available in the text +#' book. +#' +#' @docType data +#' +#' @keywords datasets +#' +#' @usage data(sugarcaneYield4) +#' +#' @format a \code{data.frame} with 9 records and 5 variables. +#' +#' @source Frederico, P. (2009). Curso de EstatÃstica Experimental (15th +#' ed.). Piracicaba, São Paulo: FEALQ. (page 132) +#' +#' Simão, S. (1960). Estudo da planta e dos frutos da mangueira +#' (\emph{Manginifera indica} L.). Piracicaba, 1960. Thesis. +#' +#' @examples +#' +#' library(lattice) +#' library(latticeExtra) +#' +#' data(cornYield2) +#' str(cornYield2) +#' +#' ## Axial triple factorial with 2 controls. +#' ftable(xtabs(~N+P+K, data=cornYield2)) +#' +#' xyplot(yield~N+P+K, +#' groups=as.integer(limestone==1 | (N+P+K)==0), +#' data=cornYield2, type=c("p", "a"), +#' auto.key=TRUE, +#' ylab=expression(Yield~(ton~ha^{-1})), +#' xlab="Nutrient content") +#' +NULL diff --git a/R/loessGui.R b/R/loessGui.R index 2ec9d051e374c38de1a06045f5770021eda15804..20fcfd27f17af5a891d0be892a492ac385d46b6a 100644 --- a/R/loessGui.R +++ b/R/loessGui.R @@ -5,11 +5,11 @@ #' @description This function opens an interface to control the settings #' of a loess regression: #' \itemize{ -#' \item degree choose the local polynomial degree with a radio +#' \item degree choose the local polynomial degree with a radio #' selector; -#' \item span set the span value that controls the degree of +#' \item span set the span value that controls the degree of #' smoothing; -#' \item center move the x value to be predicted; +#' \item center move the x value to be predicted; #' } #' #' The elements of the interface change a plot that shows the observed @@ -18,17 +18,13 @@ #' \code{gWidgets} and \code{gWidgetstcltk} packages are available. #' #' @param x,y independent and dependent (numeric) regression variables. -#' #' @param data an optional \code{data.frame}. -#' #' @param er stands for extend range. It is used to extend the plotting -#' range by a fraction on both sides and directions. Default is -#' 0.05. See \link[grDevices]{extendrange}. +#' range by a fraction on both sides and directions. Default is +#' 0.05. See \link[grDevices]{extendrange}. #' #' @return None is returned by the function, only a GUI is opened. #' -#' @import gWidgets gWidgetstcltk -#' #' @author Walmes Zeviani, \email{walmes@@ufpr.br} #' #' @export @@ -116,8 +112,8 @@ loessGui <- function(x, y, data, er=0.05){ ## Fit loess regression. ## m0 <- loess(formula=y~x, - span=svalue(SPAN), - degree=as.integer(svalue(DEGREE)), + span=gWidgets::svalue(SPAN), + degree=as.integer(gWidgets::svalue(DEGREE)), family="gaussian") ## ##------------------------------------------- @@ -131,8 +127,8 @@ loessGui <- function(x, y, data, er=0.05){ ##------------------------------------------- ## Weights to be used in local polynomial. ## - x0 <- svalue(XCENTER) - sp <- svalue(SPAN) + x0 <- gWidgets::svalue(XCENTER) + sp <- gWidgets::svalue(SPAN) a <- abs(x-x0) if (sp < 1){ q <- as.integer(sp*nx) @@ -166,53 +162,56 @@ loessGui <- function(x, y, data, er=0.05){ sum(s), nx)) ## NOTE: usar action aqui! ## xl <- c(min(c(xl[1], x0)), max(c(x0, xl[2]))) - do.call(what=paste0("f", svalue(DEGREE)), + do.call(what=paste0("f", gWidgets::svalue(DEGREE)), args=list(w=w, xl=xl)) } ## ##------------------------------------------- ## Building the GUI. ## - WDW <- gwindow(title="LOESS regression", visible=FALSE) - GG <- ggroup(container=WDW, expand=TRUE, horizontal=FALSE) - GF_DG <- gframe(text="Local polynomial degree:", container=GG) - DEGREE <- gradio(items=0:2, selected=2L, horizontal=TRUE, + WDW <- gWidgets::gwindow(title="LOESS regression", visible=FALSE) + GG <- gWidgets::ggroup(container=WDW, expand=TRUE, horizontal=FALSE) + GF_DG <- gWidgets::gframe(text="Local polynomial degree:", container=GG) + DEGREE <- gWidgets::gradio(items=0:2, selected=2L, horizontal=TRUE, handler=draw.loess, container=GF_DG) - GF_XC <- gframe(text="Predicted point:", expand=TRUE, container=GG) - XCENTER <- gslider(from=erx[1], to=erx[2], + GF_XC <- gWidgets::gframe(text="Predicted point:", expand=TRUE, + container=GG) + XCENTER <- gWidgets::gslider(from=erx[1], to=erx[2], value=mean(erx), length.out=51, handler=draw.loess, expand=TRUE, container=GF_XC) - XCLABEL <- glabel(text=sprintf("%0.2f", svalue(XCENTER)), + XCLABEL <- gWidgets::glabel(text=sprintf("%0.2f", + gWidgets::svalue(XCENTER)), container=GF_XC) - addHandlerChanged(XCENTER, + gWidgets::addHandlerChanged(XCENTER, action=XCLABEL, handler=function(h, ...){ - svalue(h$action) <- - sprintf("%0.2f", svalue(h$obj)) + gWidgets::svalue(h$action) <- + sprintf("%0.2f", gWidgets::svalue(h$obj)) }) - GF_SP <- gframe(text="Span:", expand=TRUE,container=GG) - SPAN <- gslider(from=0, to=1.5, + GF_SP <- gWidgets::gframe(text="Span:", expand=TRUE,container=GG) + SPAN <- gWidgets::gslider(from=0, to=1.5, value=0.75, by=0.05, handler=draw.loess, expand=TRUE, container=GF_SP) - SPLABEL <- glabel(text=sprintf("%0.2f", svalue(SPAN)), + SPLABEL <- gWidgets::glabel(text=sprintf("%0.2f", + gWidgets::svalue(SPAN)), container=GF_SP) - addHandlerChanged(SPAN, + gWidgets::addHandlerChanged(SPAN, action=SPLABEL, handler=function(h, ...){ - svalue(h$action) <- - sprintf("%0.2f", svalue(h$obj)) + gWidgets::svalue(h$action) <- + sprintf("%0.2f", gWidgets::svalue(h$obj)) }) ##------------------------------------------- ## Initializing. - svalue(SPAN) <- 0.75 - svalue(DEGREE) <- 1L - svalue(XCENTER) <- mean(erx) + gWidgets::svalue(SPAN) <- 0.75 + gWidgets::svalue(DEGREE) <- 1L + gWidgets::svalue(XCENTER) <- mean(erx) do.call(what=draw.loess, args=list(NA)) - visible(WDW) <- TRUE + gWidgets::visible(WDW) <- TRUE } diff --git a/R/polyGui.R b/R/polyGui.R index f1e337c9b12f78ff139c63ab075d5d7f634a64c2..9d2a328d7af16df45b639cd368e8dde2aa4271e3 100644 --- a/R/polyGui.R +++ b/R/polyGui.R @@ -3,23 +3,20 @@ #' @name polyGui #' #' @description This function opens an interface to control the -#' polynomial degree in linear regression. It shows the observed values -#' and the corresponding fitted curve superimposed with confidence bands -#' (for the fitted values) and also show the residuals plot. It assumes -#' that \code{gWidgets} and \code{gWidgetstcltk} packages are available. +#' polynomial degree in linear regression. It shows the observed +#' values and the corresponding fitted curve superimposed with +#' confidence bands (for the fitted values) and also show the +#' residuals plot. It assumes that \code{gWidgets} and +#' \code{gWidgetstcltk} packages are available. #' #' @param x,y independent and dependent (numeric) regression variables. -#' #' @param data an optional \code{data.frame}. -#' #' @param er stands for extend range. It is used to extend the plotting -#' range by a fraction on both sides and directions. Default is -#' 0.05. See \link[grDevices]{extendrange}. +#' range by a fraction on both sides and directions. Default is +#' 0.05. See \link[grDevices]{extendrange}. #' #' @return None is returned by the function. #' -#' @import gWidgets gWidgetstcltk -#' #' @author Walmes Zeviani, \email{walmes@@ufpr.br} #' #' @export @@ -65,7 +62,7 @@ polyGui <- function(x, y, data, er=0.05){ mtext(side=3, adj=1, line=2.5, text=lastcoef) mtext(side=3, adj=1, line=1.5, text=sprintf("R^2 (adj. R^2): %0.2f (%0.2f)", - 100*sm$r.squared, 100*sm$adj.r.squared)) + 100*sm$r.squared, 100*sm$adj.r.squared)) } ## ##------------------------------------------- @@ -87,17 +84,18 @@ polyGui <- function(x, y, data, er=0.05){ ## Function controled by the GUI. ## draw.poly <- function(h, ...){ - svalue(degree) <- min(c( - max(c(1L, svalue(degree)+h$action$val)), + gWidgets::svalue(degree) <- min(c( + max(c(1L, gWidgets::svalue(degree)+h$action$val)), maxd)) - m0 <- lm(y~poly(x, degree=svalue(degree))) - switch(svalue(plottype), + m0 <- lm(y~poly(x, degree=gWidgets::svalue(degree))) + switch(gWidgets::svalue(plottype), "Scatter plot"={ - cb <- predict(m0, newdata=newdata, interval="confidence") + cb <- predict(m0, newdata=newdata, + interval="confidence") plot(y~x, xlim=xr, ylim=yr, xlab=xlab, ylab=ylab) - matlines(newdata$x, cb, lty=c(1,2,2), col=1) - annotations(m0) + matlines(newdata$x, cb, lty=c(1,2,2), col=1) + annotations(m0) }, "Residuals"={ par(mfrow=c(2,2)) @@ -109,30 +107,30 @@ polyGui <- function(x, y, data, er=0.05){ ##------------------------------------------- ## Building the GUI. ## - w <- gwindow(title="Polynomial regression", visible=FALSE) - g <- ggroup(container=w, horizontal=FALSE) - gg_label <- ggroup(container=g) - dlabel <- glabel(text="Polynomial degree:", - container=gg_label) - degree <- gedit(text=1, width=2, coerce.with=as.integer, - handler=draw.poly, action=list(val=0L), - container=gg_label) - gg_buttons <- ggroup(container=g) - gminus <- gbutton(text="-", - handler=draw.poly, - action=list(val=-1L), - container=gg_buttons) - gplus <- gbutton(text="+", - handler=draw.poly, - action=list(val=1L), - container=gg_buttons) - gg_radio <- ggroup(container=g) - plottype <- gradio(items=c("Scatter plot", "Residuals"), - horizontal=TRUE, - handler=draw.poly, - action=list(val=0L), - container=gg_radio) + w <- gWidgets::gwindow(title="Polynomial regression", visible=FALSE) + g <- gWidgets::ggroup(container=w, horizontal=FALSE) + gg_label <- gWidgets::ggroup(container=g) + dlabel <- gWidgets::glabel(text="Polynomial degree:", + container=gg_label) + degree <- gWidgets::gedit(text=1, width=2, coerce.with=as.integer, + handler=draw.poly, action=list(val=0L), + container=gg_label) + gg_buttons <- gWidgets::ggroup(container=g) + gminus <- gWidgets::gbutton(text="-", + handler=draw.poly, + action=list(val=-1L), + container=gg_buttons) + gplus <- gWidgets::gbutton(text="+", + handler=draw.poly, + action=list(val=1L), + container=gg_buttons) + gg_radio <- gWidgets::ggroup(container=g) + plottype <- gWidgets::gradio(items=c("Scatter plot", "Residuals"), + horizontal=TRUE, + handler=draw.poly, + action=list(val=0L), + container=gg_radio) do.call(what=draw.poly, args=list(h=list(degree=1L))) - visible(w) <- TRUE + gWidgets::visible(w) <- TRUE invisible() } diff --git a/R/runAllChunks.R b/R/runAllChunks.R index cc7ff57f028f42cfeddd4b718f60ab2b7d9e84fe..f7b974a910d2b6162bd167086cdab0e794c7eec1 100644 --- a/R/runAllChunks.R +++ b/R/runAllChunks.R @@ -3,13 +3,12 @@ #' @name runAllChunks #' #' @description This function was developed to run all chunks in a knitr -#' Rmd (R markdown) file at once. Mainly for exploring and debugging -#' purposes. +#' Rmd (R markdown) file at once. Mainly for exploring and debugging +#' purposes. #' #' @param Rmd the name of the Rmd file. -#' #' @param envir the environment in which the chunks will be -#' evaluated. By default it is the GlobalEnv. +#' evaluated. By default it is the GlobalEnv. #' #' @references This function was based on this #' \href{http://stackoverflow.com/questions/24753969/knitr-run-all-chunks-in-an-rmarkdown-document}{SO @@ -17,8 +16,6 @@ #' #' @return Objects created in the chunks from the Rmd file. #' -#' @import knitr -#' #' @author Fernando Mayer, \email{fernando.mayer@@ufpr.br} #' #' @export @@ -29,6 +26,6 @@ runAllChunks <- function(Rmd, envir = globalenv()){ } tempR <- tempfile(tmpdir = ".", fileext = ".R") on.exit(unlink(tempR)) - purl(Rmd, output = tempR) + knitr::purl(Rmd, output = tempR) sys.source(tempR, envir = envir) } diff --git a/R/yscale.components.right.R b/R/yscale.components.right.R index afbce1c98e725548dcc99440d8deb818de8aedcb..7e6995b9222209c014ae320e911f22ed4e9b14e3 100644 --- a/R/yscale.components.right.R +++ b/R/yscale.components.right.R @@ -37,7 +37,7 @@ #' p3 <- xyplot(yield~K|N+P, data=npk, #' scales=list(y=list(relation="free", alternating=2)), #' ylab=NULL, ylab.right="Yield", -#' yscale.component=yscale.component.right, +#' yscale.component=yscale.components.right, #' between=list(x=0.5, y=0.2), #' par.settings=list( #' layout.widths=list( @@ -48,7 +48,7 @@ #' ) #' useOuterStrips(p3) #' -yscale.component.right <- function(...){ +yscale.components.right <- function(...){ ans <- yscale.components.default(...) ans$right <- ans$left ans$left <- NULL diff --git a/buildPkg.R b/buildPkg.R index e531485abbcce063c25caf9a3a48e1240c407e47..367df497d444ae28b717cd66254fbe924ba4a528 100644 --- a/buildPkg.R +++ b/buildPkg.R @@ -1,3 +1,4 @@ + ## Script to build and verify the package ## Set working directory @@ -44,10 +45,29 @@ build(manual = TRUE, vignettes = FALSE) # build the binary version for windows (not used) # build_win() +##---------------------------------------------------------------------- +## Test installation. + ## Test install with install.packages pkg <- paste0("../legTools_", packageVersion("legTools"), ".tar.gz") install.packages(pkg, repos = NULL) +## Test using devtools::install_git(). +libTest <- "~/R/" +if (file.exists(libTest)){ + file.remove(libTest) +} +dir.create(path=libTest) + +.libPaths(new=libTest); .libPaths() + +install_git(url="http://git.leg.ufpr.br/leg/legTools.git", + branch="issue#9") + +library(legTools) +packageVersion("legTools") +ls("package:legTools") + ##---------------------------------------------------------------------- ## Package vignette. ## Based on: http://r-pkgs.had.co.nz/vignettes.html @@ -55,6 +75,7 @@ install.packages(pkg, repos = NULL) ## Create the vignette template. Do just once. use_vignette("PimentelGomes") + ##====================================================================== ## Sending package tarballs and manual to remote server to be ## downloadable diff --git a/data-raw/cassavaYield.R b/data-raw/cassavaYield.R index 249177652586b7e681d46791e5c219d2c827688f..28a39a046edc776dafaa6903ecac7d76f5a6f09a 100644 --- a/data-raw/cassavaYield.R +++ b/data-raw/cassavaYield.R @@ -6,6 +6,10 @@ cassavaYield <- read.table("http://www.leg.ufpr.br/~walmes/data/pimentel_mandioc names(cassavaYield) <- c("block", "variety", "yield") str(cassavaYield) +levels(cassavaYield$variety) <- + c("Aipim bravo", "Escondida", "Mamão", "Milagrosa", "Salangó Preta", + "Sutinga") + cassavaYield <- cassavaYield[with(cassavaYield, order(block, variety)),] save(cassavaYield, file="../data/cassavaYield.RData") @@ -32,7 +36,3 @@ par(mfrow=c(2,2)); plot(m0); layout(1) ## ANOVA table. anova(m0) - -library(doBy) -ls <- LSmatrix(m0, effect="variety") -dput(ls) diff --git a/data-raw/cornYield.R b/data-raw/cornYield.R new file mode 100644 index 0000000000000000000000000000000000000000..7bb2f73bec96ac9b10cd3d0a8e645db4936706fd --- /dev/null +++ b/data-raw/cornYield.R @@ -0,0 +1,66 @@ +##---------------------------------------------------------------------- +## Data generation. + +cornYield <- expand.grid(block=gl(4, 1), N=c(-1,1), P=c(-1,1), + K=c(-1,1), KEEP.OUT.ATTRS=FALSE) +cornYield$yield <- c(1.32, 2.12, 1.75, 2.35, 1.80, 2.20, 2.95, 2.96, + 1.66, 2.66, 1.73, 2.58, 1.72, 3.85, 2.62, 3.00, + 2.58, 3.56, 2.86, 2.75, 2.72, 3.20, 2.25, 2.75, + 2.26, 2.08, 1.95, 2.70, 2.95, 3.28, 2.40, 3.35) +str(cornYield) + +save(cornYield, file="../data/cornYield.RData") + +##---------------------------------------------------------------------- +## Examples. + +library(lattice) +library(latticeExtra) + +data(cornYield) +str(cornYield) + +xyplot(yield~N|P, groups=K, + data=cornYield, type=c("p", "a"), + ylab=expression(Yield~(ton~ha^{-1})), + xlab="Nutrient level") + +xyplot(yield~N, groups=interaction(P, K), + data=cornYield, type=c("p", "a"), + auto.key=list(columns=2), + ylab=expression(Yield~(ton~ha^{-1})), + xlab="Nutrient level") + +m0 <- lm(yield~block+(N+P+K)^3, data=cornYield) +par(mfrow=c(2,2)); plot(m0); layout(1) +anova(m0) + +m1 <- update(m0, .~block+N+K) +par(mfrow=c(2,2)); plot(m1); layout(1) + +anova(m0, m1) +anova(m1) + +summary(m1) + +pred <- expand.grid(block="1", + N=seq(-1, 1, by=0.1), + K=seq(-1, 1, by=0.1)) +pred$mu <- predict(m1, newdata=pred) + +wireframe(mu~N+K, data=pred, + scales=list(arrows=FALSE), + zlab=list(expression(Yield~(ton~ha^{-1})), rot=90), + drape=TRUE, cuts=20, + col.regions=colorRampPalette( + color=brewer.pal(n=11, name="Spectral"))(21)) + +levelplot(mu~N+K, data=pred, aspect=1, + main=expression(Yield~(ton~ha^{-1})), + col.regions=colorRampPalette( + color=brewer.pal(n=11, name="Spectral"))) + +rm(list=ls()) +load("../data/cornYield.RData") +ls() +str(cornYield) diff --git a/data-raw/cornYield2.R b/data-raw/cornYield2.R new file mode 100644 index 0000000000000000000000000000000000000000..91ea8b902abe37477b93f48e3b9bd355da4d0f9c --- /dev/null +++ b/data-raw/cornYield2.R @@ -0,0 +1,38 @@ +##---------------------------------------------------------------------- +## Data generation. + +## cornYield2 <- read.table("clipboard", header=TRUE, sep="\t") +cornYield2 <- data.frame( + N=c(0L, 0L, 45L, 45L, 45L, 45L, 45L, 45L, 90L), + P=c(0L, 45L, 0L, 45L, 45L, 45L, 45L, 90L, 45L), + K=c(0L, 30L, 30L, 0L, 30L, 30L, 60L, 30L, 30L), + limestone=c(0L, 0L, 0L, 0L, 0L, 1L, 0L, 0L, 0L), + yield=c(4.192, 4.427, 4.146, 5.029, 5.29, 5.325, 5.275, 5.465, + 5.39)) +str(cornYield2) + +save(cornYield2, file="../data/cornYield2.RData") + +##---------------------------------------------------------------------- +## Examples. + +library(lattice) +library(latticeExtra) + +data(cornYield2) +str(cornYield2) + +## Axial triple factorial with 2 controls. +ftable(xtabs(~N+P+K, data=cornYield2)) + +xyplot(yield~N+P+K, + groups=as.integer(limestone==1 | (N+P+K)==0), + data=cornYield2, type=c("p", "a"), + auto.key=TRUE, + ylab=expression(Yield~(ton~ha^{-1})), + xlab="Nutrient content") + +rm(list=ls()) +load("../data/cornYield2.RData") +ls() +str(cornYield2) diff --git a/data-raw/filterCake.R b/data-raw/filterCake.R new file mode 100644 index 0000000000000000000000000000000000000000..52aa6d39a650d1b02ad9ca24e672180f69b919e9 --- /dev/null +++ b/data-raw/filterCake.R @@ -0,0 +1,49 @@ +##---------------------------------------------------------------------- +## Data generation. + +filterCake <- expand.grid(block=gl(4, 1), mineral=c(-1, 1), + cake=c(-1, 1), KEEP.OUT.ATTRS=FALSE) + +filterCake$y <- c(18.0, 8.6, 9.4, 11.4, 20.6, 21.0, 18.6, 20.6, 19.6, + 15.0, 14.6, 15.8, 19.2, 19.6, 18.4, 20.2) + +str(filterCake) + +save(filterCake, file="../data/filterCake.RData") + +##---------------------------------------------------------------------- +## Examples. + +library(lattice) +library(latticeExtra) + +data(filterCake) +str(filterCake) + +xyplot(y~cake, groups=mineral, + auto.key=list(title="Mineral", columns=2), + data=filterCake, type=c("p", "a"), + ylab="y", + xlab="Filter cake level") + +m0 <- lm(y~block+(cake+mineral)^2, data=filterCake) +par(mfrow=c(2,2)); plot(m0); layout(1) +anova(m0) + +summary(m0) + +filterCake$Mineral <- factor(filterCake$mineral, + labels=c("absent", "present")) + +m1 <- aov(y~block+Mineral/cake, data=filterCake) +anova(m1) + +## Split SS to see effect of cake in each level of mineral. +summary(m1, split=list("Mineral:cake"=list("absent"=1, "present"=2))) + +summary.lm(m1) + +rm(list=ls()) +load("../data/filterCake.RData") +ls() +str(filterCake) diff --git a/data-raw/mangoAcidity.R b/data-raw/mangoAcidity.R new file mode 100644 index 0000000000000000000000000000000000000000..f42f67c8007267097eb1ad385bba960ead5727e1 --- /dev/null +++ b/data-raw/mangoAcidity.R @@ -0,0 +1,45 @@ +##---------------------------------------------------------------------- +## Data generation. + +mangoAcidity <- expand.grid(variety=c("Bourbon", "Brasil", "Extrema", + "Maçã", "Non Plus Ultra", + "Oliveira"), + year=c(1957:1959), + month=c("N", "D", "J"), + KEEP.OUT.ATTRS=FALSE) +mangoAcidity$acid <- c(28.2, 38.3, 37.6, 47.2, 36.4, 40.0, 24.7, 32.0, + 39.0, 47.7, 35.3, 30.1, 16.4, 38.4, 50.3, 50.2, + 40.1, 30.0, 6.0, 5.0, 6.0, 6.2, 7.9, 6.0, 6.2, + 3.6, 6.6, 6.9, 10.2, 7.0, 6.9, 4.0, 6.9, 7.9, + 9.8, 8.4, 4.6, 4.6, 5.4, 5.2, 4.9, 6.1, 4.4, + 4.2, 5.4, 4.2, 6.8, 3.5, 5.0, 3.8, 5.0, 5.0, + 7.0, 4.8) +str(mangoAcidity) + +save(mangoAcidity, file="../data/mangoAcidity.RData") + +##---------------------------------------------------------------------- +## Examples. + +library(lattice) +library(latticeExtra) + +data(mangoAcidity) +str(mangoAcidity) + +## reshape::cast() can also be used. +with(mangoAcidity, + ftable(tapply(acid, + list(variety, year, month), + FUN=identity))) + +xyplot(acid~month|variety, groups=year, + data=mangoAcidity, type=c("p", "a"), + auto.key=TRUE, + ylab="Acidity", + xlab="Month") + +rm(list=ls()) +load("../data/mangoAcidity.RData") +ls() +str(mangoAcidity) diff --git a/data-raw/potatoyield.R b/data-raw/potatoYield.R similarity index 53% rename from data-raw/potatoyield.R rename to data-raw/potatoYield.R index c1b160085614dd92684329514b6abec9644df9c2..6dea6d04af80644167d4cfdd90cfc6e8cb86f098 100644 --- a/data-raw/potatoyield.R +++ b/data-raw/potatoYield.R @@ -1,26 +1,26 @@ ##---------------------------------------------------------------------- ## Data generation. -potatoyield <- read.table("http://www.leg.ufpr.br/~walmes/data/pimentel_batatinha.txt", +potatoYield <- read.table("http://www.leg.ufpr.br/~walmes/data/pimentel_batatinha.txt", header=TRUE, sep="\t") -names(potatoyield) <- c("block", "variety", "yield") -str(potatoyield) +names(potatoYield) <- c("block", "variety", "yield") +str(potatoYield) -potatoyield <- potatoyield[with(potatoyield, order(block, variety)),] +potatoYield <- potatoYield[with(potatoYield, order(block, variety)),] -save(potatoyield, file="../data/potatoyield.RData") +save(potatoYield, file="../data/potatoYield.RData") ##---------------------------------------------------------------------- ## Examples. require(lattice) -xyplot(yield~variety, data=potatoyield, +xyplot(yield~variety, data=potatoYield, groups=block, type="o", ylab=expression(Yield~(t~ha^{-1})), xlab="Variety") rm(list=ls()) -load("../data/potatoyield.RData") +load("../data/potatoYield.RData") ls() -str(potatoyield) +str(potatoYield) diff --git a/data-raw/sugarcaneYield4.R b/data-raw/sugarcaneYield4.R new file mode 100644 index 0000000000000000000000000000000000000000..3050b59eef4a0e8f857b92477eb8a8e316df9f2f --- /dev/null +++ b/data-raw/sugarcaneYield4.R @@ -0,0 +1,85 @@ +##---------------------------------------------------------------------- +## Data generation. + +sugarcaneYield4 <- read.table("http://www.leg.ufpr.br/~walmes/data/pimentel_npk2.txt", + header=TRUE, sep="\t") +names(sugarcaneYield4)[c(1,6)] <- c("block", "yield") +sugarcaneYield4 <- transform(sugarcaneYield4, rept=factor(rept)) +str(sugarcaneYield4) + +sugarcaneYield4 <- sugarcaneYield4[ + with(sugarcaneYield4, order(block, rept, N, P, K)),] + +save(sugarcaneYield4, file="../data/sugarcaneYield4.RData") + +##---------------------------------------------------------------------- +## Examples. + +library(lattice) +library(latticeExtra) +library(multcomp) + +data(sugarcaneYield4) +str(sugarcaneYield4) + +xyplot(yield~N|P, groups=K, + auto.key=list(title="Potassim level", columns=3), + strip=strip.custom(var.name="Phosphorus", strip.names=TRUE, + strip.levels=TRUE, sep=": "), + data=sugarcaneYield4, type=c("p", "a"), + ylab=expression(Yield~(ton~ha^{-1})), + xlab="Nitrogen level level") + +## Sums in each cell combination. +addmargins(with(sugarcaneYield4, tapply(yield, list(P, N), FUN=sum))) +addmargins(with(sugarcaneYield4, tapply(yield, list(K, N), FUN=sum))) +addmargins(with(sugarcaneYield4, tapply(yield, list(K, P), FUN=sum))) + +sugarcaneYield4 <- transform(sugarcaneYield4, + blockr=interaction(block, rept), + nitro=factor(N), + phosp=factor(P), + potas=factor(K)) +str(sugarcaneYield4) + +m0 <- lm(yield~blockr+(nitro+phosp+potas)^3, data=sugarcaneYield4) +par(mfrow=c(2,2)); plot(m0); layout(1) +anova(m0) + +m1 <- update(m0, .~blockr+(nitro+phosp)^2) +par(mfrow=c(2,2)); plot(m1); layout(1) + +anova(m0, m1) +anova(m1) + +m2 <- aov(yield~blockr+nitro/phosp, data=sugarcaneYield4) +anova(m2) + +PinN <- sapply(paste0("nitro", levels(sugarcaneYield4$nitro)), + FUN=grep, x=names(coef(m2))[m2$assign==3L], + simplify=FALSE) + +summary(m2, split=list("nitro:phosp"=PinN)) + +X <- model.matrix(m1) +X + +aggregate(X~nitro+phosp, data=sugarcaneYield4, FUN=mean) + +## It is better use multcomp::LSmatrix(). +L <- aggregate(X~nitro+phosp, data=sugarcaneYield4, FUN=mean) +rownames(L) <- with(L, paste0("N", nitro, ":P", phosp)) +L <- as.matrix(L[, colnames(X)]) +str(L) + +## Least squares means for N:P combinations. +L%*%coef(m1) + +g1 <- glht(m1, linfct=L) + +confint(g1, calpha=univariate_calpha()) + +rm(list=ls()) +load("../data/sugarcaneYield4.RData") +ls() +str(sugarcaneYield4) diff --git a/data-raw/vinasseFert.R b/data-raw/vinasseFert.R new file mode 100644 index 0000000000000000000000000000000000000000..be78f45e285e2a4c57869c6660cded7523392a86 --- /dev/null +++ b/data-raw/vinasseFert.R @@ -0,0 +1,45 @@ +##---------------------------------------------------------------------- +## Data generation. + +vinasseFert <- expand.grid(block=gl(4, 1), mineral=c(-1, 1), + vinasse=c(-1, 1), KEEP.OUT.ATTRS=FALSE) + +vinasseFert$y <- c(0.020, 0.630, 0.110, 0.115, 0.020, 2.005, 0.700, + 1.120, 3.040, 4.760, 5.860, 5.520, 5.150, 4.770, + 3.960, 5.230) + +str(vinasseFert) + +save(vinasseFert, file="../data/vinasseFert.RData") + +##---------------------------------------------------------------------- +## Examples. + +library(lattice) +library(latticeExtra) + +data(vinasseFert) +str(vinasseFert) + +xyplot(y~vinasse, groups=mineral, + auto.key=list(title="Mineral", columns=2), + data=vinasseFert, type=c("p", "a"), + ylab="y", + xlab="Vinasse level") + +m0 <- lm(y~block+(vinasse+mineral)^2, data=vinasseFert) +par(mfrow=c(2,2)); plot(m0); layout(1) +anova(m0) + +m1 <- update(m0, .~block+vinasse) +par(mfrow=c(2,2)); plot(m1); layout(1) + +anova(m0, m1) +anova(m1) + +summary(m1) + +rm(list=ls()) +load("../data/vinasseFert.RData") +ls() +str(vinasseFert) diff --git a/data-raw/wgpigs.R b/data-raw/wgPigs.R similarity index 58% rename from data-raw/wgpigs.R rename to data-raw/wgPigs.R index 5a3cfe8076219634b0b57d7109c85ef40646b334..8beb3af0edf06bd2d3004d30aec9b4dbf608533a 100644 --- a/data-raw/wgpigs.R +++ b/data-raw/wgPigs.R @@ -1,38 +1,38 @@ ##---------------------------------------------------------------------- ## Data generation. -wgpigs <- read.table("http://www.leg.ufpr.br/~walmes/data/pimentel_racoes.txt", +wgPigs <- read.table("http://www.leg.ufpr.br/~walmes/data/pimentel_racoes.txt", header=TRUE, sep="\t") -names(wgpigs) <- c("ft","wg") -str(wgpigs) +names(wgPigs) <- c("ft","wg") +str(wgPigs) -save(wgpigs, file="../data/wgpigs.RData") +save(wgPigs, file="../data/wgPigs.RData") ##---------------------------------------------------------------------- ## Examples. require(lattice) -xyplot(wg~ft, data=wgpigs, +xyplot(wg~ft, data=wgPigs, ylab="Weight gain (kg)", xlab="Feeding type") rm(list=ls()) -load("../data/wgpigs.RData") +load("../data/wgPigs.RData") ls() -str(wgpigs) +str(wgPigs) ##---------------------------------------------------------------------- -write.table(x=wgpigs, file="wgpigs.txt", +write.table(x=wgPigs, file="wgPigs.txt", sep="\t", quote=FALSE, row.names=FALSE) ## Port and IP. u <- scan(n=2, what=character()) -cmd <- paste0("scp -P ", u[1], " wgpigs.txt leg@", u[2], +cmd <- paste0("scp -P ", u[1], " wgPigs.txt leg@", u[2], ":/home/leg/public_html/legTools/dataset") system(cmd) -url <- "http://blog.leg.ufpr.br/~leg/legTools/dataset/wgpigs.txt" +url <- "http://blog.leg.ufpr.br/~leg/legTools/dataset/wgPigs.txt" browseURL(url) -wgpigs <- read.table(file=url, header=TRUE, sep="\t") +wgPigs <- read.table(file=url, header=TRUE, sep="\t") diff --git a/data-raw/wgPigs2.R b/data-raw/wgPigs2.R new file mode 100644 index 0000000000000000000000000000000000000000..1e72f6b275fde66f0ed88e4c09acbb84a12fea4e --- /dev/null +++ b/data-raw/wgPigs2.R @@ -0,0 +1,63 @@ +##---------------------------------------------------------------------- +## Data generation. + +wgPigs2 <- read.table("http://www.leg.ufpr.br/~walmes/data/pimentel_castracao.txt", + header=TRUE, sep="\t") +names(wgPigs2) <- c("litter", "size", "age", "wg") +wgPigs2 <- transform(wgPigs2, litter=factor(litter), size=factor(size)) + +aggregate(wg~age, data=wgPigs2, FUN=mean) + +wgPigs2$age <- factor(wgPigs2$age, + levels=levels(wgPigs2$age)[c(4,3,1,2)], + labels=c("control", "7", "21", "56")) +str(wgPigs2) + +save(wgPigs2, file="../data/wgPigs2.RData") + +##---------------------------------------------------------------------- +## Examples. + +library(lattice) + +data(wgPigs2) +str(wgPigs2) + +xyplot(wg~age, data=wgPigs2, groups=litter, + ylab="Weight gain (kg)", + xlab="Age at castration (days)") + +m0 <- lm(wg~litter+size+age, data=wgPigs2) +par(mfrow=c(2,2)); plot(m0); layout(1) +anova(m0) + +summary(m0) + +library(multcomp) +summary(glht(m0, linfct=mcp(age="Dunnet")), + test=adjusted(type="single-step")) + +m1 <- glm(wg~litter+size+age, data=wgPigs2, family=Gamma) +m2 <- glm(wg~litter+size+age, data=wgPigs2, + family=Gamma(link="log")) +m3 <- glm(wg~litter+size+age, data=wgPigs2, + family=Gamma(link="identity")) + +rbind(logLik(m0), + logLik(m1), + logLik(m2), + logLik(m3)) + +par(mfrow=c(2,2)); plot(m1); layout(1) +anova(m1, test="F") +anova(m2, test="F") +anova(m3, test="F") + +summary(glht(m3, linfct=mcp(age="Dunnet")), + test=adjusted(type="single-step")) + +rm(list=ls()) +load("../data/wgPigs2.RData") +ls() +str(wgPigs2) + diff --git a/data/cassavaYield.RData b/data/cassavaYield.RData index 07cdb35446a418b6d57821875406864be2fff9a8..6fa7094064f95fc01ec7dc5f087b8d8fafb1b09a 100644 Binary files a/data/cassavaYield.RData and b/data/cassavaYield.RData differ diff --git a/data/cornYield.RData b/data/cornYield.RData new file mode 100644 index 0000000000000000000000000000000000000000..ee9c3dbf0c11c7172f7254b18bfeafe008b0aee8 Binary files /dev/null and b/data/cornYield.RData differ diff --git a/data/cornYield2.RData b/data/cornYield2.RData new file mode 100644 index 0000000000000000000000000000000000000000..2fbd34fbf48dd46f8fadf8ddef7c60d6482574b7 Binary files /dev/null and b/data/cornYield2.RData differ diff --git a/data/filterCake.RData b/data/filterCake.RData new file mode 100644 index 0000000000000000000000000000000000000000..a0de62bd28138af476f33e6348a87bfd0ee00b62 Binary files /dev/null and b/data/filterCake.RData differ diff --git a/data/mangoAcidity.RData b/data/mangoAcidity.RData new file mode 100644 index 0000000000000000000000000000000000000000..d6dc2ed24a5e71f3bc05a1ef56396c99f5e479d6 Binary files /dev/null and b/data/mangoAcidity.RData differ diff --git a/data/potatoYield.RData b/data/potatoYield.RData new file mode 100644 index 0000000000000000000000000000000000000000..b640671588ce1ba3ab701862821577e03eda9e25 Binary files /dev/null and b/data/potatoYield.RData differ diff --git a/data/potatoyield.RData b/data/potatoyield.RData deleted file mode 100644 index c650a954d79af8e08247412563bcb3aa15f310ef..0000000000000000000000000000000000000000 Binary files a/data/potatoyield.RData and /dev/null differ diff --git a/data/sugarcaneYield4.RData b/data/sugarcaneYield4.RData new file mode 100644 index 0000000000000000000000000000000000000000..e8821cf112ad01881612e566986a55844359b73c Binary files /dev/null and b/data/sugarcaneYield4.RData differ diff --git a/data/vinasseFert.RData b/data/vinasseFert.RData new file mode 100644 index 0000000000000000000000000000000000000000..68936a5086a615fd434fb664c2fe78942a8ab486 Binary files /dev/null and b/data/vinasseFert.RData differ diff --git a/data/wgPigs.RData b/data/wgPigs.RData new file mode 100644 index 0000000000000000000000000000000000000000..efecff0ddff82bc4119f7b5eb7ffbf6e7c191ddd Binary files /dev/null and b/data/wgPigs.RData differ diff --git a/data/wgPigs2.RData b/data/wgPigs2.RData new file mode 100644 index 0000000000000000000000000000000000000000..f80771e612a39e20723c6ff3467ae4eb473d3950 Binary files /dev/null and b/data/wgPigs2.RData differ diff --git a/data/wgpigs.RData b/data/wgpigs.RData deleted file mode 100644 index d44077aacfd23b90dfbc7f015257af67796e1c3c..0000000000000000000000000000000000000000 Binary files a/data/wgpigs.RData and /dev/null differ diff --git a/legTools.bmk b/legTools.bmk new file mode 100644 index 0000000000000000000000000000000000000000..3189f1d18322ad5b3161e3423fa6c75482e09e33 --- /dev/null +++ b/legTools.bmk @@ -0,0 +1,239 @@ +;;;; Emacs Bookmark Format Version 1 ;;;; +;;; This format is meant to be slightly human-readable; +;;; nevertheless, you probably don't want to edit it. +;;; -*- End Of Bookmark File Format Version Stamp -*- +(#1=(#("legTools@git.leg" 0 16 + (bmkp-full-record #1#)) + (time 22015 20561 731318 645000) + (visits . 0) + (filename . " - no file -") + (location . "http://git.leg.ufpr.br/leg/legTools") + (handler . bmkp-jump-url-browse)) +#1=(#("directories" 0 11 + (bmkp-full-record #1#)) + (buffer-name . "legTools") + (front-context-string . "legTools.R\n -rw") + (rear-context-string . "79 Set 20 16:41 ") + (front-context-region-string) + (rear-context-region-string) + (visits . 1) + (time 22015 20600 851351 336000) + (created 22015 19730 128634 379000) + (position . 1541) + (filename . "/home/walmes/GitLab/legTools/") + (dired-directory . "~/GitLab/legTools/") + (dired-marked) + (dired-switches . "-al") + (dired-subdirs + ("/home/walmes/GitLab/legTools/data-raw/") + ("/home/walmes/GitLab/legTools/R/")) + (dired-hidden-dirs "/home/walmes/GitLab/legTools/") + (handler . bmkp-jump-dired)) +#1=(#("mangoAcidity" 0 12 + (bmkp-full-record #1#)) + (filename . "~/GitLab/legTools/R/legTools.R") + (buffer-name . "legTools.R") + (front-context-string . "@name mangoAcidi") + (rear-context-string . "())\n#'\nNULL\n\n#' ") + (front-context-region-string) + (rear-context-region-string) + (visits . 0) + (time . #2=(22014 65331 826950 768000)) + (created . #2#) + (position . 24814)) +#1=(#("sugarcaneYield4" 0 15 + (bmkp-full-record #1#)) + (filename . "~/GitLab/legTools/R/legTools.R") + (buffer-name . "legTools.R") + (front-context-string . "@name sugarcaneY") + (rear-context-string . "\n#'\n#'\nNULL\n\n#' ") + (front-context-region-string) + (rear-context-region-string) + (visits . 0) + (time . #2=(22014 55562 242485 989000)) + (created . #2#) + (position . 21758)) +#1=(#("filterCake" 0 10 + (bmkp-full-record #1#)) + (filename . "~/GitLab/legTools/R/legTools.R") + (buffer-name . "legTools.R") + (front-context-string . "@name filterCake") + (rear-context-string . "m1)\n#'\nNULL\n\n#' ") + (front-context-region-string) + (rear-context-region-string) + (visits . 0) + (time . #2=(22014 51467 333208 857000)) + (created . #2#) + (position . 20038)) +#1=(#("vinasseFert" 0 11 + (bmkp-full-record #1#)) + (filename . "~/GitLab/legTools/R/legTools.R") + (buffer-name . "legTools.R") + (front-context-string . "@name vinasseFer") + (rear-context-string . ")))\n#'\nNULL\n\n#' ") + (front-context-region-string) + (rear-context-region-string) + (visits . 0) + (time . #2=(22014 51452 901653 865000)) + (created . #2#) + (position . 18556)) +#1=(#("kornYield" 0 9 + (bmkp-full-record #1#)) + (filename . "~/GitLab/legTools/R/legTools.R") + (buffer-name . "legTools.R") + (front-context-string . "@name kornYield\n") + (rear-context-string . "\"))\n#'\nNULL\n\n#' ") + (front-context-region-string) + (rear-context-region-string) + (visits . 0) + (time . #2=(22014 6386 355822 993000)) + (created . #2#) + (position . 16336)) +#1=(#("wgpigs2" 0 7 + (bmkp-full-record #1#)) + (end-position . 14001) + (filename . "~/GitLab/legTools/R/legTools.R") + (buffer-name . "legTools.R") + (front-context-string . "@name wgpigs2\n#'") + (rear-context-string . "an)\n#'\nNULL\n\n#' ") + (front-context-region-string) + (rear-context-region-string) + (visits . 3) + (time 22014 6373 782337 593000) + (created 22014 2449 877392 862000) + (position . 14001)) +#1=(#("sugarcaneYield3" 0 15 + (bmkp-full-record #1#)) + (filename . "~/GitLab/legTools/R/legTools.R") + (buffer-name . "legTools.R") + (front-context-string . "@name sugarcaneY") + (rear-context-string . "an)\n#'\nNULL\n\n#' ") + (front-context-region-string) + (rear-context-region-string) + (visits . 2) + (time 22014 6373 622489 1000) + (created 22014 2438 565160 262000) + (position . 11050)) +#1=(#("sugarcaneYield2" 0 15 + (bmkp-full-record #1#)) + (filename . "~/GitLab/legTools/R/legTools.R") + (buffer-name . "legTools.R") + (front-context-string . "@name sugarcaneY") + (rear-context-string . "y\")\n#'\nNULL\n\n#' ") + (front-context-region-string) + (rear-context-region-string) + (visits . 1) + (time 22014 6373 470955 812000) + (created 22014 2428 365189 950000) + (position . 9217)) +#1=(#("sugarcaneYield" 0 14 + (bmkp-full-record #1#)) + (filename . "~/GitLab/legTools/R/legTools.R") + (buffer-name . "legTools.R") + (front-context-string . "@name sugarcaneY") + (rear-context-string . "y\")\n#'\nNULL\n\n#' ") + (front-context-region-string) + (rear-context-region-string) + (visits . 1) + (time 22014 6373 318366 504000) + (created 22014 2414 357030 236000) + (position . 8152)) +#1=(#("cassavaYield" 0 12 + (bmkp-full-record #1#)) + (filename . "~/GitLab/legTools/R/legTools.R") + (buffer-name . "legTools.R") + (front-context-string . "@name cassavaYie") + (rear-context-string . "2))\n#'\nNULL\n\n#' ") + (front-context-region-string) + (rear-context-region-string) + (visits . 1) + (time 22014 6373 167010 949000) + (created 22014 2401 421345 289000) + (position . 6963)) +#1=(#("defoliation" 0 11 + (bmkp-full-record #1#)) + (filename . "~/GitLab/legTools/R/legTools.R") + (buffer-name . "legTools.R") + (front-context-string . "@name defoliatio") + (rear-context-string . "l\")\n#'\nNULL\n\n#' ") + (front-context-region-string) + (rear-context-region-string) + (visits . 1) + (time 22014 6373 30840 723000) + (created 22014 2388 893464 613000) + (position . 3566)) +#1=(#("plowing" 0 7 + (bmkp-full-record #1#)) + (filename . "~/GitLab/legTools/R/legTools.R") + (buffer-name . "legTools.R") + (front-context-string . "@name plowing\n#'") + (rear-context-string . "y\")\n#'\nNULL\n\n#' ") + (front-context-region-string) + (rear-context-region-string) + (visits . 1) + (time 22014 6372 878551 941000) + (created 22014 2377 645195 878000) + (position . 2330)) +#1=(#("potatoYield" 0 11 + (bmkp-full-record #1#)) + (filename . "~/GitLab/legTools/R/legTools.R") + (buffer-name . "legTools.R") + (front-context-string . "@name potatoYiel") + (rear-context-string . "e\")\n#'\nNULL\n\n#' ") + (front-context-region-string) + (rear-context-region-string) + (visits . 1) + (time 22014 6372 742266 92000) + (created 22014 2364 877635 749000) + (position . 1285)) +#1=(#("wgpigs" 0 6 + (bmkp-full-record #1#)) + (filename . "~/GitLab/legTools/R/legTools.R") + (buffer-name . "legTools.R") + (front-context-string . "@name wgpigs\n#'\n") + (rear-context-string . "gTools\nNULL\n\n#' ") + (front-context-region-string) + (rear-context-region-string) + (visits . 2) + (time 22014 6374 126563 478000) + (created 22014 2268 166496 375000) + (position . 219)) +#1=(#("legTools.R" 0 10 + (bmkp-full-record #1#)) + (annotation) + (tags) + (filename . "~/GitLab/legTools/R/legTools.R") + (buffer-name . "legTools.R") + (front-context-string . "@name legTools\nN") + (rear-context-string . "ype package\n##' ") + (front-context-region-string) + (rear-context-region-string) + (visits . 3) + (time 22014 6373 950617 320000) + (created 22014 2255 246295 352000) + (position . 195)) +#1=(#("DESCRIPTION" 0 11 + (bmkp-full-record #1#)) + (filename . "~/GitLab/legTools/DESCRIPTION") + (buffer-name . "DESCRIPTION") + (front-context-string . "Imports:\n lat") + (rear-context-string . " R (>= 3.2.1)\n") + (front-context-region-string) + (rear-context-region-string) + (visits . 0) + (time . #2=(22014 1949 31996 134000)) + (created . #2#) + (position . 598)) +#1=(#("buildPkg.R" 0 10 + (bmkp-full-record #1#)) + (filename . "~/GitLab/legTools/buildPkg.R") + (buffer-name . "buildPkg.R") + (front-context-string . "library(devtools") + (rear-context-string . "\n}\n\n## Packages\n") + (front-context-region-string) + (rear-context-region-string) + (visits . 2) + (time 22013 63883 15658 195000) + (created 22013 63860 548172 204000) + (position . 207)) +) diff --git a/man/cornYield.Rd b/man/cornYield.Rd new file mode 100644 index 0000000000000000000000000000000000000000..7c7d0580367cb88c9d9e49a22fac3b7036e31580 --- /dev/null +++ b/man/cornYield.Rd @@ -0,0 +1,47 @@ +% Generated by roxygen2 (4.1.1): do not edit by hand +% Please edit documentation in R/legTools.R +\docType{data} +\name{cornYield} +\alias{cornYield} +\title{Corn yield as function of fertilization with NPK} +\format{a \code{data.frame} with 32 records and 4 variables.} +\source{ +Frederico, P. (2009). Curso de EstatÃstica Experimental (15th + ed.). Piracicaba, São Paulo: FEALQ. (page 115) +} +\usage{ +data(cornYield) +} +\description{ +These data are from an \eqn{2^3} factorial experiment + studing the effect of Nitrogen (N), Phosporus (P) and Potassium + (K) on corn yield in a randomized block design. + +\itemize{ + \item \code{block} a factor with 4 levels. + \item \code{N} low (-1) and high (+1) levels of nitrogen. + \item \code{P} low (-1) and high (+1) levels of phosporus. + \item \code{K} low (-1) and high (+1) levels of potassium. + \item \code{yield} corn yield (ton/ha). +} +} +\examples{ +library(lattice) +library(latticeExtra) + +data(cornYield) +str(cornYield) + +xyplot(yield~N|P, groups=K, + data=cornYield, type=c("p", "a"), + ylab=expression(Yield~(ton~ha^{-1})), + xlab="Nutrient level") + +xyplot(yield~N, groups=interaction(P, K), + data=cornYield, type=c("p", "a"), + auto.key=list(columns=2), + ylab=expression(Yield~(ton~ha^{-1})), + xlab="Nutrient level") +} +\keyword{datasets} + diff --git a/man/cornYield2.Rd b/man/cornYield2.Rd new file mode 100644 index 0000000000000000000000000000000000000000..e6f18b139b10b52eb16a3583cb58d9c023e62644 --- /dev/null +++ b/man/cornYield2.Rd @@ -0,0 +1,55 @@ +% Generated by roxygen2 (4.1.1): do not edit by hand +% Please edit documentation in R/legTools.R +\docType{data} +\name{cornYield2} +\alias{cornYield2} +\title{Axial factorial NPK experiment with added treatments} +\format{a \code{data.frame} with 9 records and 5 variables.} +\source{ +Frederico, P. (2009). Curso de EstatÃstica Experimental (15th + ed.). Piracicaba, São Paulo: FEALQ. (page 132) + +Simão, S. (1960). Estudo da planta e dos frutos da mangueira + (\emph{Manginifera indica} L.). Piracicaba, 1960. Thesis. +} +\usage{ +data(sugarcaneYield4) +} +\description{ +These data are from an axial 3 factorial experiment + studing NPK in the yield of corn. Tow controls were added, one is + zer control (no NPK) and the other is central factorial point + plus presence of limestone. + +\itemize{ + \item \code{N} content of nitrogen in the fertilizer. + \item \code{P} content of phosphorus in the fertilizer. + \item \code{K} content of potassium in the fertilizer. + \item \code{limestone} presence (1) or absence of limestone (0). + \item \code{acid} mean of corn yield in 16 locations (ton/ha). +} +} +\details{ +The experiment was caried out in 16 different locations but + only the mean by cell combinations were available in the text + book. +} +\examples{ +library(lattice) +library(latticeExtra) + +data(cornYield2) +str(cornYield2) + +## Axial triple factorial with 2 controls. +ftable(xtabs(~N+P+K, data=cornYield2)) + +xyplot(yield~N+P+K, + groups=as.integer(limestone==1 | (N+P+K)==0), + data=cornYield2, type=c("p", "a"), + auto.key=TRUE, + ylab=expression(Yield~(ton~ha^{-1})), + xlab="Nutrient content") +} +\keyword{datasets} + diff --git a/man/filterCake.Rd b/man/filterCake.Rd new file mode 100644 index 0000000000000000000000000000000000000000..6ddae712d3635d514921f43d8296b20c26f83a62 --- /dev/null +++ b/man/filterCake.Rd @@ -0,0 +1,45 @@ +% Generated by roxygen2 (4.1.1): do not edit by hand +% Please edit documentation in R/legTools.R +\docType{data} +\name{filterCake} +\alias{filterCake} +\title{Fertilization with filter cake and mineral} +\format{a \code{data.frame} with 16 records and 4 variables.} +\source{ +Frederico, P. (2009). Curso de EstatÃstica Experimental (15th + ed.). Piracicaba, São Paulo: FEALQ. (page 120) +} +\usage{ +data(filterCake) +} +\description{ +These data are from an \eqn{2^2} factorial experiment + studing the effect of fertilizaton with filter cake (a residual + from industrial processing of sugar cane) and traditional mineral + fertilization. + +\itemize{ + \item \code{block} a factor with 4 levels. + \item \code{mineral} low (-1) and high (+1) levels of mineral + fertilization. + \item \code{cake} low (-1) and high (+1) levels of fetilization + with filter cake. + \item \code{y} some response variable. The text book doesn't give + any information. +} +} +\examples{ +library(lattice) +library(latticeExtra) + +data(filterCake) +str(filterCake) + +xyplot(y~cake, groups=mineral, + auto.key=list(title="Mineral", columns=2), + data=filterCake, type=c("p", "a"), + ylab="y", + xlab="Filter cake level") +} +\keyword{datasets} + diff --git a/man/loessGui.Rd b/man/loessGui.Rd index 6c5ad1404e9efeed995a7de4eb7c4a52d76d0162..c2901e7a5d4e5320895527583114842648b106b3 100644 --- a/man/loessGui.Rd +++ b/man/loessGui.Rd @@ -12,8 +12,8 @@ loessGui(x, y, data, er = 0.05) \item{data}{an optional \code{data.frame}.} \item{er}{stands for extend range. It is used to extend the plotting -range by a fraction on both sides and directions. Default is -0.05. See \link[grDevices]{extendrange}.} + range by a fraction on both sides and directions. Default is + 0.05. See \link[grDevices]{extendrange}.} } \value{ None is returned by the function, only a GUI is opened. @@ -22,11 +22,11 @@ None is returned by the function, only a GUI is opened. This function opens an interface to control the settings of a loess regression: \itemize{ - \item degree choose the local polynomial degree with a radio + \item degree choose the local polynomial degree with a radio selector; - \item span set the span value that controls the degree of + \item span set the span value that controls the degree of smoothing; - \item center move the x value to be predicted; + \item center move the x value to be predicted; } The elements of the interface change a plot that shows the observed diff --git a/man/mangoAcidity.Rd b/man/mangoAcidity.Rd new file mode 100644 index 0000000000000000000000000000000000000000..85fb633e3498df0486d95aac11912c4d51d5cb39 --- /dev/null +++ b/man/mangoAcidity.Rd @@ -0,0 +1,51 @@ +% Generated by roxygen2 (4.1.1): do not edit by hand +% Please edit documentation in R/legTools.R +\docType{data} +\name{mangoAcidity} +\alias{mangoAcidity} +\title{Acidity of mango fruits by varieties, years and months} +\format{a \code{data.frame} with 54 records and 6 variables.} +\source{ +Frederico, P. (2009). Curso de EstatÃstica Experimental (15th + ed.). Piracicaba, São Paulo: FEALQ. (page 132) + +Simão, S. (1960). Estudo da planta e dos frutos da mangueira + (\emph{Manginifera indica} L.). Piracicaba, 1960. Thesis. +} +\usage{ +data(sugarcaneYield4) +} +\description{ +These data are from an observational study along 3 years + where acidity in fruits of 6 varieties of mango was determined in + Novermber, December and January. + +\itemize{ + \item \code{variety} a categorical variable with 6 levels that + represents mango varieties studied. + \item \code{year} the year of harvesting. + \item \code{month} the month of harvesting. + \item \code{acid} mean of the acidity determined in 3 fruits. +} +} +\examples{ +library(lattice) +library(latticeExtra) + +data(mangoAcidity) +str(mangoAcidity) + +## reshape::cast() can also be used. +with(mangoAcidity, + ftable(tapply(acid, + list(variety, year, month), + FUN=identity))) + +xyplot(acid~month|variety, groups=year, + data=mangoAcidity, type=c("p", "a"), + auto.key=TRUE, + ylab="Acidity", + xlab="Month") +} +\keyword{datasets} + diff --git a/man/plowing.Rd b/man/plowing.Rd index 66fc799e3e867bf1900a1f18a2de5c528d62150e..30c69cacc5761c0d39ad9463b2e461cf81dcf26b 100644 --- a/man/plowing.Rd +++ b/man/plowing.Rd @@ -29,7 +29,7 @@ These data are from an experiment done by the engineer } \examples{ library(lattice) -data(potatoyield) +data(plowing) xyplot(yield~plow|block, data=plowing, type=c("p", "a"), ylab=expression(Yield~(t~ha^{-1})), diff --git a/man/polyGui.Rd b/man/polyGui.Rd index 4b084c8f62269e04cc3dc5a0b1fdb6509a62f177..049c113c519ccc5f715232f86ae97fc5d1c72377 100644 --- a/man/polyGui.Rd +++ b/man/polyGui.Rd @@ -12,18 +12,19 @@ polyGui(x, y, data, er = 0.05) \item{data}{an optional \code{data.frame}.} \item{er}{stands for extend range. It is used to extend the plotting -range by a fraction on both sides and directions. Default is -0.05. See \link[grDevices]{extendrange}.} + range by a fraction on both sides and directions. Default is + 0.05. See \link[grDevices]{extendrange}.} } \value{ None is returned by the function. } \description{ This function opens an interface to control the -polynomial degree in linear regression. It shows the observed values -and the corresponding fitted curve superimposed with confidence bands -(for the fitted values) and also show the residuals plot. It assumes -that \code{gWidgets} and \code{gWidgetstcltk} packages are available. + polynomial degree in linear regression. It shows the observed + values and the corresponding fitted curve superimposed with + confidence bands (for the fitted values) and also show the + residuals plot. It assumes that \code{gWidgets} and + \code{gWidgetstcltk} packages are available. } \examples{ \donttest{ diff --git a/man/potatoyield.Rd b/man/potatoYield.Rd similarity index 89% rename from man/potatoyield.Rd rename to man/potatoYield.Rd index 441fce52b311a438c6aa1f1e765ccf9a585cdbe2..3a0752606e317a05121ac7558ed23f1a5014e590 100644 --- a/man/potatoyield.Rd +++ b/man/potatoYield.Rd @@ -1,8 +1,8 @@ % Generated by roxygen2 (4.1.1): do not edit by hand % Please edit documentation in R/legTools.R \docType{data} -\name{potatoyield} -\alias{potatoyield} +\name{potatoYield} +\alias{potatoYield} \title{Potato variety competition experiment} \format{a \code{data.frame} with 32 records and 3 variables.} \source{ @@ -10,7 +10,7 @@ Frederico, P. (2009). Curso de EstatÃstica Experimental (15th ed.). Piracicaba, São Paulo: FEALQ. (page 76) } \usage{ -data(potatoyield) +data(potatoYield) } \description{ These data are from an experiment done by the engineer @@ -27,9 +27,9 @@ These data are from an experiment done by the engineer } \examples{ library(lattice) -data(potatoyield) +data(potatoYield) -plot(yield~variety, data=potatoyield, +plot(yield~variety, data=potatoYield, groups=block, type="o", ylab=expression(Yield~(t~ha^{-1})), xlab="Variety") diff --git a/man/runAllChunks.Rd b/man/runAllChunks.Rd index 3602646e0ca20153358dd7f3bf75304c4902a54f..e8abbbe62431f8cd6e91f81ca19224c8c065bfc8 100644 --- a/man/runAllChunks.Rd +++ b/man/runAllChunks.Rd @@ -10,15 +10,15 @@ runAllChunks(Rmd, envir = globalenv()) \item{Rmd}{the name of the Rmd file.} \item{envir}{the environment in which the chunks will be -evaluated. By default it is the GlobalEnv.} + evaluated. By default it is the GlobalEnv.} } \value{ Objects created in the chunks from the Rmd file. } \description{ This function was developed to run all chunks in a knitr -Rmd (R markdown) file at once. Mainly for exploring and debugging -purposes. + Rmd (R markdown) file at once. Mainly for exploring and debugging + purposes. } \author{ Fernando Mayer, \email{fernando.mayer@ufpr.br} diff --git a/man/sugarcaneYield3.Rd b/man/sugarcaneYield3.Rd index b7418bf52cefa4b442e48191f3ac4cce9dedaa33..048af7a28000f61f627a4957d2ed5d733898fa35 100644 --- a/man/sugarcaneYield3.Rd +++ b/man/sugarcaneYield3.Rd @@ -18,20 +18,20 @@ These data are from an experiment done in a latin square experimental unit. \itemize{ - \item \code{row} the rows of the latin square that controls in + \item \code{row} the rows of the latin square that controls in one dimention. A categorical unordered factor with 6 levels. - \item \code{col} the columns of the latin square that controls in + \item \code{col} the columns of the latin square that controls in one dimention perpendicular to the previus. A categorical unordered factor with 6 levels. - \item \code{fertil} a categorical unordered factor with 6 + \item \code{fertil} a categorical unordered factor with 6 levels that is the fertilization strategy applied. These levels are a result of treatment cells in a three incomplete factorial arrangrment. See detais for more information. - \item \code{yield} sugarcane yield (kg/plot). + \item \code{yield} sugarcane yield (kg/plot). } } \details{ -The levels of fetilization are in fact a combination of a +The levels of fertilization are in fact a combination of a \eqn{3^2} factorial experiment but not all cells are present, so this is a (intentional) incomplete three factorial experiment. The factors used were limestone (A: present, a: diff --git a/man/sugarcaneYield4.Rd b/man/sugarcaneYield4.Rd new file mode 100644 index 0000000000000000000000000000000000000000..b0a20021e4e7cf9284dde5a41e0adf2d7dd855d4 --- /dev/null +++ b/man/sugarcaneYield4.Rd @@ -0,0 +1,48 @@ +% Generated by roxygen2 (4.1.1): do not edit by hand +% Please edit documentation in R/legTools.R +\docType{data} +\name{sugarcaneYield4} +\alias{sugarcaneYield4} +\title{Triple factorial NPK fertilization on sugar cane yield} +\format{a \code{data.frame} with 54 records and 6 variables.} +\source{ +Frederico, P. (2009). Curso de EstatÃstica Experimental (15th + ed.). Piracicaba, São Paulo: FEALQ. (page 126) +} +\usage{ +data(sugarcaneYield4) +} +\description{ +These data are from an \eqn{3^3} factorial experiment + studing the effect of NPK on the yield of sugar cane. + +\itemize{ + \item \code{block} a local control factor with 3 levels. + \item \code{rept} factor with 2 levels. + \item \code{N} integer coded nitrogen levels (0, 1, 2). + \item \code{P} integer coded phosphorus levels (0, 1, 2). + \item \code{K} integer coded potassium levels (0, 1, 2). + \item \code{yield} sugar cane yield (ton/ha). +} +} +\details{ +There is a missprint in the book for the 9th entry, which + has yield 59.0, that is coded as 202 istead of 220. +} +\examples{ +library(lattice) +library(latticeExtra) + +data(sugarcaneYield4) +str(sugarcaneYield4) + +xyplot(yield~N|P, groups=K, + auto.key=list(title="Potassim level", columns=3), + strip=strip.custom(var.name="Phosphorus", strip.names=TRUE, + strip.levels=TRUE, sep=": "), + data=sugarcaneYield4, type=c("p", "a"), + ylab=expression(Yield~(ton~ha^{-1})), + xlab="Nitrogen level level") +} +\keyword{datasets} + diff --git a/man/vinasseFert.Rd b/man/vinasseFert.Rd new file mode 100644 index 0000000000000000000000000000000000000000..c52ece6e40284557829e798b3e7279cf95c6783a --- /dev/null +++ b/man/vinasseFert.Rd @@ -0,0 +1,45 @@ +% Generated by roxygen2 (4.1.1): do not edit by hand +% Please edit documentation in R/legTools.R +\docType{data} +\name{vinasseFert} +\alias{vinasseFert} +\title{Fertilization with vinasse and mineral} +\format{a \code{data.frame} with 16 records and 4 variables.} +\source{ +Frederico, P. (2009). Curso de EstatÃstica Experimental (15th + ed.). Piracicaba, São Paulo: FEALQ. (page 119) +} +\usage{ +data(vinasseFert) +} +\description{ +These data are from an \eqn{2^2} factorial experiment + studing the effect of fertilizaton with vinasse (a residual from + industrial processing of sugar cane) and complete mineral + fertilization. + +\itemize{ + \item \code{block} a factor with 4 levels. + \item \code{mineral} low (-1) and high (+1) levels of mineral + fertilization. + \item \code{vinasse} low (-1) and high (+1) levels of fetilization + with vinasse. + \item \code{y} some response variable. The text book doesn't give + any information. +} +} +\examples{ +library(lattice) +library(latticeExtra) + +data(vinasseFert) +str(vinasseFert) + +xyplot(y~vinasse, groups=mineral, + auto.key=list(title="Mineral", columns=2), + data=vinasseFert, type=c("p", "a"), + ylab="y", + xlab="Vinasse level") +} +\keyword{datasets} + diff --git a/man/wgpigs.Rd b/man/wgPigs.Rd similarity index 92% rename from man/wgpigs.Rd rename to man/wgPigs.Rd index 3fc9a3ee41e441766520f2385b24fb0e11bb5095..e107692f914c6ec870518286efbb857f8a2c4e78 100644 --- a/man/wgpigs.Rd +++ b/man/wgPigs.Rd @@ -1,8 +1,8 @@ % Generated by roxygen2 (4.1.1): do not edit by hand % Please edit documentation in R/legTools.R \docType{data} -\name{wgpigs} -\alias{wgpigs} +\name{wgPigs} +\alias{wgPigs} \title{Feeding type in pig weight gain} \format{a \code{data.frame} with 20 records and 2 variables.} \source{ @@ -10,7 +10,7 @@ Frederico, P. (2009). Curso de EstatÃstica Experimental (15th ed.). Piracicaba, São Paulo: FEALQ. (page 62) } \usage{ -data(wgpigs) +data(wgPigs) } \description{ This is an artifial dataset corresponding a experiment @@ -29,9 +29,9 @@ This is an artifial dataset corresponding a experiment } \examples{ library(lattice) -data(wgpigs) +data(wgPigs) -xyplot(wg~ft, data=wgpigs, +xyplot(wg~ft, data=wgPigs, ylab="Weight gain (kg)", xlab="Feeding type") } diff --git a/man/wgPigs2.Rd b/man/wgPigs2.Rd new file mode 100644 index 0000000000000000000000000000000000000000..8ac1bb48b2aae8dae99418fa7113c493a9e978b3 --- /dev/null +++ b/man/wgPigs2.Rd @@ -0,0 +1,47 @@ +% Generated by roxygen2 (4.1.1): do not edit by hand +% Please edit documentation in R/legTools.R +\docType{data} +\name{wgPigs2} +\alias{wgPigs2} +\title{Age of castration in pig weight gain} +\format{a \code{data.frame} with 16 records and 4 variables.} +\source{ +Frederico, P. (2009). Curso de EstatÃstica Experimental (15th + ed.). Piracicaba, São Paulo: FEALQ. (page 110) +} +\usage{ +data(wgPigs2) +} +\description{ +This is an artifial dataset corresponding a experiment + to study the effect of feeding type (factor with 4 categorical + nominal levels) in pig weight gain. The experiment was a + randomized complete design with five experimental units per + treatment level. The experimental unit was a pig. The response + measured was weight gain from the beggining to the end of the + experiment. + +\itemize{ + \item \code{litter} a categorical factor with 4 levels that + represents the rows of the lattin square design and control for + the differences among litters. + \item code{size} a categorical ordered variable that represents the + columns of latin square desing and control for the weight of the + animals at the beggining of the experiment. + \item \code{age} age of the animal (days) when castration was + done. \code{controls} are the animals without castration. + \item \code{wg} weight gain (kg) after 252 days. +} +} +\examples{ +library(lattice) + +data(wgPigs2) +str(wgPigs2) + +xyplot(wg~age, data=wgPigs2, groups=litter, + ylab="Weight gain (kg)", + xlab="Age at castration (days)") +} +\keyword{datasets} + diff --git a/man/yscale.components.right.Rd b/man/yscale.components.right.Rd index cfe1220fbe2e36861731f8125f1c16cdedb9552e..7d94a5b22589303ff4a3484844e7909042eff3e4 100644 --- a/man/yscale.components.right.Rd +++ b/man/yscale.components.right.Rd @@ -1,7 +1,6 @@ % Generated by roxygen2 (4.1.1): do not edit by hand % Please edit documentation in R/yscale.components.right.R \name{yscale.components.right} -\alias{yscale.component.right} \alias{yscale.components.right} \title{y-axis annotations on the right side} \source{ @@ -10,7 +9,7 @@ When such feature was necessary, a search in the web was done \code{http://r.789695.n4.nabble.com/Spacing-between-lattice-panels-td855613.html}. } \usage{ -yscale.component.right(...) +yscale.components.right(...) } \arguments{ \item{...}{arguments passed by the lattice function called. See @@ -38,7 +37,7 @@ useOuterStrips(p2) p3 <- xyplot(yield~K|N+P, data=npk, scales=list(y=list(relation="free", alternating=2)), ylab=NULL, ylab.right="Yield", - yscale.component=yscale.component.right, + yscale.component=yscale.components.right, between=list(x=0.5, y=0.2), par.settings=list( layout.widths=list(