[Vegan-commits] r2889 - in pkg/vegan: . R man tests tests/Examples

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Tue Sep 30 09:24:03 CEST 2014


Author: jarioksa
Date: 2014-09-30 09:24:02 +0200 (Tue, 30 Sep 2014)
New Revision: 2889

Added:
   pkg/vegan/R/permustats.R
   pkg/vegan/man/permustats.Rd
Removed:
   pkg/vegan/R/density.anosim.R
   pkg/vegan/R/density.oecosimu.R
   pkg/vegan/R/densityplot.oecosimu.R
   pkg/vegan/man/density.adonis.Rd
Modified:
   pkg/vegan/NAMESPACE
   pkg/vegan/R/print.oecosimu.R
   pkg/vegan/R/vegan-deprecated.R
   pkg/vegan/man/adonis.Rd
   pkg/vegan/man/anosim.Rd
   pkg/vegan/man/betadisper.Rd
   pkg/vegan/man/mantel.Rd
   pkg/vegan/man/mrpp.Rd
   pkg/vegan/man/oecosimu.Rd
   pkg/vegan/man/procrustes.Rd
   pkg/vegan/man/vegan-deprecated.Rd
   pkg/vegan/tests/Examples/vegan-Ex.Rout.save
   pkg/vegan/tests/oecosimu-tests.R
   pkg/vegan/tests/oecosimu-tests.Rout.save
   pkg/vegan/tests/vegan-tests.Rout.save
Log:
Merge branch 'master' into r-forge-svn-local

Add permustats() function and their support with replace and
enhance old density and densityplot methods for permutation
and simulation results.

Modified: pkg/vegan/NAMESPACE
===================================================================
--- pkg/vegan/NAMESPACE	2014-09-24 08:53:17 UTC (rev 2888)
+++ pkg/vegan/NAMESPACE	2014-09-30 07:24:02 UTC (rev 2889)
@@ -19,7 +19,7 @@
 ordihull, ordilabel, ordiplot, ordipointlabel, ordiresids,
 ordisegments, ordispider, ordisplom, ordistep, ordisurf,
 orditkplot, orditorp, ordixyplot, 
-pcnm, permatfull, permatswap, permutest,
+pcnm, permatfull, permatswap, permustats, permutest,
 poolaccum, postMDS, prc, prestondistr, prestonfit, procrustes,
 protest, radfit, radlattice, rankindex, rarefy, rarecurve, raupcrick,
 rda, renyiaccum, renyi, rrarefy, scores, scoverage,
@@ -51,6 +51,15 @@
 
 ## Export .Depracated functions (to be removed later)
 export(commsimulator)
+S3method(density, adonis)
+S3method(density, anosim)
+S3method(density, mantel)
+S3method(density, mrpp)
+S3method(density, oecosimu)
+S3method(density, permutest.cca)
+S3method(density, protest)
+S3method(densityplot, adonis)
+S3method(densityplot, oecosimu)
 
 ## do NOT export the following internal functions
 
@@ -140,16 +149,9 @@
 # cophenetic: stats
 S3method(cophenetic, spantree)
 # density: stats
-S3method(density, adonis)
-S3method(density, anosim)
-S3method(density, mantel)
-S3method(density, mrpp)
-S3method(density, oecosimu)
-S3method(density, permutest.cca)
-S3method(density, protest)
+S3method(density, permustats)
 # densityplot: lattice
-S3method(densityplot, adonis)
-S3method(densityplot, oecosimu)
+S3method(densityplot, permustats)
 # deviance: stats
 S3method(deviance, cca)
 S3method(deviance, rda)
@@ -237,6 +239,26 @@
 # ordisurf: vegan
 S3method(ordisurf, default)
 S3method(ordisurf, formula)
+
+## permustats methods
+S3method(permustats, adonis)
+S3method(permustats, anosim)
+S3method(permustats, mantel)
+S3method(permustats, mrpp)
+S3method(permustats, oecosimu)
+S3method(permustats, permutest.cca)
+## these return an error: no permutation data
+S3method(permustats, CCorA)
+S3method(permustats, envfit)
+S3method(permustats, factorfit)
+S3method(permustats, vectorfit)
+S3method(permustats, mso)
+S3method(permustats, permutest.betadisper)
+
+S3method(print, permustats)
+S3method(summary, permustats)
+S3method(print, summary.permustats)
+
 # permutest: vegan
 S3method(permutest, betadisper)
 S3method(permutest, cca)
@@ -375,6 +397,10 @@
 # see note on 'confint'
 S3method(profile, MOStest)
 S3method(profile, humpfit)
+## qqmath: lattice
+S3method(qqmath, permustats)
+## qqnorm: stats
+S3method(qqnorm, permustats)
 # radfit: vegan
 S3method(radfit, data.frame)
 S3method(radfit, default)

Deleted: pkg/vegan/R/density.anosim.R
===================================================================
--- pkg/vegan/R/density.anosim.R	2014-09-24 08:53:17 UTC (rev 2888)
+++ pkg/vegan/R/density.anosim.R	2014-09-30 07:24:02 UTC (rev 2889)
@@ -1,135 +0,0 @@
-### density & densityplot methods for vegan functions returning
-### statistics from permuted/simulated data. These are modelled after
-### density.oecosimu and densityplot.oecosimu (which are in their
-### separate files).
-
-## anosim
-
-`density.anosim` <-
-    function(x, ...)
-{
-    obs <- x$statistic
-    ## Put observed statistic among permutations
-    out <- density(c(obs, x$perm), ...)
-    out$call <- match.call()
-    out$observed <- obs
-    out$call[[1]] <- as.name("density")
-    class(out) <- c("vegandensity", class(out))
-    out
-}
-
-## adonis can return a matrix of terms, hence we also have densityplot()
-
-`density.adonis` <-
-    function(x, ...)
-{
-    cols <- ncol(x$f.perms)
-    if (cols > 1)
-        warning("'density' is meaningful only with one term, you have ", cols)
-    obs <- x$aov.tab$F.Model
-    obs <- obs[!is.na(obs)]
-    out <- density(c(obs, x$f.perms), ...)
-    out$observed <- obs
-    out$call <- match.call()
-    out$call[[1]] <- as.name("density")
-    class(out) <- c("vegandensity", class(out))
-    out
-}
-
-`densityplot.adonis` <-
-    function(x, data, xlab = "Null", ...)
-{
-    obs <- x$aov.tab$F.Model
-    obs <- obs[!is.na(obs)]
-    sim <- rbind(obs, x$f.perms)
-    nm <- rownames(x$aov.tab)[col(sim)]
-    densityplot( ~ as.vector(sim) | factor(nm, levels = unique(nm)),
-                xlab = xlab,
-                panel = function(x, ...) {
-                    panel.densityplot(x, ...)
-                    panel.abline(v = obs[panel.number()], ...)
-                },
-                ...)
-}
-
-## mantel
-
-`density.mantel` <-
-    function(x, ...)
-{
-    obs <- x$statistic
-    out <- density(c(obs, x$perm), ...)
-    out$observed <- obs
-    out$call <- match.call()
-    out$call[[1]] <- as.name("density")
-    class(out) <- c("vegandensity", class(out))
-    out
-}
-
-## mrpp
-
-`density.mrpp` <-
-    function(x, ...)
-{
-    obs <- x$delta
-    out <- density(c(obs, x$boot.deltas), ...)
-    out$observed <- obs
-    out$call <- match.call()
-    out$call[[1]] <- as.name("density")
-    class(out) <- c("vegandensity", class(out))
-    out
-}
-
-## anova.cca does not return permutation results, but permutest.cca
-## does. However, permutest.cca always finds only one statistic. Full
-## tables anova.cca are found by repeated calls to permutest.cca.
-
-`density.permutest.cca` <-
-    function(x, ...)
-{
-    obs <- x$F.0
-    out <- density(c(obs, x$F.perm), ...)
-    out$observed <- obs
-    out$call <- match.call()
-    out$call[[1]] <- as.name("density")
-    class(out) <- c("vegandensity", class(out))
-    out
-}
-
-## protest
-
-`density.protest` <-
-    function(x, ...)
-{
-    obs <- x$t0
-    out <- density(c(obs, x$t), ...)
-    out$observed <- obs
-    out$call <- match.call()
-    out$call[[1]] <- as.name("density")
-    class(out) <- c("vegandensity", class(out))
-    out
-}
-
-#### plot method: the following copies stats::plot.density() code but
-#### adds one new argument to draw abline(v=...) for the observed
-#### statistic
-
-`plot.vegandensity` <-
-    function (x, main = NULL, xlab = NULL, ylab = "Density", type = "l", 
-    zero.line = TRUE, obs.line = TRUE, ...) 
-{
-    if (is.null(xlab)) 
-        xlab <- paste("N =", x$n, "  Bandwidth =", formatC(x$bw))
-    if (is.null(main)) 
-        main <- deparse(x$call)
-    ## change obs.line to col=2 (red) if it was logical TRUE
-    if (isTRUE(obs.line))
-        obs.line <- 2
-    plot.default(x, main = main, xlab = xlab, ylab = ylab, type = type,
-                 ...)
-    if (zero.line) 
-        abline(h = 0, lwd = 0.1, col = "gray")
-    if (is.character(obs.line) || obs.line)
-        abline(v = x$observed, col = obs.line)
-    invisible(NULL)
-}

Deleted: pkg/vegan/R/density.oecosimu.R
===================================================================
--- pkg/vegan/R/density.oecosimu.R	2014-09-24 08:53:17 UTC (rev 2888)
+++ pkg/vegan/R/density.oecosimu.R	2014-09-30 07:24:02 UTC (rev 2889)
@@ -1,14 +0,0 @@
-`density.oecosimu` <-
-    function(x, ...)
-{
-    cols <- nrow(x$oecosimu$simulated)
-    if (cols > 1)
-        warning("'density' is meaningful only with one statistic, you have ", cols)
-    obs <- x$oecosimu$statistic
-    out <- density(rbind(obs, t(x$oecosimu$simulated)), ...)
-    out$observed <- obs
-    out$call <- match.call()
-    out$call[[1]] <- as.name("density")
-    class(out) <- c("vegandensity", class(out))
-    out
-}

Deleted: pkg/vegan/R/densityplot.oecosimu.R
===================================================================
--- pkg/vegan/R/densityplot.oecosimu.R	2014-09-24 08:53:17 UTC (rev 2888)
+++ pkg/vegan/R/densityplot.oecosimu.R	2014-09-30 07:24:02 UTC (rev 2889)
@@ -1,14 +0,0 @@
-`densityplot.oecosimu` <-
-    function(x, data, xlab = "Simulated", ...)
-{
-    obs <- x$oecosimu$statistic
-    sim <- rbind(obs, t(x$oecosimu$simulated))
-    nm <- names(obs)[col(sim)]
-    densityplot( ~ as.vector(sim) | factor(nm, levels = unique(nm)),
-                xlab = xlab,
-                panel = function(x, ...) {
-                    panel.densityplot(x, ...)
-                    panel.abline(v = obs[panel.number()], ...)
-                },
-                ...)
-}

Added: pkg/vegan/R/permustats.R
===================================================================
--- pkg/vegan/R/permustats.R	                        (rev 0)
+++ pkg/vegan/R/permustats.R	2014-09-30 07:24:02 UTC (rev 2889)
@@ -0,0 +1,241 @@
+### Functions to extract permutation statististic or null model
+### results from various vegan objects.
+
+## extract items as 'statistic' and 'permutations'. Specific methods
+## towards the end of this file
+
+`permustats` <-
+    function(x, ...)
+{
+    UseMethod("permustats")
+}
+
+## something like str()
+`print.permustats` <-
+    function(x, ...)
+{
+    print(str(x))
+    invisible(x)
+}
+
+### modelled after print.oecosimu (should perhaps have oecosimu() args
+### like 'alternative'
+
+`summary.permustats` <-
+    function(object, probs, ...)
+{
+    ## default cut levels for quantiles: these are two-sided
+    if (missing(probs))
+        probs <- switch(object$alternative,
+                        "two.sided" = c(0.025, 0.5, 0.975),
+                        "greater" = c(0.5, 0.95),
+                        "less" = c(0.05, 0.5)) 
+    sim <- t(object$permutations)
+    object$means <- rowMeans(sim)
+    sd <- apply(sim, 1, sd)
+    object$z <-
+        (object$statistic - object$means)/sd
+    object$quantile <-
+        apply(sim, 1, quantile, probs = probs, na.rm = TRUE)
+    ## not (yet) P-values...
+    class(object) <- "summary.permustats"
+    object
+}
+
+`print.summary.permustats` <-
+    function(x, ...)
+{
+    m <- cbind("statistic" = x$statistic,
+               "z" = x$z,
+               "mean" = x$means,
+               t(x$quantile))
+    printCoefmat(m, cs.ind = 3:ncol(m), ...)
+    invisible(x)
+}
+
+### densityplot
+
+`densityplot.permustats` <-
+    function(x, data, xlab = "Permutations", ...)
+{
+    obs <- x$statistic
+    sim <- rbind(x$statistic, as.matrix(x$permutations))
+    nm <- names(obs)[col(sim)]
+    densityplot( ~ as.vector(sim) | factor(nm, levels = unique(nm)),
+                xlab = xlab,
+                panel = function(x, ...) {
+                    panel.densityplot(x, ...)
+                    panel.abline(v = obs[panel.number()], ...)
+                },
+                ...)
+}
+
+### simple density: normally densityplot should be used (or I suggest
+### so), but we also offer basic density. This can be either with or
+### without observed statistic.
+
+`density.permustats` <-
+    function(x, observed = TRUE, ...)
+{
+    ## only works with statistic
+    if (length(x$statistic) > 1)
+        stop(gettextf("only works with one statistic: you got %d",
+                      length(x$statistic)))
+    p <- x$permutations
+    if (observed)
+        p <- c(x$statistic, p)
+    out <- density(p)
+    out$call <- match.call()
+    out$call[[1]] <- as.name("density")
+    out
+}
+
+### QQ-plot against Guaussian distribution
+
+`qqnorm.permustats` <-
+    function(y, observed = TRUE, ...)
+{
+    ## only works with statistic
+    if (length(y$statistic) > 1)
+        stop(gettextf("only works with one statistic: you got %d",
+                      length(y$statistic)))
+    p <- y$permutations
+    if (observed)
+        p <- c(y$statistic, p)
+    q <- qqnorm(p, ...)
+    if (observed)
+        abline(h = y$statistic, ...)
+    invisible(q)
+}
+
+`qqmath.permustats` <-
+    function(x, data, observed = TRUE, ylab = "Permutations", ...)
+{
+    obs <- x$statistic
+    if (observed)
+        sim <- rbind(x$statistic, as.matrix(x$permutations))
+    else
+        sim <- as.matrix(x$permutations)
+    nm <- names(obs)[col(sim)]
+    qqmath( ~ as.vector(sim) | factor(nm, levels = unique(nm)),
+                ylab = ylab,
+                panel = function(x, ...) {
+                    panel.qqmath(x, ...)
+                    if (observed)
+                        panel.abline(h = obs[panel.number()], ...)
+                },
+                ...)
+}
+
+###
+### specific methods to extract permustats
+###
+
+`permustats.anosim` <-
+    function(x, ...)
+{
+    structure(list(
+        "statistic" = structure(x$statistic, names="R"),
+        "permutations" = x$perm,
+        "alternative" = "greater"),
+              class="permustats")
+}
+
+`permustats.adonis` <-
+    function(x, ...)
+{
+    tab <- x$aov.tab
+    k <- !is.na(tab$F.Model)
+    structure(list(
+        "statistic" = structure(tab$F.Model[k], names = rownames(tab)[k]),
+        "permutations" = x$f.perms,
+        "alternative" = "greater"),
+              class="permustats")
+}
+
+`permustats.mantel` <-
+    function(x, ...)
+{
+    structure(list(
+        "statistic" = structure(x$statistic, names="r"),
+        "permutations" = x$perm,
+        "alternative" = "greater"),
+              class="permustats")
+}
+
+`permustats.mrpp` <-
+    function(x, ...)
+{
+    structure(list(
+        "statistic" = structure(x$delta, names="delta"),
+        "permutations" = x$boot.deltas,
+        "alternative" = "less"),
+              class="permustats")
+}
+
+`permustats.oecosimu` <-
+    function(x, ...)
+{
+    structure(list(
+        "statistic" = x$oecosimu$statistic,
+        "permutations" = t(x$oecosimu$simulated),
+        "alternative" = x$oecosimu$alternative),
+              class="permustats")
+}
+
+`permustats.permutest.cca` <-
+    function(x, ...)
+{
+    structure(list(
+        "statistic" = structure(x$F.0, names = "F"),
+        "permutations" = x$F.perm,
+        "alternative" = "greater"),
+              class="permustats")
+}
+
+`permustats.protest` <-
+    function(x, ...)
+{
+    structure(list(
+        "statistic" = structure(x$t0, names = "r"),
+        "permutations" = x$t,
+        "alternative" = "greater"),
+              class="permustats")
+}
+
+### the following do not return permutation data
+`permustats.CCorA` <-
+    function(x, ...)
+{
+    stop("no permutation data available")
+}
+
+`permustats.envfit` <-
+    function(x, ...)
+{
+    stop("no permutation data available")
+}
+
+`permustats.factorfit` <-
+    function(x, ...)
+{
+    stop("no permutation data available")
+}
+
+`permustats.vectorfit` <-
+    function(x, ...)
+{
+    stop("no permutation data available")
+}
+
+`permustats.mso` <-
+    function(x, ...)
+{
+    stop("no permutation data available")
+}
+
+`permustats.permutest.betadisper` <-
+    function(x, ...)
+{
+    stop("no permutation data available")
+}

Modified: pkg/vegan/R/print.oecosimu.R
===================================================================
--- pkg/vegan/R/print.oecosimu.R	2014-09-24 08:53:17 UTC (rev 2888)
+++ pkg/vegan/R/print.oecosimu.R	2014-09-30 07:24:02 UTC (rev 2889)
@@ -28,13 +28,13 @@
     }
     probs <- switch(x$oecosimu$alternative,
                     two.sided = c(0.025, 0.5, 0.975),
-                    greater = c(0, 0.5, 0.95),
-                    less = c(0.05, 0.5, 1))
+                    greater = c(0.5, 0.95),
+                    less = c(0.05, 0.5))
     qu <- apply(x$oecosimu$simulated, 1, quantile, probs=probs, na.rm = TRUE)
     m <- cbind("statistic" = x$oecosimu$statistic,
                "z" = x$oecosimu$z, "mean" = x$oecosimu$means, t(qu),
                "Pr(sim.)"=x$oecosimu$pval)
-    printCoefmat(m, cs.ind = 3:6, ...)
+    printCoefmat(m, cs.ind = 3:(ncol(m)-1), ...)
     if (any(is.na(x$oecosimu$simulated))) {
         nacount <- rowSums(is.na(x$oecosimu$simulated))
         cat("\nNumber of NA cases removed from simulations:\n",

Modified: pkg/vegan/R/vegan-deprecated.R
===================================================================
--- pkg/vegan/R/vegan-deprecated.R	2014-09-24 08:53:17 UTC (rev 2888)
+++ pkg/vegan/R/vegan-deprecated.R	2014-09-30 07:24:02 UTC (rev 2889)
@@ -1,6 +1,9 @@
+### rewritten commsimulator
+
 "commsimulator" <-
 function (x, method, thin = 1) 
 {
+    .Deprecated("nullmodel", package="vegan")
     method <- match.arg(method, 
                         c("r0","r1","r2","r00","c0","swap", "tswap",
                           "backtrack", "quasiswap"))
@@ -12,3 +15,189 @@
     attributes(out) <- attributes(x)
     out
 }
+
+### density and densityplot
+
+### density & densityplot methods for vegan functions returning
+### statistics from permuted/simulated data. These are modelled after
+### density.oecosimu and densityplot.oecosimu (which are in their
+### separate files).
+
+## anosim
+
+`density.anosim` <-
+    function(x, ...)
+{
+    .Deprecated("densityplot(permustats(<anosim.result>))",
+                package="vegan")
+    obs <- x$statistic
+    ## Put observed statistic among permutations
+    out <- density(c(obs, x$perm), ...)
+    out$call <- match.call()
+    out$observed <- obs
+    out$call[[1]] <- as.name("density")
+    class(out) <- c("vegandensity", class(out))
+    out
+}
+
+## adonis can return a matrix of terms, hence we also have densityplot()
+
+`density.adonis` <-
+    function(x, ...)
+{
+    .Deprecated("densityplot(permustats(<adonis.result>))",
+                package="vegan")
+    cols <- ncol(x$f.perms)
+    if (cols > 1)
+        warning("'density' is meaningful only with one term, you have ", cols)
+    obs <- x$aov.tab$F.Model
+    obs <- obs[!is.na(obs)]
+    out <- density(c(obs, x$f.perms), ...)
+    out$observed <- obs
+    out$call <- match.call()
+    out$call[[1]] <- as.name("density")
+    class(out) <- c("vegandensity", class(out))
+    out
+}
+
+`densityplot.adonis` <-
+    function(x, data, xlab = "Null", ...)
+{
+    .Deprecated("densityplot(permustats(<adonis.result>))",
+                package="vegan")
+    obs <- x$aov.tab$F.Model
+    obs <- obs[!is.na(obs)]
+    sim <- rbind(obs, x$f.perms)
+    nm <- rownames(x$aov.tab)[col(sim)]
+    densityplot( ~ as.vector(sim) | factor(nm, levels = unique(nm)),
+                xlab = xlab,
+                panel = function(x, ...) {
+                    panel.densityplot(x, ...)
+                    panel.abline(v = obs[panel.number()], ...)
+                },
+                ...)
+}
+
+## mantel
+
+`density.mantel` <-
+    function(x, ...)
+{
+    .Deprecated("densityplot(permustats(<mantel.result>))",
+                package="vegan")
+    obs <- x$statistic
+    out <- density(c(obs, x$perm), ...)
+    out$observed <- obs
+    out$call <- match.call()
+    out$call[[1]] <- as.name("density")
+    class(out) <- c("vegandensity", class(out))
+    out
+}
+
+## mrpp
+
+`density.mrpp` <-
+    function(x, ...)
+{
+    .Deprecated("densityplot(permustats(<mrpp.result>))",
+                package="vegan")
+    obs <- x$delta
+    out <- density(c(obs, x$boot.deltas), ...)
+    out$observed <- obs
+    out$call <- match.call()
+    out$call[[1]] <- as.name("density")
+    class(out) <- c("vegandensity", class(out))
+    out
+}
+
+## anova.cca does not return permutation results, but permutest.cca
+## does. However, permutest.cca always finds only one statistic. Full
+## tables anova.cca are found by repeated calls to permutest.cca.
+
+`density.permutest.cca` <-
+    function(x, ...)
+{
+    .Deprecated("densityplot(permustats(<permutest.result>))",
+                package="vegan")
+    obs <- x$F.0
+    out <- density(c(obs, x$F.perm), ...)
+    out$observed <- obs
+    out$call <- match.call()
+    out$call[[1]] <- as.name("density")
+    class(out) <- c("vegandensity", class(out))
+    out
+}
+
+## protest
+
+`density.protest` <-
+    function(x, ...)
+{
+    .Deprecated("densityplot(permustats(<protest.result>))",
+                package="vegan")
+    obs <- x$t0
+    out <- density(c(obs, x$t), ...)
+    out$observed <- obs
+    out$call <- match.call()
+    out$call[[1]] <- as.name("density")
+    class(out) <- c("vegandensity", class(out))
+    out
+}
+
+#### plot method: the following copies stats::plot.density() code but
+#### adds one new argument to draw abline(v=...) for the observed
+#### statistic
+
+`plot.vegandensity` <-
+    function (x, main = NULL, xlab = NULL, ylab = "Density", type = "l", 
+    zero.line = TRUE, obs.line = TRUE, ...) 
+{
+    if (is.null(xlab)) 
+        xlab <- paste("N =", x$n, "  Bandwidth =", formatC(x$bw))
+    if (is.null(main)) 
+        main <- deparse(x$call)
+    ## change obs.line to col=2 (red) if it was logical TRUE
+    if (isTRUE(obs.line))
+        obs.line <- 2
+    plot.default(x, main = main, xlab = xlab, ylab = ylab, type = type,
+                 ...)
+    if (zero.line) 
+        abline(h = 0, lwd = 0.1, col = "gray")
+    if (is.character(obs.line) || obs.line)
+        abline(v = x$observed, col = obs.line)
+    invisible(NULL)
+}
+
+`density.oecosimu` <-
+    function(x, ...)
+{
+    .Deprecated("densityplot(permustats(<oecosimu.result>))",
+                package="vegan") 
+    cols <- nrow(x$oecosimu$simulated)
+    if (cols > 1)
+        warning("'density' is meaningful only with one statistic, you have ", cols)
+    obs <- x$oecosimu$statistic
+    out <- density(rbind(obs, t(x$oecosimu$simulated)), ...)
+    out$observed <- obs
+    out$call <- match.call()
+    out$call[[1]] <- as.name("density")
+    class(out) <- c("vegandensity", class(out))
+    out
+}
+
+`densityplot.oecosimu` <-
+    function(x, data, xlab = "Simulated", ...)
+{
+    .Deprecated("densityplot(permustats(<oecosimu.result>))",
+                package="vegan")
+    obs <- x$oecosimu$statistic
+    sim <- rbind(obs, t(x$oecosimu$simulated))
+    nm <- names(obs)[col(sim)]
+    densityplot( ~ as.vector(sim) | factor(nm, levels = unique(nm)),
+                xlab = xlab,
+                panel = function(x, ...) {
+                    panel.densityplot(x, ...)
+                    panel.abline(v = obs[panel.number()], ...)
+                },
+                ...)
+}

Modified: pkg/vegan/man/adonis.Rd
===================================================================
--- pkg/vegan/man/adonis.Rd	2014-09-24 08:53:17 UTC (rev 2888)
+++ pkg/vegan/man/adonis.Rd	2014-09-30 07:24:02 UTC (rev 2889)
@@ -138,9 +138,8 @@
     your predictors. }   
   \item{f.perms}{ an \eqn{N} by \eqn{m} matrix of the null \eqn{F}
     statistics for each source of variation based on \eqn{N}
-    permutations of the data. The distribution of a single term can be
-    inspected with \code{\link{density.adonis}} function, or all terms
-    simultaneously with \code{densityplot.adonis}.}
+    permutations of the data. The permutations can be inspected with
+    \code{\link{permustats}} and its support functions.}
   \item{model.matrix}{The \code{\link{model.matrix}} for the right hand
     side of the formula.}
   \item{terms}{The \code{\link{terms}} component of the model.}

Modified: pkg/vegan/man/anosim.Rd
===================================================================
--- pkg/vegan/man/anosim.Rd	2014-09-24 08:53:17 UTC (rev 2888)
+++ pkg/vegan/man/anosim.Rd	2014-09-30 07:24:02 UTC (rev 2889)
@@ -61,7 +61,7 @@
   permuting the grouping vector to obtain the empirical distribution
   of \eqn{R} under null-model.  See \code{\link{permutations}} for
   additional details on permutation tests in Vegan. The distribution
-  of simulated values can be inspected with the \code{density}
+  of simulated values can be inspected with the \code{\link{permustats}}
   function.
 
   The function has \code{summary} and \code{plot} methods.  These both
@@ -78,7 +78,7 @@
   \item{statistic}{The value of ANOSIM statistic \eqn{R}}
   \item{signif}{Significance from permutation.}
   \item{perm}{Permutation values of \eqn{R}. The distribution of
-    permutation values can be inspected with function \code{\link{density.anosim}}.}
+    permutation values can be inspected with function \code{\link{permustats}}.}
   \item{class.vec}{Factor with value \code{Between} for dissimilarities
     between classes and class name for corresponding dissimilarity
     within class.}

Modified: pkg/vegan/man/betadisper.Rd
===================================================================
--- pkg/vegan/man/betadisper.Rd	2014-09-24 08:53:17 UTC (rev 2888)
+++ pkg/vegan/man/betadisper.Rd	2014-09-30 07:24:02 UTC (rev 2889)
@@ -111,7 +111,7 @@
   parts respectively. This is equation (3) in Anderson (2006). If the
   imaginary part is greater in magnitude than the real part, then we
   would be taking the square root of a negative value, resulting in
-  NaN. From \pkg{vegan} 1.12-12 \code{betadisper} takes the absolute
+  NaN.  Function takes the absolute
   value of the real distance minus the imaginary distance, before
   computing the square root. This is in line with the behaviour of Marti
   Anderson's PERMDISP2 programme. 
@@ -140,7 +140,7 @@
   (Anderson \emph{et al} 2006). Function \code{\link{betadiver}}
   provides some popular dissimilarity measures for this purpose.
 
-  As noted in passing by Anderson (2001) and in a related
+  As noted in passing by Anderson (2006) and in a related
   context by O'Neill (2000), estimates of dispersion around a
   central location (median or centroid) that is calculated from the same data
   will be biased downward. This bias matters most when comparing diversity
@@ -200,9 +200,6 @@
   analysis gives the correct error rates.
 }
 \references{
-  Anderson, M. J. (2001) A new method for non-parametric multivariate 
-  analysis of variance. \emph{Austral Ecology} \strong{26}, 32--46.
-
   Anderson, M.J. (2006) Distance-based tests for homogeneity of
   multivariate dispersions. \emph{Biometrics} \strong{62}, 245--253.
 

Deleted: pkg/vegan/man/density.adonis.Rd
===================================================================
--- pkg/vegan/man/density.adonis.Rd	2014-09-24 08:53:17 UTC (rev 2888)
+++ pkg/vegan/man/density.adonis.Rd	2014-09-30 07:24:02 UTC (rev 2889)
@@ -1,114 +0,0 @@
-\name{density.adonis}
-\alias{density.adonis}
-\alias{density.anosim}
-\alias{density.mantel}
-\alias{density.mrpp}
-\alias{density.permutest.cca}
-\alias{density.protest}
-\alias{plot.vegandensity}
-\alias{densityplot.adonis}
-
-\title{
-  Kernel Density Estimation for Permutation Results in Vegan
-}
-
-\description{ 
-  The \code{density} functions can directly access the permutation
-  results of \pkg{vegan} functions, and \code{plot} can display the
-  densities. The \code{densityplot} method can access and display the
-  permutation results of functions that return permutations of several
-  statistics simultaneously.  
-}
-
-\usage{
-\method{density}{adonis}(x, ...)
-\method{plot}{vegandensity}(x, main = NULL, xlab = NULL, ylab = "Density", 
-   type = "l", zero.line = TRUE, obs.line = TRUE, ...)
-}
-
-\arguments{
-  \item{x}{The object to be handled. For \code{density} and
-     \code{densityplot} this is an object containing permutations. For
-     \code{plot} this is a result of \pkg{vegan} \code{density}
-     function.}
-  \item{main, xlab, ylab, type, zero.line}{Arguments of
-    \code{\link{plot.density}} and \code{\link[lattice]{densityplot}}
-    functions.}
-  \item{obs.line}{Draw vertical line for the observed
-    statistic. Logical value \code{TRUE} draws a red line, and
-    \code{FALSE} draws nothing. Alternatively, \code{obs.line} can be a
-    definition of the colour used for the line, either as a numerical
-    value from the \code{\link[grDevices]{palette}} or as the name of
-    the colour, or other normal definition of the colour.}
-  \item{\dots}{ Other arguments passed to the function. In
-    \code{density} these are passed to \code{\link{density.default}}.}
-}
-
-\details{ 
-
-  The \code{density} and \code{densityplot} function can directly access
-  permutation results of most \pkg{vegan} functions.  The \code{density}
-  function is identical to \code{\link{density.default}} and takes all
-  its arguments, but adds the observed statistic to the result as item
-  \code{"observed"}. The observed statistic is also put among the
-  permuted values so that the results are consistent with significance
-  tests. The \code{plot} method is similar to the default
-  \code{\link{plot.density}}, but can also add the observed statistic to
-  the graph as a vertical line.  The \code{densityplot} function is
-  based on the same function in the \pkg{lattice} package (see
-  \code{\link[lattice]{densityplot}}).
-
-  The density methods are available for \pkg{vegan} functions
-  \code{\link{adonis}}, \code{\link{anosim}}, \code{\link{mantel}},
-  \code{\link{mantel.partial}}, \code{\link{mrpp}},
-  \code{\link{permutest.cca}}, and \code{\link{protest}}.  The
-  \code{density} function for \code{\link{oecosimu}} is documented
-  separately, and it is also used for \code{\link{adipart}},
-  \code{\link{hiersimu}} and \code{\link{multipart}}.
-
-  All \pkg{vegan} \code{density} functions return an object of class
-  \code{"vegandensity"} inheriting from \code{\link{density}}, and can
-  be plotted with its \code{plot} method.  This is identical to the
-  standard \code{plot} of \code{densiy} objects, but can also add a
-  vertical line for the observed statistic.
-
-  Functions that can return several permuted statistics simultaneously
-  also have \code{\link[lattice]{densityplot}} method
-  (\code{\link{adonis}}, \code{\link{oecosimu}} and diversity 
-  partitioning functions based on \code{oecosimu}).  The standard
-  \code{\link{density}} can only handle univariate data, and a warning
-  is issued if the function is used for a model with several observed
-  statistics.  The \code{\link[lattice]{densityplot}} method is available
-  for \code{\link{adonis}} and \code{\link{oecosimu}} (documented
-  separately). NB, there is no \code{density} method for
-  \code{\link{anova.cca}}, but only for \code{\link{permutest.cca}}.
-
-}
-
-\value{
-  The \code{density} function returns the standard \code{\link{density}}
-  result object with one new item: \code{"observed"} for the observed
-  value of the statistic. The functions have a specific \code{plot}
-  method, but otherwise they use methods for
-  \code{\link{density.default}}, such as \code{print} and \code{lines}.
-}
-
-\author{
-  Jari Oksanen
-}
-
-\seealso{
-  \code{\link{density.default}}.
-}
-
-\examples{
-data(dune)
-data(dune.env)
-mod <- adonis(dune ~ Management, data = dune.env)
-plot(density(mod))
-mod <- adonis(dune ~ Management * Moisture, dune.env)
-densityplot(mod)
-}
-
-\keyword{ distribution }
-\keyword{ smooth }

Modified: pkg/vegan/man/mantel.Rd
===================================================================
--- pkg/vegan/man/mantel.Rd	2014-09-24 08:53:17 UTC (rev 2888)
+++ pkg/vegan/man/mantel.Rd	2014-09-30 07:24:02 UTC (rev 2889)
@@ -70,7 +70,7 @@
   \item{statistic}{The Mantel statistic.}
   \item{signif}{Empirical significance level from permutations.}
   \item{perm}{A vector of permuted values. The distribution of
-    permuted values can be inspected with \code{\link{density.mantel}} 
+    permuted values can be inspected with \code{\link{permustats}} 
     function.}
   \item{permutations}{Number of permutations.}
   \item{control}{A list of control values for the permutations

Modified: pkg/vegan/man/mrpp.Rd
===================================================================
--- pkg/vegan/man/mrpp.Rd	2014-09-24 08:53:17 UTC (rev 2888)
+++ pkg/vegan/man/mrpp.Rd	2014-09-30 07:24:02 UTC (rev 2889)
@@ -146,7 +146,7 @@
   \item{weight.type}{The choice of group weights used.}
   \item{boot.deltas}{The vector of "permuted deltas," the deltas
     calculated from each of the permuted datasets. The distribution of
-    this item can be inspected with \code{\link{density.mrpp}} function.}
+    this item can be inspected with \code{\link{permustats}} function.}
   \item{permutations}{The number of permutations used.}
   \item{control}{A list of control values for the permutations
     as returned by the function \code{\link[permute]{how}}.}

Modified: pkg/vegan/man/oecosimu.Rd
===================================================================
--- pkg/vegan/man/oecosimu.Rd	2014-09-24 08:53:17 UTC (rev 2888)
+++ pkg/vegan/man/oecosimu.Rd	2014-09-30 07:24:02 UTC (rev 2889)
@@ -3,8 +3,6 @@
 \alias{oecosimu}
 \alias{as.ts.oecosimu}
 \alias{as.mcmc.oecosimu}
-\alias{density.oecosimu}
-\alias{densityplot.oecosimu}
 
 \title{Evaluate Statistics with Null Models of Biological Communities }
 
@@ -32,8 +30,6 @@
    batchsize = NA, parallel = getOption("mc.cores"), ...)
 \method{as.ts}{oecosimu}(x, ...)
 \method{as.mcmc}{oecosimu}(x)
-\method{density}{oecosimu}(x, ...)
-\method{densityplot}{oecosimu}(x, data, xlab = "Simulated", ...)
 }
 
 \arguments{
@@ -88,8 +84,7 @@
     cluster before the call. See \code{\link{vegandocs}}
     \code{decision-vegan} for details. }
   \item{x}{An \code{oecosimu} result object.}
-  \item{data}{Ignored argument of the generic function.}
-  \item{xlab}{Label of the x-axis.}
+
   \item{\dots}{Other arguments to functions.}
 }
 
@@ -167,18 +162,10 @@
   methods, and summary of the results. Please consult the
   documentation of the \pkg{coda} package.
 
-  Function \code{density} provides an interface to the
-  standard \code{\link{density}} function for the simulated
-  values. Function \code{densityplot} is an interface to the
-  \code{\link[lattice]{densityplot}} function of the \pkg{lattice}
-  package. The \code{density} can be used meaningfully only for single
-  statistics and must be plotted separately. The \code{densityplot}
-  function can handle multiple statistics, and it plots the results
-  directly. In addition to the density, the \code{densityplot} also
-  shows the observed value of the statistic (provided it is within the
-  graph limits). The \code{densityplot} function is defined as a
-  generic function in the \pkg{lattice} package and you must either
-  load the \pkg{lattice} library before calling \code{densityplot}.
+  Function \code{\link{permustats}} provides support to the standard
[TRUNCATED]

To get the complete diff run:
    svnlook diff /svnroot/vegan -r 2889


More information about the Vegan-commits mailing list