[Analogue-commits] r261 - in pkg: . R inst man

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Wed Apr 11 00:15:02 CEST 2012


Author: gsimpson
Date: 2012-04-11 00:15:02 +0200 (Wed, 11 Apr 2012)
New Revision: 261

Modified:
   pkg/NAMESPACE
   pkg/R/caterpillarPlot.R
   pkg/inst/ChangeLog
   pkg/man/caterpillarPlot.Rd
   pkg/man/optima.Rd
   pkg/man/wa.Rd
Log:
make caterpillarPlot an S3 generic with default, data.frame, and wa methods

Modified: pkg/NAMESPACE
===================================================================
--- pkg/NAMESPACE	2012-04-05 21:48:31 UTC (rev 260)
+++ pkg/NAMESPACE	2012-04-10 22:15:02 UTC (rev 261)
@@ -143,6 +143,9 @@
 S3method(residuals, mat)
 S3method(residuals, pcr)
 ## plotting
+S3method(caterpillarPlot, default)
+S3method(caterpillarPlot, data.frame)
+S3method(caterpillarPlot, wa)
 S3method(plot, minDC)
 S3method(plot, bayesF)
 S3method(plot, cma)

Modified: pkg/R/caterpillarPlot.R
===================================================================
--- pkg/R/caterpillarPlot.R	2012-04-05 21:48:31 UTC (rev 260)
+++ pkg/R/caterpillarPlot.R	2012-04-10 22:15:02 UTC (rev 261)
@@ -1,13 +1,22 @@
-`caterpillarPlot` <- function(x, env, useN2 = TRUE, decreasing = TRUE,
-                              mult = 1, labels, xlab = NULL,
-                              pch = 21, bg = "white", col = "black", lcol = col,
-                              ...) {
+`caterpillarPlot` <- function(x, ...) {
+    UseMethod("caterpillarPlot")
+}
+
+`caterpillarPlot.data.frame` <- function(x, env, useN2 = TRUE, ...) {
     ## compute the optima
     opt <- optima(x = x, env = env)
     ## and tolerances
     tol <- tolerance(x = x, env = env, useN2 = useN2)
 
+    ## do the plot
+    caterpillarPlot.default(x = opt, tol = tol, ...)
+}
+
+`caterpillarPlot.default` <- function(x, tol, mult = 1, decreasing = TRUE,
+                                      labels, xlab = NULL, pch = 21, bg = "white",
+                                      col = "black", lcol = col, ...) {
     ## reorder
+    opt <- x
     ord <- order(opt, decreasing = decreasing)
     opt <- opt[ord]
     tol <- tol[ord]
@@ -17,12 +26,14 @@
     on.exit(par(op))
 
     ## number of species
-    nspp <- ncol(x)
+    nspp <- length(opt)
     yvals <- seq_len(nspp)
 
     ## labels == spp names
     if(missing(labels)) {
         labels <- names(opt)
+        if(is.null(labels))
+            labels <- paste0("Var", yvals)
     }
     linch <- if (!is.null(labels))
         max(strwidth(labels, "inch"), na.rm = TRUE)
@@ -47,6 +58,22 @@
     axis(side = 1, ...)
     axis(side = 2, labels = labels, at = yvals, las = 1, ...)
     box()
+
+    ## return object
     out <- data.frame(Optima = opt, Tolerance = tol)
     invisible(out)
 }
+
+`caterpillarPlot.wa` <- function(x, type = c("observed","model"), ...) {
+    ## which type of tolerances
+    type <- match.arg(type)
+    ## extract the optima and tolerances
+    opt <- x$wa.optima
+    tol <- if(isTRUE(all.equal(type, "observed"))) {
+        x$tolerances
+    } else {
+        x$model.tol
+    }
+    ## do the plot
+    caterpillarPlot.default(x = opt, tol = tol, ...)
+}

Modified: pkg/inst/ChangeLog
===================================================================
--- pkg/inst/ChangeLog	2012-04-05 21:48:31 UTC (rev 260)
+++ pkg/inst/ChangeLog	2012-04-10 22:15:02 UTC (rev 261)
@@ -3,7 +3,8 @@
 Version 0.9-0
 
 	* caterpillarPlot: new function that draws a caterpillar plot
-	of species WA optima and tolerances.
+	of species WA optima and tolerances. Methods for data frames
+	and wa() fits are available alongside the default method.
 
 Version 0.8-2
 

Modified: pkg/man/caterpillarPlot.Rd
===================================================================
--- pkg/man/caterpillarPlot.Rd	2012-04-05 21:48:31 UTC (rev 260)
+++ pkg/man/caterpillarPlot.Rd	2012-04-10 22:15:02 UTC (rev 261)
@@ -1,5 +1,8 @@
 \name{caterpillarPlot}
 \alias{caterpillarPlot}
+\alias{caterpillarPlot.default}
+\alias{caterpillarPlot.data.frame}
+\alias{caterpillarPlot.wa}
 
 \title{
   Caterpillar plot of species' WA optima and tolerance range.
@@ -11,14 +14,22 @@
 }
 
 \usage{
-caterpillarPlot(x, env, useN2 = TRUE, decreasing = TRUE, mult = 1,
+
+\method{caterpillarPlot}{default}(x, tol, mult = 1, decreasing = TRUE,
                 labels, xlab = NULL, pch = 21, bg = "white",
                 col = "black", lcol = col, ...)
+
+\method{caterpillarPlot}{data.frame}(x, env, useN2 = TRUE, ...)
+
+\method{caterpillarPlot}{wa}(x, type = c("observed","model"), ...)
 }
 
 
 \arguments{
-  \item{x}{Species data matrix or data frame.}
+  \item{x}{For the \code{default} method, a numeric vector of species
+    optima. For the \code{data.frame} method a species data matrix or data
+    frame. For the \code{wa} method an object of class \code{"wa"}.}
+  \item{tol}{numeric; vector of species tolerances.}
   \item{env}{numeric; variable for which optima and tolerances are
     required.}
   \item{useN2}{logical; should Hill's N2 values be used to produce
@@ -33,6 +44,10 @@
   \item{pch, bg, col}{The plotting character to use and its background and
     foreground colour. See \code{\link{par}}.}
   \item{lcol}{The colour to use for the tolerance range.}
+  \item{type}{character; \code{"observed"} uses the actual tolerances
+    observed from the data. \code{"model"} uses the tolerances used in
+    the WA model where very small tolerances have been reset for some
+    definition of small.}
   \item{\dots}{Additional graphical arguments to be passed on to
     plotting functions.}
 }

Modified: pkg/man/optima.Rd
===================================================================
--- pkg/man/optima.Rd	2012-04-05 21:48:31 UTC (rev 260)
+++ pkg/man/optima.Rd	2012-04-10 22:15:02 UTC (rev 261)
@@ -54,6 +54,9 @@
 ## WA tolerances
 (tol <- tolerance(ImbrieKipp, SumSST, useN2 = TRUE))
 
+## caterpillar plot
+caterpillarPlot(opt, tol)
+
 ## convert to data frame
 as.data.frame(opt)
 as.data.frame(tol)

Modified: pkg/man/wa.Rd
===================================================================
--- pkg/man/wa.Rd	2012-04-05 21:48:31 UTC (rev 260)
+++ pkg/man/wa.Rd	2012-04-10 22:15:02 UTC (rev 261)
@@ -175,6 +175,10 @@
 plot(mod)
 par(mfrow = c(1,1))
 
+## caterpillar plot of optima and tolerances
+caterpillarPlot(mod)                 ## observed tolerances
+caterpillarPlot(mod, type = "model") ## with tolerances used in WA model
+
 ## tolerance DW
 mod2 <- wa(SumSST ~ ., data = ImbrieKipp, tol.dw = TRUE,
            min.tol = 2, small.tol = "min")



More information about the Analogue-commits mailing list