From noreply at r-forge.r-project.org Thu Nov 6 10:17:30 2014
From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org)
Date: Thu, 6 Nov 2014 10:17:30 +0100 (CET)
Subject: [Vegan-commits] r2906 - in pkg/vegan: . R inst man tests/Examples
vignettes
Message-ID: <20141106091730.2F05D186AC6@r-forge.r-project.org>
Author: jarioksa
Date: 2014-11-06 10:17:29 +0100 (Thu, 06 Nov 2014)
New Revision: 2906
Added:
pkg/vegan/R/ordiareatest.R
Modified:
pkg/vegan/NAMESPACE
pkg/vegan/R/estimateR.default.R
pkg/vegan/R/permustats.R
pkg/vegan/R/poolaccum.R
pkg/vegan/R/specpool.R
pkg/vegan/R/text.cca.R
pkg/vegan/inst/ChangeLog
pkg/vegan/inst/NEWS.Rd
pkg/vegan/man/dune.taxon.Rd
pkg/vegan/man/ordihull.Rd
pkg/vegan/man/permustats.Rd
pkg/vegan/man/specpool.Rd
pkg/vegan/tests/Examples/vegan-Ex.Rout.save
pkg/vegan/vignettes/diversity-vegan.Rnw
pkg/vegan/vignettes/vegan.bib
Log:
Squashed commit of the following:
commit 73619424238a9fe15a6297bdd715a2204f6c9075
Author: Jari Oksanen
Date: Thu Nov 6 11:08:31 2014 +0200
Update examples (see comments below for: commsim swhs_samp)
* CHECK THIS: commsim models seem to have changed with
allowing double in swsh_samp methods
* Changes in avoiding dollar for with, and with for data
* Chao changes, in particular the small sample correction
commit 1f038ef610efc1fc7a317a9aaf87474ed36cbdf9
Author: Jari Oksanen
Date: Thu Nov 6 10:59:42 2014 +0200
Bad \usage lines found in documentation object 'specpool'
commit c20e2f330776f260bce1c218ba451bfc1851a26b
Author: Jari Oksanen
Date: Thu Nov 6 10:51:58 2014 +0200
Proof read NEWS (and dune.taxon man page accordingly)
commit 9e8329093b8077d7164086bb1f8b899f6a54688f
Author: Jari Oksanen
Date: Thu Nov 6 10:25:37 2014 +0200
NEWS about changes in Chao extrapolated richness
commit e92c6af0f46e197c170166104bd69746ea79c48f
Merge: f238aa9 b77c88d
Author: Gavin Simpson
Date: Wed Nov 5 07:37:01 2014 -0700
Merge pull request #64 from jarioksa/ordiareatests
Add ordiareatests for ordihull and ordiellipse
commit f238aa9c5a20936f0b4df0cfa721643fdc47417c
Merge: 6c108fa 01af54f
Author: Gavin Simpson
Date: Wed Nov 5 07:26:32 2014 -0700
Merge pull request #67 from jarioksa/chao
Chao equations
commit 01af54fbc842dec7f90879296276485d742d7ab2
Author: Jari Oksanen
Date: Wed Nov 5 10:11:31 2014 +0200
sync poolaccum with Chao changes in specpool
* switch to bias-corrected Chao when a2==0
* use small-sample correction in Chao (hard-wired)
commit 69c971df80cb088e933d8927e304ac1979aa60e6
Author: Jari Oksanen
Date: Wed Nov 5 09:56:58 2014 +0200
estimateR will not use small sample correction
In addition, clarify man/ page for estimateR
commit 2e2df0e15eb45170519554a16aedd6902fa8d292
Author: Jari Oksanen
Date: Tue Nov 4 13:41:02 2014 +0200
Make small sample correction optional in specpool
commit 3af5f26640f18f000911fb908f348f39a77a8b4e
Author: Jari Oksanen
Date: Tue Nov 4 11:41:59 2014 +0200
Update diversity vignette for the current state of Chao estimates
commit b5b8b8e19bc2fc0869690cd6120a8e7b39e38ec6
Author: Jari Oksanen
Date: Tue Nov 4 11:39:02 2014 +0200
fix small sample correction of var(Chao) when there are no doubletons
I reconstructed the variance formula (3b) of Chiu et al. 2014 using
the procedure described in their online appendix. I could get the same
formula except for the small-sample correction: it seems that EstimateS
web page got this correctly, but Chiu et al. ignore the small-sample
correction for all but the first term.
commit 562a531935df234fd204f917a813602ac5e9d3a2
Author: Jari Oksanen
Date: Mon Nov 3 11:08:03 2014 +0200
Use EstimateS formula (eq6) for the variance
The EstimateS web page eq6 formula is actually incorrect: it is
derived on the partial derivatives of classic Chao, but the terms
of the final result are replaced with the terms of bias-corrected
Chao. However, numerically the error is only about 1% of the correct
form and therefore we resent to use this widespread approximation.
commit 6c108fa55254aa06c0286f8b4e4bdecf4260eae0
Merge: 6819b9d feaf74e
Author: Jari Oksanen
Date: Sun Nov 2 16:41:57 2014 +0200
Merge pull request #68 from gavinsimpson/text-cca-labels-and-centroids
Text cca labels and centroids
commit feaf74e1ac5001831946a2fe8649d2e8d25963f7
Author: Gavin Simpson
Date: Sat Nov 1 20:09:48 2014 -0600
document change to text.cca with centroids and user-supplied labels
commit c439fae28d932500e1992cad2a4b5689c61c2382
Author: Gavin Simpson
Date: Sat Nov 1 20:08:10 2014 -0600
fix testing if centroids in biplot scores when user-supplied labels are given
commit 1768ac0d0eea8171b05791a3ea5e958cab1f5b65
Author: Jari Oksanen
Date: Fri Oct 31 10:00:27 2014 +0200
Forgot to take the sd of variance in estimateR
commit cdbaa810c18a6b7924f65aeacf61155a41223f53
Author: Jari Oksanen
Date: Thu Oct 30 19:28:46 2014 +0200
Proof-read equations in updated Chao documentation
commit b128c28d8c5c2913d8714236d08c0cffea4736f7
Author: Jari Oksanen
Date: Thu Oct 30 19:23:29 2014 +0200
proof-read and format man/specpool.Rd
commit 7ae52d63725e684723a6259193d760d16ccb170b
Author: Jari Oksanen
Date: Thu Oct 30 18:42:55 2014 +0200
update man/ pages for upgraded Chao richness
commit 38f01e08de3a3413cc6e96a170b6dbaaee17b223
Author: Jari Oksanen
Date: Thu Oct 30 18:17:09 2014 +0200
Use always bias-corrected form in Chao1 of estimateR
commit 0502202e501f878adc38cc5c1a869980c11b3374
Author: Jari Oksanen
Date: Thu Oct 30 16:49:51 2014 +0200
Update vignettes to the update Chao richness estimators
commit 4e056265951a001aac8b1b41f3f53c1c80e3bc4a
Author: Jari Oksanen
Date: Thu Oct 30 16:08:31 2014 +0200
Finally complete eq. for variance of extrapolated bootstrap richness
commit a34f01f7fdc9a2903fba9517cac2bac6c1e7ef88
Author: Jari Oksanen
Date: Wed Oct 29 21:00:30 2014 +0200
Chao index in specpool got small-sample correction and bias-correction
commit a0a2b1fd664214aded5b902eee83e420f47742ae
Author: Jari Oksanen
Date: Wed Oct 29 20:20:37 2014 +0200
Chao1 got small-sample correction and bias-corrected variance
estimateR upgrade following Chun et al., Biometrics 70, 671-682
(2014). Now the behaviour should be similar as in EstimateS, but
the variance formulae differ (our based on the cited publication).
commit 016b37945d8ddcd57756cb7ef51c940702e4a3c6
Author: Jari Oksanen
Date: Wed Oct 29 19:55:56 2014 +0200
esttimateR: use bias-corrected Chao1 only when doubletons = 0
Previously we always used bias-corrected form of Chao1, but
it seems that the normal biased form should normally be used, and
only when it cannot be estimated (because we divide by the number
of doubletons).
The sd of bias-corrected form is made NA in this commit: fixed in
the next one.
commit b77c88d91e57e08b47a9646947095c2d0d8fa3ab
Author: Jari Oksanen
Date: Mon Oct 27 11:30:06 2014 +0200
NEWS about ordiareatests
commit 8117a128d867501b5e1c6dfd5d7811c39e3cff4d
Author: Jari Oksanen
Date: Sun Oct 26 20:00:08 2014 +0200
permutations need be transposed in permustats of ordiareatest
commit ffa3878e89fcf67a02e1bc487dde99ab098a3dab
Author: Jari Oksanen
Date: Sun Oct 26 19:41:53 2014 +0200
Add permustats.ordiareatest
commit 04eb066c03e5c2262c299944f5dcc82cc5cbf75f
Author: Jari Oksanen
Date: Sun Oct 26 19:41:07 2014 +0200
Document and export ordiareatest: passes R CMD check
commit d96189be2f931bd2b017dc404e20e875ffe0c09b
Author: Jari Oksanen
Date: Sun Oct 26 18:52:09 2014 +0200
Add print.ordiareatest
commit 86a385a44011dead168f902f343b172aeb83354e
Author: Jari Oksanen
Date: Sun Oct 26 18:28:55 2014 +0200
Add ordiareatest for the areas of convex hulls or ellipses in ordination
The function is bases on ordihull and ordiellipse and performs permutation
tests on the sizes of fitted convex hulls or ellipses. The tests are
one-sided and the alternative hypothesis is that the areas covered by
convex hulls or ellipses are smaller than random expectations.
Modified: pkg/vegan/NAMESPACE
===================================================================
--- pkg/vegan/NAMESPACE 2014-10-29 08:36:32 UTC (rev 2905)
+++ pkg/vegan/NAMESPACE 2014-11-06 09:17:29 UTC (rev 2906)
@@ -15,6 +15,7 @@
metaMDSdist, metaMDSiter, metaMDSredist, MDSrotate, metaMDS, monoMDS,
mrpp, msoplot, mso, multipart, make.commsim, nestedbetajac, nestedbetasor, nestedchecker,
nesteddisc, nestedn0, nestednodf, nestedtemp, nullmodel, oecosimu,
+ordiareatest,
ordiR2step, ordiarrows, ordicloud, ordicluster, ordiellipse, ordigrid,
ordihull, ordilabel, ordiplot, ordipointlabel, ordiresids,
ordisegments, ordispider, ordisplom, ordistep, ordisurf,
@@ -246,6 +247,7 @@
S3method(permustats, mantel)
S3method(permustats, mrpp)
S3method(permustats, oecosimu)
+S3method(permustats, ordiareatest)
S3method(permustats, permutest.betadisper)
S3method(permustats, permutest.cca)
S3method(permustats, protest)
@@ -362,6 +364,7 @@
S3method(print, nestedtemp)
S3method(print, nullmodel)
S3method(print, oecosimu)
+S3method(print, ordiareatest)
S3method(print, permat)
S3method(print, permutest.betadisper)
S3method(print, permutest.cca)
Modified: pkg/vegan/R/estimateR.default.R
===================================================================
--- pkg/vegan/R/estimateR.default.R 2014-10-29 08:36:32 UTC (rev 2905)
+++ pkg/vegan/R/estimateR.default.R 2014-11-06 09:17:29 UTC (rev 2906)
@@ -28,8 +28,9 @@
}
if (!identical(all.equal(x, round(x)), TRUE))
stop("function accepts only integers (counts)")
- freq <- x[x > 0]
X <- x[x > 0]
+ N <- sum(X)
+ SSC <- 1 # (N-1)/N # do NOT use small-sample correction
T.X <- table(X)
S.obs <- length(X)
S.rare <- sum(T.X[as.numeric(names(T.X)) <= 10])
@@ -41,9 +42,28 @@
}
a <- sapply(i, COUNT, X)
G <- a[1]/a[2]
- S.Chao1 <- S.obs + a[1] * (a[1] - 1) / (a[2] + 1)/ 2
+ ## EstimateS uses basic Chao only if a[2] > 0, and switches to
+ ## bias-corrected version only if a[2] == 0. However, we always
+ ## use bias-corrected form. The switchin code is commented out so
+ ## that it is easy to put back.
+
+ ##if (a[2] > 0)
+ ## S.Chao1 <- S.obs + SSC * a[1]^2/2/a[2]
+ ##else if (a[1] > 0)
+ ##
+ S.Chao1 <- S.obs + SSC * a[1]*(a[1]-1) / (a[2]+1)/2
+ ##else
+ ## S.Chao1 <- S.obs
Deriv.Ch1 <- gradF(a, i)
- sd.Chao1 <- sqrt(a[2] * ((G^4)/4 + G^3 + (G^2)/2))
+ ##if (a[2] > 0)
+ ## sd.Chao1 <- sqrt(a[2] * (SSC * (SSC * (G^4/4 + G^3) + G^2/2)))
+ ##else if (a[1] > 0)
+ sd.Chao1 <-
+ sqrt(SSC*(a[1]*(a[1]-1)/2/(a[2]+1) +
+ SSC*(a[1]*(2*a[1]-1)^2/4/(a[2]+1)^2 +
+ a[1]^2*a[2]*(a[1]-1)^2/4/(a[2]+1)^4)))
+ ##else
+ ## sd.Chao1 <- 0
C.ace <- 1 - a[1]/N.rare
i <- 1:length(a)
thing <- i * (i - 1) * a
Added: pkg/vegan/R/ordiareatest.R
===================================================================
--- pkg/vegan/R/ordiareatest.R (rev 0)
+++ pkg/vegan/R/ordiareatest.R 2014-11-06 09:17:29 UTC (rev 2906)
@@ -0,0 +1,69 @@
+#' Permutation test for the area of convex hull or ellipse in ordination
+#'
+#' Finds if the area covered by a convex hull or fitted ellipse is
+#' smaller than expected under null hypothesis using permutation test.
+#'
+#' @param ord 2-d ordination
+#' @param factor defining groups
+#' @param are of convex hull of or an ellipse
+#' @param permutations: number, permutation matrix or a
+#' \code{\link[permute]{how}} definition.
+#' @param parallel parallel processing
+#' @param \dots other parameters passed to area functions
+#'
+#' @author Jari Oksanen
+`ordiareatest` <-
+ function(ord, groups, area = c("hull", "ellipse"), permutations = 999,
+ parallel = getOption("mc.cores"), ...)
+{
+ ## Function to find area
+ area <- match.arg(area)
+ areafun <- if (area == "hull") ordihull else ordiellipse
+ areafun <- match.fun(areafun)
+ ## Observed statistics
+ obs <- summary(areafun(ord, groups, draw = "none", ...))["Area",]
+ ## permutations
+ pfun <- function(take, ...)
+ summary(areafun(ord, groups[take], draw = "none", ...))["Area",]
+ perm <- getPermuteMatrix(permutations, length(groups))
+ nperm <- nrow(perm)
+ if (is.null(parallel))
+ parallel <- 1
+ hasClus <- inherits(parallel, "cluster")
+ if ((hasClus || parallel > 1) && require(parallel)) {
+ if(.Platform$OS.type == "unix" && !hasClus) {
+ areas <- do.call(cbind,
+ mclapply(1:permutations,
+ function(i, ...) pfun(perm[i,],...),
+ mc.cores = parallel))
+ } else {
+ if (!hasClus) {
+ parallel <- makeCluster(parallel)
+ }
+ areas <- parApply(parallel, perm, MARGIN=1, pfun)
+ if (!hasClus)
+ stopCluster(parallel)
+ }
+ } else {
+ areas <- sapply(1:permutations, function(i, ...) pfun(perm[i,], ...))
+ }
+ signif <- (rowSums(areas <= obs) + 1)/(nperm + 1)
+ out <- list("areas" = obs, "pvalues" = signif, "permutations" = areas,
+ nperm = nperm, control = attr(perm, "control"), "kind" = area)
+ class(out) <- "ordiareatest"
+ out
+}
+
+### print method
+
+`print.ordiareatest` <-
+ function(x, ...)
+{
+ qu <- apply(x$permutations, 1, quantile, probs=c(0.05, 0.5))
+ m <- cbind("Area" = x$areas, t(qu), "Pr( 0, 2, cumsum)
S[,i] <- rowSums(tmp > 0)
@@ -20,7 +23,8 @@
boot[,i] <- 2*S[,i] - m + rowSums(exp(sweep(log1p(-sweep(tmp, 1, N, "/")), 1, N, "*") ))
a1 <- rowSums(tmp == 1)
a2 <- rowSums(tmp == 2)
- chao[, i] <- S[,i] + ifelse(a2 > 0, a1*a1/2/a2, 0)
+ chao[, i] <- S[,i] + ifelse(a2 > 0, (N-1)/N*a1*a1/2/a2,
+ (N-1)/N*a1*(a1-1)/2)
jack1[,i] <- S[,i] + a1 * (N-1)/N
jack2[,i] <- S[,i] + a1*(2*N-3)/N - a2*(N-2)^2/N/(N-1)
}
Modified: pkg/vegan/R/specpool.R
===================================================================
--- pkg/vegan/R/specpool.R 2014-10-29 08:36:32 UTC (rev 2905)
+++ pkg/vegan/R/specpool.R 2014-11-06 09:17:29 UTC (rev 2906)
@@ -1,5 +1,5 @@
-"specpool" <-
- function (x, pool)
+`specpool` <-
+ function (x, pool, smallsample = TRUE)
{
x <- as.matrix(x)
if (missing(pool))
@@ -25,6 +25,10 @@
n <- length(gr)
if (n <= 0)
next
+ if (smallsample)
+ ssc <- (n-1)/n
+ else
+ ssc <- 1
X <- x[gr, , drop = FALSE]
freq <- colSums(X > 0)
p <- freq[freq > 0]/n
@@ -37,8 +41,9 @@
a2 <- sum(freq == 2)
else 0
chao[is] <- S[is] + if(!is.na(a2) && a2 > 0)
- a1 * a1/2/a2
- else 0
+ ssc * a1 * a1/2/a2
+ else
+ ssc * a1 * (a1-1)/2
jack.1[is] <- S[is] + a1 * (n - 1)/n
jack.2[is] <- S[is] + a1 * (2 * n - 3)/n - a2 * (n -
2)^2/n/(n - 1)
@@ -46,7 +51,11 @@
aa <- if (!is.na(a2) && a2 > 0)
a1/a2
else 0
- var.chao[is] <- a2 * (0.5 + (1 + aa/4) * aa) * aa * aa
+ if (a2 > 0)
+ var.chao[is] <- a2 * ssc * (0.5 + ssc * (1 + aa/4) * aa) * aa * aa
+ else
+ var.chao[is] <-
+ ssc * (ssc * (a1*(2*a1-1)^2/4 - a1^4/chao[is]/4) + a1*(a1-1)/2)
if (!is.na(a1) && a1 > 0) {
jf <- table(rowSums(X[, freq == 1, drop = FALSE] >
0))
Modified: pkg/vegan/R/text.cca.R
===================================================================
--- pkg/vegan/R/text.cca.R 2014-10-29 08:36:32 UTC (rev 2905)
+++ pkg/vegan/R/text.cca.R 2014-11-06 09:17:29 UTC (rev 2906)
@@ -7,13 +7,16 @@
stop("only one 'display' item can be added in one command")
pts <- scores(x, choices = choices, display = display, scaling = scaling,
const)
+ ## store rownames of pts for use later, otherwise if user supplies
+ ## labels, the checks in "cn" branch fail and "bp" branch will
+ ## be entered even if there should be no "bp" plotting
+ cnam <- rownames(pts)
if (!missing(labels))
rownames(pts) <- labels
if (!missing(select))
pts <- .checkSelect(select, pts)
if (display == "cn") {
- cnam <- rownames(pts)
- text(pts, labels = cnam, ...)
+ text(pts, labels = rownames(pts), ...)
pts <- scores(x, choices = choices, display = "bp", scaling = scaling,
const)
bnam <- rownames(pts)
Modified: pkg/vegan/inst/ChangeLog
===================================================================
--- pkg/vegan/inst/ChangeLog 2014-10-29 08:36:32 UTC (rev 2905)
+++ pkg/vegan/inst/ChangeLog 2014-11-06 09:17:29 UTC (rev 2906)
@@ -42,6 +42,10 @@
was specified using `control` which is not an argument to the
`permutest()` method for `betadisper()`.
+ * text.cca: was incorrectly testing if factor constraints were
+ in the biplot scores when user-suppiled lables for factors were
+ given.
+
* ccanova: removed from vegan. These were backup functions of old
anova.cca, and were completely rewritten for new vegan.
Modified: pkg/vegan/inst/NEWS.Rd
===================================================================
--- pkg/vegan/inst/NEWS.Rd 2014-10-29 08:36:32 UTC (rev 2905)
+++ pkg/vegan/inst/NEWS.Rd 2014-11-06 09:17:29 UTC (rev 2906)
@@ -13,7 +13,7 @@
integer giving the number of parallel processes. In unix-alikes
(Mac OS, Linux) this will launch \code{"multicore"} processing
and in Windows it will set up \code{"snow"} clusters as desribed
- in the documentation of \pkg{parallel} package. If \code{option}
+ in the documentation of the \pkg{parallel} package. If \code{option}
\code{"mc.cores"} is set to an integer > 1, this will be used to
automatically start parallel processing. Finally, the argument
can also be a previously set up \code{"snow"} cluster which will
@@ -23,21 +23,20 @@
extensive documentation on parallel processing in \R.
The following function use parallel processing in analysing
- permutatin statistics: \code{adonis}, \code{anosim},
+ permutation statistics: \code{adonis}, \code{anosim},
\code{anova.cca} (and \code{permutest.cca}), \code{mantel} (and
- \code{mantel.partial}), \code{mrpp}, \code{permutest.betadisper}
- and \code{simper}. In addition, \code{bioenv} can compare
- several candidate sets of models in paralle, \code{metaMDS} can
- launch several random starts in parallel, and \code{oecosimu}
- can evaluate test statistics for several null models in
- parallel.
+ \code{mantel.partial}), \code{mrpp}, \code{ordiareatest},
+ \code{permutest.betadisper} and \code{simper}. In addition,
+ \code{bioenv} can compare several candidate sets of models in
+ paralle, \code{metaMDS} can launch several random starts in
+ parallel, and \code{oecosimu} can evaluate test statistics for
+ several null models in parallel.
- \item All permutation tests are based on the \pkg{permute}
- package which offers strong tools for restricted
- permutation. All these functions have argument
- \code{permutations}. The default usage of simple non-restricted
- permutations is achieved by giving a single integer number as
- its argument. Restricted permutations can be defined using the
+ \item All permutation tests are based on the \pkg{permute} package
+ which offers strong tools for restricted permutation. All these
+ functions have argument \code{permutations}. The default usage of
+ simple non-restricted permutations is achieved by giving a single
+ integer number. Restricted permutations can be defined using the
\code{how} function of the \pkg{permute} package. Finally, the
argument can be a permutation matrix where rows define
permutations. It is possible to use external or user constructed
@@ -50,13 +49,13 @@
\code{vegandocs("permutations")}.
The following functions use the \pkg{permute} package:
- \code{CCorA}, \code{adonis}, \code{anosim}, \code{anova.cca}
- (plus associated \code{permutest.cca}, \code{add1.cca},
+ \code{CCorA}, \code{adonis}, \code{anosim}, \code{anova.cca} (plus
+ associated \code{permutest.cca}, \code{add1.cca},
\code{drop1.cca}, \code{ordistep}, \code{ordiR2step}),
\code{envfit} (plus associated \code{factorfit} and
\code{vectorfit}), \code{mantel} (and \code{mantel.partial}),
- \code{mrpp}, \code{mso}, \code{permutest.betadisper},
- \code{protest} and \code{simper}.
+ \code{mrpp}, \code{mso}, \code{ordiareatest},
+ \code{permutest.betadisper}, \code{protest} and \code{simper}.
\item Community null model generation has been completely
redesigned and rewritten. The communities are constructed with
@@ -103,27 +102,32 @@
\item New \code{hclust} support functions \code{reorder},
\code{rev} and \code{scores}. Functions \code{reorder} and
\code{rev} are similar as these functions for \code{dendrogram}
- objects. However, \code{reorder} can use (and defaults to)
- weighted mean. In weighted mean the node average is always the
+ objects in base \R. However, \code{reorder} can use (and defaults
+ to) weighted mean. In weighted mean the node average is always the
mean of member leaves, whereas the \code{dendrogram} uses always
- the unweighted means of joined branches.
+ unweighted means of joined branches.
- \item \code{permustats} to extract and inspect permutation
+ \item Function \code{ordiareatest} supplements \code{ordihull} and
+ \code{ordiellipse} and provides a randomization test for the
+ one-sided alternative hypothesis that convex hulls or ellipses in
+ two-dimensional ordination space have smaller areas than with
+ randomized groups.
+
+ \item Function \code{permustats} extracts and inspects permutation
results with support functions \code{summary}, \code{density},
\code{densityplot}, \code{qqnorm} and \code{qqmath}. The
- \code{density} and \code{qqnorm} are standard \R{} tools that
- only work with one statistic, and \code{densityplot} and
- \code{qqmath} are \pkg{lattice} graphics that work with
- univariate and multivariate statistics. The results of following
- functions can be extracted: \code{anosim}, \code{adonis},
- \code{mantel} (and \code{mantel.partial}), \code{mrpp},
- \code{oecosimu}, \code{permustest.cca} (but not the
- corresponding \code{anova} methods),
- \code{permutest.betadisper}, and \code{protest}.
+ \code{density} and \code{qqnorm} are standard \R{} tools that only
+ work with one statistic, and \code{densityplot} and \code{qqmath}
+ are \pkg{lattice} graphics that work with univariate and
+ multivariate statistics. The results of following functions can be
+ extracted: \code{anosim}, \code{adonis}, \code{mantel} (and
+ \code{mantel.partial}), \code{mrpp}, \code{oecosimu},
+ \code{permustest.cca} (but not the corresponding \code{anova}
+ methods), \code{permutest.betadisper}, and \code{protest}.
- \item \code{stressplot} functions display the ordination
- distances at given number of dimensions against original
- distances. These are a generalization of \code{stressplot} for
+ \item \code{stressplot} functions display the ordination distances
+ at given number of dimensions against original distances. The
+ method functins are similar to \code{stressplot} for
\code{metaMDS}, and always use the inherent distances of each
ordination method. The functions are available for the results
\code{capscale}, \code{cca}, \code{princomp}, \code{prcomp},
@@ -139,7 +143,7 @@
of a random value.
\item \code{ordiellipse} can handle points exactly on a line,
- including only two points.
+ including only two points (with a warning).
\item plotting \code{radfit} results for several species failed if
any of the communities had no species or had only one species.
@@ -199,15 +203,41 @@
\item \code{rankindex} can use Manhattan, Gower and Mahalanobis
distance in addition to the default Euclidean.
- \item User can set colours and line types in unction
+ \item User can set colours and line types in function
\code{rarecurve} for plotting rarefaction curves.
\item \code{spantree} gained a support function \code{as.hclust}
- to change the minimum spannig tree into an \code{hclust} tree.
+ to change the minimum spanning tree into an \code{hclust} tree.
\item \code{fitspecaccum} can do weighted analysis. Gained
\code{lines} method.
+ \item Functions for extrapolated number of species or for the size
+ of species pool using Chao method were modified following Chiu et
+ al., \emph{Biometrics} 70, 671--682 (2014).
+
+ Incidence based \code{specpool} can now use (and defaults to)
+ small sample correction with number of sites as the sample
+ size. Function uses basic Chao extrapolation based on the ratio of
+ singletons and doubletons, but switches now to bias corrected Chao
+ extrapolation if there are no doubletons (species found
+ twice). The variance formula for bias corrected Chao was derived
+ following the supporting
+ \href{http://onlinelibrary.wiley.com/doi/10.1111/biom.12200/suppinfo}{online material}
+ and differs slightly from Chiu et al. (2014).
+
+ The \code{poolaccum} function was changed similarly, but the small
+ sample correction is used always.
+
+ The abundance based \code{estimateR} uses bias corrected Chao
+ extrapolation, but earlier it estimated its variance with classic
+ Chao model. Now we use the widespread
+ \href{http://viceroy.eeb.uconn.edu/EstimateS/EstimateSPages/EstSUsersGuide/EstimateSUsersGuide.htm#AppendixB}{approximate
+ equation} for variance.
+
+ With these changes these functions are more similar to
+ \href{http://viceroy.eeb.uconn.edu/EstimateS/EstimateSPages/EstSUsersGuide/EstimateSUsersGuide.htm#AppendixB}{EstimateS}.
+
\item \code{tabasco} uses now \code{reorder.hclust} for
\code{hclust} object for better ordering than previously when it
cast trees to \code{dendrogram} objects.
@@ -224,7 +254,7 @@
III. \code{varespec} and \code{dune} use 8-character names (4
from genus + 4 from species epithet). New data set on
phylogenetic distances for \code{dune} was extracted from Zanne
- et al. (\emph{Nature}, 2014).
+ et al. (\emph{Nature} 506, 89--92; 2014).
\item User configurable plots for \code{rarecurve}.
@@ -243,12 +273,12 @@
extract scaled results.
\item \code{commsimulator} is deprecated. Replace
- \code{commsimulator(x, method)} with \code{simulate(nullmodel(x,
- method))}.
+ \code{commsimulator(x, method)} with
+ \code{simulate(nullmodel(x, method))}.
\item \code{density} and \code{densityplot} for permutation
- results: use \code{permustats} with its \code{density} and
- \code{densityplot} method.
+ results are deprecated: use \code{permustats} with its
+ \code{density} and \code{densityplot} method.
} %end itemize
} % end deprecated
Modified: pkg/vegan/man/dune.taxon.Rd
===================================================================
--- pkg/vegan/man/dune.taxon.Rd 2014-10-29 08:36:32 UTC (rev 2905)
+++ pkg/vegan/man/dune.taxon.Rd 2014-11-06 09:17:29 UTC (rev 2906)
@@ -39,8 +39,7 @@
I.J., Aarssen, L., Bertin, R.I., Calaminus, A., Govaerts, R.,
Hemmings, F., Leishman, M.R., Oleksyn, J., Soltis, P.S., Swenson,
N.G., Warman, L. & Beaulieu, J.M. (2014) Three keys to the radiation
- of angiosperms into freezing environments. \emph{Nature}
- doi:10.1038/nature12872 (published online Dec 22, 2013).
+ of angiosperms into freezing environments. \emph{Nature} 506, 89--92.
}
Modified: pkg/vegan/man/ordihull.Rd
===================================================================
--- pkg/vegan/man/ordihull.Rd 2014-10-29 08:36:32 UTC (rev 2905)
+++ pkg/vegan/man/ordihull.Rd 2014-11-06 09:17:29 UTC (rev 2906)
@@ -9,6 +9,7 @@
\alias{summary.ordihull}
\alias{scores.ordihull}
\alias{summary.ordiellipse}
+\alias{ordiareatest}
\title{Display Groups or Factor Levels in Ordination Diagrams}
@@ -30,6 +31,8 @@
w = weights(ord, display), ...)
\method{summary}{ordihull}(object, ...)
\method{summary}{ordiellipse}(object, ...)
+ordiareatest(ord, groups, area = c("hull", "ellipse"), permutations = 999,
+ parallel = getOption("mc.cores"), ...)
}
\arguments{
@@ -96,6 +99,19 @@
can be saved, and used for summaries (areas etc. of hulls and
ellipses). }
+ \item{area}{Evaluate the area of convex hulls of \code{ordihull}, or of
+ ellipses of \code{ordiellipse}.}
+
+ \item{permutations}{a list of control values for the permutations
+ as returned by the function \code{\link[permute]{how}}, or the
+ number of permutations required, or a permutation matrix where each
+ row gives the permuted indices.}
+
+ \item{parallel}{Number of parallel processes or a predefined socket
+ cluster. With \code{parallel = 1} uses ordinary, non-parallel
+ processing. The parallel processing is done with \pkg{parallel}
+ package.}
+
\item{\dots}{Parameters passed to graphical functions or to
\code{\link{scores}} to select axes and scaling etc. }
}
@@ -114,6 +130,12 @@
An ellipsoid hull can be drawn with function
\code{\link[cluster]{ellipsoidhull}} of package \pkg{cluster}.
+ Function \code{ordihull} and \code{ordiellipse} return invisibly an
+ object that has a \code{summary} method that returns the coordinates
+ of centroids and areas of the hulls or ellipses. Function
+ \code{ordiareatest} studies the one-sided hypothesis that these
+ areas are smaller than with randomized \code{groups}.
+
Function \code{ordispider} draws a \sQuote{spider} diagram where
each point is connected to the group centroid with
\code{\link{segments}}. Weighted centroids are used in the
@@ -151,10 +173,7 @@
Function \code{ordihull} returns a list of coordinates of the hulls
(which can be extracted with \code{scores}), and \code{ordiellipse}
returns a list of covariance matrices and scales used in drawing the
- ellipses. These result objects have a \code{summary} method that
- returns the coordinates of the centres of the ellipses or hulls and
- their surface areas in user units. With \code{draw = "none"} only
- the result object is returned and nothing is drawn.
+ ellipses.
}
Modified: pkg/vegan/man/permustats.Rd
===================================================================
--- pkg/vegan/man/permustats.Rd 2014-10-29 08:36:32 UTC (rev 2905)
+++ pkg/vegan/man/permustats.Rd 2014-11-06 09:17:29 UTC (rev 2906)
@@ -9,6 +9,7 @@
\alias{permustats.mrpp}
\alias{permustats.mso}
\alias{permustats.oecosimu}
+\alias{permustats.ordiareatest}
\alias{permustats.permutest.betadisper}
\alias{permustats.permutest.cca}
\alias{permustats.protest}
@@ -92,7 +93,7 @@
The \code{permustats} can extract permutation statistics from the
results of \code{\link{adonis}}, \code{\link{anosim}},
\code{\link{mantel}}, \code{\link{mantel.partial}},
- \code{\link{mrpp}}, \code{\link{oecosimu}},
+ \code{\link{mrpp}}, \code{\link{oecosimu}}, \code{\link{ordiareatest}},
\code{\link{permutest.cca}}, \code{\link{protest}}, and
\code{\link{permutest.betadisper}}. NB, there is no \code{permustats}
method for \code{\link{anova.cca}}, but only for
Modified: pkg/vegan/man/specpool.Rd
===================================================================
--- pkg/vegan/man/specpool.Rd 2014-10-29 08:36:32 UTC (rev 2905)
+++ pkg/vegan/man/specpool.Rd 2014-11-06 09:17:29 UTC (rev 2906)
@@ -19,7 +19,7 @@
is based on abundances (counts) on single sample site.
}
\usage{
-specpool(x, pool)
+specpool(x, pool, smallsample = TRUE)
estimateR(x, ...)
specpool2vect(X, index = c("jack1","jack2", "chao", "boot","Species"))
poolaccum(x, permutations = 100, minsize = 3)
@@ -33,6 +33,8 @@
for \code{plot} function.}
\item{pool}{A vector giving a classification for pooling the sites in
the species data. If missing, all sites are pooled together.}
+ \item{smallsample}{Use small sample correction \eqn{(N-1)/N}, where
+ \eqn{N} is the number of sites within the \code{pool}.}
\item{X, object}{A \code{specpool} result object.}
\item{index}{The selected index of extrapolated richness.}
\item{permutations}{Number of permutations of sampling order of sites.}
@@ -59,33 +61,39 @@
sites in the collection. The variants of extrapolated richness in
\code{specpool} are:
\tabular{ll}{
- Chao
- \tab \eqn{S_P = S_0 + a1^2/(2*a2)}
+ Chao
+ \tab \eqn{S_P = S_0 + \frac{a_1^2}{2 a_2}\frac{N-1}{N}}{S_P = S_0 + a1^2/(2*a2) * (N-1)/N}
\cr
+ Chao bias-corrected
+ \tab \eqn{S_P = S_0 + \frac{a_1(a_1-1)}{2(a_2+1)} \frac{N-1}{N}}{S_P = S_0 + a1*(a1-1)/(2*(a2+1)) * (N-1)/N}
+ \cr
First order jackknife
\tab \eqn{S_P = S_0 + a_1 \frac{N-1}{N}}{S_P = S_0 + a1*(N-1)/N}
\cr
Second order jackknife
\tab \eqn{S_P = S_0 + a_1 \frac{2N - 3}{N} - a_2 \frac{(N-2)^2}{N
- (N-1)}}{S_P = S_0 + a1*(2*n-3)/n - a2*(n-2)^2/n/(n-1)}
+ (N-1)}}{S_P = S_0 + a1*(2*N-3)/N - a2*(N-2)^2/N/(N-1)}
\cr
Bootstrap
\tab \eqn{S_P = S_0 + \sum_{i=1}^{S_0} (1 - p_i)^N}{S_P = S_0 + Sum
(1-p_i)^N}
}
+ \code{specpool} normally uses basic Chao equation, but when there
+ are no doubletons (\eqn{a2=0}) it switches to bias-corrected
+ version. In that case the Chao equation simplifies to
+ \eqn{S_0 + \frac{1}{2} a_1 (a_1-1) \frac{N-1}{N}}{S_0 + (N-1)/N * a1*(a1-1)/2}.
- The abundance-based estimates in \code{estimateR} use counts (frequencies) of
- species in a single site. If called for a matrix or data frame, the
- function will give separate estimates for each site. The two
- variants of extrapolated richness in \code{estimateR} are Chao
- (unbiased variant) and ACE. In the Chao estimate
- \eqn{a_i} refers to number of species with abundance \eqn{i} instead
- of incidence:
+ The abundance-based estimates in \code{estimateR} use counts
+ (numbers of individuals) of species in a single site. If called for
+ a matrix or data frame, the function will give separate estimates
+ for each site. The two variants of extrapolated richness in
+ \code{estimateR} are bias-corrected Chao and ACE (O'Hara 2005, Chiu
+ et al. 2014). The Chao estimate is similar as the bias corrected
+ one above, but \eqn{a_i} refers to the number of species with
+ abundance \eqn{i} instead of number of sites, and the small-sample
+ correction is not used. The ACE estimate is defined as:
+
\tabular{ll}{
- Chao
- \tab \eqn{S_P = S_0 + \frac{a_1 (a_1 -1)}{2 (a_2 + 1)}}{S_P = S_0 +
- a1*(a1-1)/(2*(a2+1))}
- \cr
ACE
\tab \eqn{S_P = S_{abund} + \frac{S_{rare}}{C_{ace}}+ \frac{a_1}{C_{ace}}
\gamma^2_{ace}}{S_P = S_abund + S_rare/C_ace + a1/C_ace * gamma^2}
@@ -108,16 +116,16 @@
Functions estimate the standard errors of the estimates. These
only concern the number of added species, and assume that there is
- no variance in the observed richness.
- The equations of standard errors are too complicated to be reproduced in
- this help page, but they can be studied in the \R source code of the
- function.
- The standard error are based on the following sources: Chao (1987)
- for the Chao estimate and Smith and van Belle (1984) for the
- first-order Jackknife and the bootstrap (second-order jackknife is
- still missing).
- The variance estimator of \eqn{S_{ace}}{S_ace} was
- developed by Bob O'Hara (unpublished).
+ no variance in the observed richness. The equations of standard
+ errors are too complicated to be reproduced in this help page, but
+ they can be studied in the \R source code of the function and are
+ discussed in the \code{\link{vignette}} \dQuote{diversity-vegan}
+ that can be read with the \code{\link{vegandocs}} command. The
+ standard error are based on the following sources: Chiu et
+ al. (2014) for the Chao estimates and Smith and van Belle (1984)
+ for the first-order Jackknife and the bootstrap (second-order
+ jackknife is still missing). For the variance estimator of
+ \eqn{S_{ace}}{S_ace} see O'Hara (2005).
Functions \code{poolaccum} and \code{estaccumR} are similar to
\code{\link{specaccum}}, but estimate extrapolated richness indices
@@ -127,12 +135,14 @@
data. The functions share \code{summary} and \code{plot}
methods. The \code{summary} returns quantile envelopes of
permutations corresponding the given level of \code{alpha} and
- standard deviation of permutations for each sample size. The
+ standard deviation of permutations for each sample size. NB., these
+ are not based on standard deviations estimated within \code{specpool}
+ or \code{estimateR}, but they are based on permutations. The
\code{plot} function shows the mean and envelope of permutations
with given \code{alpha} for models. The selection of models can be
restricted and order changes using the \code{display} argument in
\code{summary} or \code{plot}. For configuration of \code{plot}
- command, see \code{\link[lattice]{xyplot}}
+ command, see \code{\link[lattice]{xyplot}}.
}
\value{
@@ -151,11 +161,18 @@
\references{
Chao, A. (1987). Estimating the population size for capture-recapture
data with unequal catchability. \emph{Biometrics} 43, 783--791.
+
+ Chiu, C.H., Wang, Y.T., Walther, B.A. & Chao, A. (2014). Improved
+ nonparametric lower bound of species richness via a modified
+ Good-Turing frequency formula. \emph{Biometrics} 70, 671--682.
Colwell, R.K. & Coddington, J.A. (1994). Estimating terrestrial
biodiversity through
extrapolation. \emph{Phil. Trans. Roy. Soc. London} B 345, 101--118.
+ O'Hara, R.B. (2005). Species richness estimators: how many species
+ can dance on the head of a pin? \emph{J. Anim. Ecol.} 74, 375--386.
+
Palmer, M.W. (1990). The estimation of species richness by
extrapolation. \emph{Ecology} 71, 1195--1198.
@@ -163,12 +180,19 @@
species richness. \emph{Biometrics} 40, 119--129.
}
\author{Bob O'Hara (\code{estimateR}) and Jari Oksanen.}
-\note{
- The functions are based on assumption that there is a species pool:
- The community is closed so that there is a fixed pool size \eqn{S_P}.
- Such cases may exist, although I have not seen them yet. All indices
- are biased for open communities.
+\note{ The functions are based on assumption that there is a species
+ pool: The community is closed so that there is a fixed pool size
+ \eqn{S_P}. In general, the functions give only the lower limit of
+ species richness: the real richness is \eqn{S >= S_P}, and there is
+ a consistent bias in the estimates. Even the bias-correction in Chao
+ only reduces the bias, but does not remove it completely (Chiu et
+ al. 2014).
+
+ Optional small sample correction was added to \code{specpool} in
+ \pkg{vegan} 2.2-0. It was not used in the older literature (Chao
+ 1987), but it is recommended recently (Chiu et al. 2014).
+
See \url{http://viceroy.eeb.uconn.edu/EstimateS} for a more complete
(and positive) discussion and alternative software for some platforms.
}
[TRUNCATED]
To get the complete diff run:
svnlook diff /svnroot/vegan -r 2906
From noreply at r-forge.r-project.org Thu Nov 6 14:43:26 2014
From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org)
Date: Thu, 6 Nov 2014 14:43:26 +0100 (CET)
Subject: [Vegan-commits] r2907 - www
Message-ID: <20141106134326.E54CC186AC6@r-forge.r-project.org>
Author: jarioksa
Date: 2014-11-06 14:43:26 +0100 (Thu, 06 Nov 2014)
New Revision: 2907
Modified:
www/NEWS.html
Log:
Update NEWS.html to vegan 2.2-0
Modified: www/NEWS.html
===================================================================
--- www/NEWS.html 2014-11-06 09:17:29 UTC (rev 2906)
+++ www/NEWS.html 2014-11-06 13:43:26 UTC (rev 2907)
@@ -1,10 +1,9 @@
-
-R: vegan News
-
-
+R: vegan News
+
+
-
NEWS
R Documentation
+
NEWS
R Documentation
vegan News
@@ -22,32 +21,31 @@
integer giving the number of parallel processes. In unix-alikes
(Mac OS, Linux) this will launch "multicore" processing
and in Windows it will set up "snow" clusters as desribed
-in the documentation of parallel package. If option
+in the documentation of the parallel package. If option"mc.cores" is set to an integer > 1, this will be used to
automatically start parallel processing. Finally, the argument
can also be a previously set up "snow" cluster which will
be used both in Windows and in unix-alikes. Vegan vignette
on Design decision explains the implementation (use
vegandocs("decission"), and parallel package has more
-extensive documentation on parallel processing in R.
+extensive documentation on parallel processing in R.
The following function use parallel processing in analysing
-permutatin statistics: adonis, anosim,
+permutation statistics: adonis, anosim,
anova.cca (and permutest.cca), mantel (and
-mantel.partial), mrpp, permutest.betadisper
-and simper. In addition, bioenv can compare
-several candidate sets of models in paralle, metaMDS can
-launch several random starts in parallel, and oecosimu
-can evaluate test statistics for several null models in
-parallel.
+mantel.partial), mrpp, ordiareatest,
+permutest.betadisper and simper. In addition,
+bioenv can compare several candidate sets of models in
+paralle, metaMDS can launch several random starts in
+parallel, and oecosimu can evaluate test statistics for
+several null models in parallel.
-
All permutation tests are based on the permute
-package which offers strong tools for restricted
-permutation. All these functions have argument
-permutations. The default usage of simple non-restricted
-permutations is achieved by giving a single integer number as
-its argument. Restricted permutations can be defined using the
+
All permutation tests are based on the permute package
+which offers strong tools for restricted permutation. All these
+functions have argument permutations. The default usage of
+simple non-restricted permutations is achieved by giving a single
+integer number. Restricted permutations can be defined using the
how function of the permute package. Finally, the
argument can be a permutation matrix where rows define
permutations. It is possible to use external or user constructed
@@ -60,13 +58,13 @@
vegandocs("permutations").
The following functions use the permute package:
-CCorA, adonis, anosim, anova.cca
-(plus associated permutest.cca, add1.cca,
+CCorA, adonis, anosim, anova.cca (plus
+associated permutest.cca, add1.cca,
drop1.cca, ordistep, ordiR2step),
envfit (plus associated factorfit and
vectorfit), mantel (and mantel.partial),
-mrpp, mso, permutest.betadisper,
-protest and simper.
+mrpp, mso, ordiareatest,
+permutest.betadisper, protest and simper.
Community null model generation has been completely
@@ -93,7 +91,7 @@
vegan package dependencies and namespace imports
-were adapted to changes in R, and no more trigger warnings and
+were adapted to changes in R, and no more trigger warnings and
notes in package tests.
@@ -112,7 +110,7 @@
Function dispweight implements dispersion weighting
-of Clarke et al. (Marine Ecology Progress Series, 320,
+of Clarke et al. (Marine Ecology Progress Series, 320,
11–27). In addition, we implemented a new method for
generalized dispersion weighting gdispweight. Both
methods downweight species that are significantly
@@ -122,29 +120,35 @@
New hclust support functions reorder,
rev and scores. Functions reorder and
rev are similar as these functions for dendrogram
-objects. However, reorder can use (and defaults to)
-weighted mean. In weighted mean the node average is always the
+objects in base R. However, reorder can use (and defaults
+to) weighted mean. In weighted mean the node average is always the
mean of member leaves, whereas the dendrogram uses always
-the unweighted means of joined branches.
+unweighted means of joined branches.
-
permustats to extract and inspect permutation
+
Function ordiareatest supplements ordihull and
+ordiellipse and provides a randomization test for the
+one-sided alternative hypothesis that convex hulls or ellipses in
+two-dimensional ordination space have smaller areas than with
+randomized groups.
+
+
+
Function permustats extracts and inspects permutation
results with support functions summary, density,
densityplot, qqnorm and qqmath. The
-density and qqnorm are standard R tools that
-only work with one statistic, and densityplot and
-qqmath are lattice graphics that work with
-univariate and multivariate statistics. The results of following
-functions can be extracted: anosim, adonis,
-mantel (and mantel.partial), mrpp,
-oecosimu, permustest.cca (but not the
-corresponding anova methods),
-permutest.betadisper, and protest.
+density and qqnorm are standard R tools that only
+work with one statistic, and densityplot and qqmath
+are lattice graphics that work with univariate and
+multivariate statistics. The results of following functions can be
+extracted: anosim, adonis, mantel (and
+mantel.partial), mrpp, oecosimu,
+permustest.cca (but not the corresponding anova
+methods), permutest.betadisper, and protest.
-
stressplot functions display the ordination
-distances at given number of dimensions against original
-distances. These are a generalization of stressplot for
+
stressplot functions display the ordination distances
+at given number of dimensions against original distances. The
+method functins are similar to stressplot for
metaMDS, and always use the inherent distances of each
ordination method. The functions are available for the results
capscale, cca, princomp, prcomp,
@@ -164,7 +168,7 @@
ordiellipse can handle points exactly on a line,
-including only two points.
+including only two points (with a warning).
plotting radfit results for several species failed if
@@ -239,18 +243,45 @@
distance in addition to the default Euclidean.
-
User can set colours and line types in unction
+
User can set colours and line types in function
rarecurve for plotting rarefaction curves.
spantree gained a support function as.hclust
-to change the minimum spannig tree into an hclust tree.
+to change the minimum spanning tree into an hclust tree.
fitspecaccum can do weighted analysis. Gained
lines method.
+
Functions for extrapolated number of species or for the size
+of species pool using Chao method were modified following Chiu et
+al., Biometrics 70, 671–682 (2014).
+
+
Incidence based specpool can now use (and defaults to)
+small sample correction with number of sites as the sample
+size. Function uses basic Chao extrapolation based on the ratio of
+singletons and doubletons, but switches now to bias corrected Chao
+extrapolation if there are no doubletons (species found
+twice). The variance formula for bias corrected Chao was derived
+following the supporting
+online material
+and differs slightly from Chiu et al. (2014).
+
+
The poolaccum function was changed similarly, but the small
+sample correction is used always.
+
+
The abundance based estimateR uses bias corrected Chao
+extrapolation, but earlier it estimated its variance with classic
+Chao model. Now we use the widespread
+approximate
+equation for variance.
+
+
With these changes these functions are more similar to
+EstimateS.
+
+
tabasco uses now reorder.hclust for
hclust object for better ordering than previously when it
cast trees to dendrogram objects.
@@ -270,7 +301,7 @@
III. varespec and dune use 8-character names (4
from genus + 4 from species epithet). New data set on
phylogenetic distances for dune was extracted from Zanne
-et al. (Nature, 2014).
+et al. (Nature 506, 89–92; 2014).
User configurable plots for rarecurve.
@@ -295,13 +326,13 @@
commsimulator is deprecated. Replace
-commsimulator(x, method) with simulate(nullmodel(x,
- method)).
+commsimulator(x, method) with
+simulate(nullmodel(x, method)).
density and densityplot for permutation
-results: use permustats with its density and
-densityplot method.
+results are deprecated: use permustats with its
+density and densityplot method.
@@ -402,11 +433,11 @@
This version is released due to changes in programming
-interface and testing procedures in R 3.0.2. If you are using an
-older version of R, there is no need to upgrade vegan. There
+interface and testing procedures in R 3.0.2. If you are using an
+older version of R, there is no need to upgrade vegan. There
are no new features nor bug fixes. The only user-visible changes
are in documentation and in output messages and formatting. Because
-of R changes, this version is dependent on R version 2.14.0
+of R changes, this version is dependent on R version 2.14.0
or newer and on lattice package.
@@ -422,7 +453,7 @@
This is a maintenance release that fixes some issues
-raised by changed in R toolset for processing vignettes. In
+raised by changed in R toolset for processing vignettes. In
the same we also fix some typographic issues in the vignettes.
@@ -468,7 +499,7 @@
tabasco() is a new function for graphical display
-of community data matrix. Technically it is an interface to R
+of community data matrix. Technically it is an interface to Rheatmap, but its use is closer to vegan function
vegemite. The function can reorder the community data
matrix similarly as vegemite, for instance, by ordination
@@ -657,7 +688,7 @@
plot etc. of the results. These methods are only used if
the full wcmdscale result is returned with, e.g., argument
eig = TRUE. The default is still to return only a matrix of
-scores similarly as the standard R function cmdscale(),
+scores similarly as the standard R function cmdscale(),
and in that case the new methods are not used.
@@ -756,13 +787,13 @@
version of LaTeX (TeXLive 2012).
-
R versions later than 2.15-1 (including development
+
R versions later than 2.15-1 (including development
version) report warnings and errors when installing and checking
vegan, and you must upgrade vegan to this version.
The warnings concern functions cIndexKM and
betadisper, and the error occurs in betadisper.
These errors and warnings were triggered by internal changes in
-R.
+R.
@@ -893,8 +924,8 @@
Added new nestedness functions nestedbetasor and
nestedbetajac that implement multiple-site dissimilarity
indices and their decomposition into turnover and nestedness
-components following Baselga (Global Ecology and
-Biogeography 19, 134–143; 2010).
+components following Baselga (Global Ecology and
+Biogeography 19, 134–143; 2010).
Added function rarecurve to draw rarefaction curves
@@ -904,8 +935,8 @@
Added function simper that implements
-“similarity percentages” of Clarke (Australian
-Journal of Ecology 18, 117–143; 1993). The method compares
+“similarity percentages” of Clarke (Australian
+Journal of Ecology 18, 117–143; 1993). The method compares
two or more groups and decomposes the average between-group
Bray-Curtis dissimilarity index to contributions by individual
species. The code was developed in
@@ -977,8 +1008,8 @@
Added Cao dissimilarity (CYd) as a new dissimilarity
-method in vegdist following Cao et al., Water
-Envir Res 69, 95–106 (1997). The index should be good for
+method in vegdist following Cao et al., Water
+Envir Res 69, 95–106 (1997). The index should be good for
data with high beta diversity and variable sampling
intensity. Thanks to consultation to Yong Cao (Univ Illinois,
USA).
@@ -1057,7 +1088,7 @@
clamtest: new function to classify species as
generalists and specialists in two distinct habitats (CLAM test of
-Chazdon et al., Ecology 92, 1332–1343; 2011). The test is
+Chazdon et al., Ecology 92, 1332–1343; 2011). The test is
based on multinomial distribution of individuals in two habitat
types or sampling units, and it is applicable only to count data
with no over-dispersion.
@@ -1077,7 +1108,7 @@
vegdist, but that uses equal sampling probabilities for
species and analytic equations. The new raupcrick
function uses simulation with oecosimu. The function
-follows Chase et al. (2011) Ecosphere 2:art24
+follows Chase et al. (2011) Ecosphere 2:art24
[doi:10.1890/ES10-00117.1],
and was developed with the consultation of Brian Inouye.
@@ -1110,12 +1141,12 @@
updated because of a ‘NAMESPACE’ issue.
-
R 2.14.0 changed so that it does not accept using
+
R 2.14.0 changed so that it does not accept using
sd() function for matrices (which was the behaviour at
-least since R 1.0-0), and several vegan functions were
+least since R 1.0-0), and several vegan functions were
changed to adapt to this change (rda, capscale,
simulate methods for rda, cca and
-capscale). The change in R 2.14.0 does not influence the
+capscale). The change in R 2.14.0 does not influence the
results but you probably wish to upgrade vegan to avoid
annoying warnings.
@@ -1149,11 +1180,11 @@
Peter Minchin joins the vegan team.
-
vegan implements standard R ‘NAMESPACE’. In
+
vegan implements standard R ‘NAMESPACE’. In
general, S3 methods are not exported which means that you
cannot directly use or see contents of functions like
cca.default, plot.cca or anova.ccabyterm. To
-use these functions you should rely on R delegation and simply
+use these functions you should rely on R delegation and simply
use cca and for its result objects use plot and
anova without suffix .cca. To see the contents of
the function you can use :::, such as
@@ -1200,7 +1231,7 @@
eventstar finds the minimum of the evenness profile
on the Tsallis entropy, and uses this to find the corresponding
values of diversity, evenness and numbers equivalent following
-Mendes et al. (Ecography 31, 450-456; 2008). The code was
+Mendes et al. (Ecography 31, 450-456; 2008). The code was
contributed by Eduardo Ribeira Cunha and Heloisa Beatriz Antoniazi
Evangelista and adapted to vegan by Peter Solymos.
@@ -1209,9 +1240,9 @@
the species accumulation results from specaccum. The
function can use new self-starting species accumulation models
in vegan or other self-starting non-linear regression
-models in R. The function can fit Arrhenius, Gleason, Gitay,
+models in R. The function can fit Arrhenius, Gleason, Gitay,
Lomolino (in vegan), asymptotic, Gompertz,
-Michaelis-Menten, logistic and Weibull (in base R) models. The
+Michaelis-Menten, logistic and Weibull (in base R) models. The
function has plot and predict methods.
@@ -1220,7 +1251,7 @@
SSlomolino. These can be used with fitspecaccum or
directly in non-linear regression with nls. These functions
were implemented because they were found good for species-area
-models by Dengler (J. Biogeogr. 36, 728-744; 2009).
+models by Dengler (J. Biogeogr. 36, 728-744; 2009).
From noreply at r-forge.r-project.org Thu Nov 6 14:44:14 2014
From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org)
Date: Thu, 6 Nov 2014 14:44:14 +0100 (CET)
Subject: [Vegan-commits] r2908 - pkg/vegan
Message-ID: <20141106134414.EFBFD186AC6@r-forge.r-project.org>
Author: jarioksa
Date: 2014-11-06 14:44:14 +0100 (Thu, 06 Nov 2014)
New Revision: 2908
Modified:
pkg/vegan/DESCRIPTION
Log:
Merge branch 'master' into r-forge-svn-local
Modified: pkg/vegan/DESCRIPTION
===================================================================
--- pkg/vegan/DESCRIPTION 2014-11-06 13:43:26 UTC (rev 2907)
+++ pkg/vegan/DESCRIPTION 2014-11-06 13:44:14 UTC (rev 2908)
@@ -1,7 +1,7 @@
Package: vegan
Title: Community Ecology Package
-Version: 2.1-43
-Date: 2014-09-12
+Version: 2.1-99
+Date: 2014-11-06
Author: Jari Oksanen, F. Guillaume Blanchet, Roeland Kindt, Pierre Legendre,
Peter R. Minchin, R. B. O'Hara, Gavin L. Simpson, Peter Solymos,
M. Henry H. Stevens, Helene Wagner
From mark.vankleunen at uni-konstanz.de Fri Nov 7 12:21:29 2014
From: mark.vankleunen at uni-konstanz.de (Mark van Kleunen)
Date: Fri, 07 Nov 2014 12:21:29 +0100
Subject: [Vegan-commits] species accumulation curves
Message-ID: <545CAB39.9050801@uni-konstanz.de>
Hi,
Is there a function in vegan or in another R package that allows one to
make species accumulation curves, in which the the cumulative number of
species is not fitted against the number of sites (as done in specaccum)
but against the cumulative area of the sites. Take as example that one
has a big matrix of the presence-absence of species in multiple European
countries, and wants to know the relationship between species richness
and area. So, I would like to randomly select one country, keep the
number of species and the area of that country, then randomly select
another country, combine it with the first country, keep the cumulative
number of species and the cumulative area of both countries, and so on.
This should then be repeated a 100 or 1000 times to get some confidence
intervals. Is this possible with any of the current functions?
best wishes,
Mark van Kleunen
From jari.oksanen at oulu.fi Fri Nov 7 13:01:06 2014
From: jari.oksanen at oulu.fi (Jari Oksanen)
Date: Fri, 7 Nov 2014 12:01:06 +0000
Subject: [Vegan-commits] species accumulation curves
In-Reply-To: <545CAB39.9050801@uni-konstanz.de>
References: <545CAB39.9050801@uni-konstanz.de>
Message-ID: <4d7f2dbf3d644811a4053e94a55e7185@nippu12.univ.yo.oulu.fi>
Function specaccum() in vegan has argument 'w' for weights or sampling effort. Use size are as weight.
Cheers, Jari Oksanen
________________________________________
From: vegan-commits-bounces at r-forge.wu-wien.ac.at on behalf of Mark van Kleunen
Sent: 07 November 2014 13:21
To: vegan-commits at r-forge.wu-wien.ac.at
Subject: [Vegan-commits] species accumulation curves
Hi,
Is there a function in vegan or in another R package that allows one to
make species accumulation curves, in which the the cumulative number of
species is not fitted against the number of sites (as done in specaccum)
but against the cumulative area of the sites. Take as example that one
has a big matrix of the presence-absence of species in multiple European
countries, and wants to know the relationship between species richness
and area. So, I would like to randomly select one country, keep the
number of species and the area of that country, then randomly select
another country, combine it with the first country, keep the cumulative
number of species and the cumulative area of both countries, and so on.
This should then be repeated a 100 or 1000 times to get some confidence
intervals. Is this possible with any of the current functions?
best wishes,
Mark van Kleunen
_______________________________________________
Vegan-commits mailing list
Vegan-commits at lists.r-forge.r-project.org
https://lists.r-forge.r-project.org/cgi-bin/mailman/listinfo/vegan-commits
From noreply at r-forge.r-project.org Fri Nov 7 15:12:28 2014
From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org)
Date: Fri, 7 Nov 2014 15:12:28 +0100 (CET)
Subject: [Vegan-commits] r2909 - in pkg/vegan: . tests tests/Examples
Message-ID: <20141107141228.728681810FB@r-forge.r-project.org>
Author: jarioksa
Date: 2014-11-07 15:12:27 +0100 (Fri, 07 Nov 2014)
New Revision: 2909
Removed:
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.R
pkg/vegan/tests/vegan-tests.Rout.save
Modified:
pkg/vegan/DESCRIPTION
Log:
Squashed commit of the following:
commit a3213955f51ffdd3feed87e7d38c101a807bbd12
Author: Jari Oksanen
Date: Fri Nov 7 15:50:07 2014 +0200
remove tests from the release version
commit e076ea25e2e8720136ac930e63ab075107d2b8f7
Author: Jari Oksanen
Date: Fri Nov 7 15:48:33 2014 +0200
Bump up version to 2.2-0 for CRAN release
commit f44316d16f19fa1d5fd307c61f96f0bc253f9bab
Author: Jari Oksanen
Date: Fri Nov 7 15:45:46 2014 +0200
Update web addresses to use github instead of R-Forge
Modified: pkg/vegan/DESCRIPTION
===================================================================
--- pkg/vegan/DESCRIPTION 2014-11-06 13:44:14 UTC (rev 2908)
+++ pkg/vegan/DESCRIPTION 2014-11-07 14:12:27 UTC (rev 2909)
@@ -1,7 +1,7 @@
Package: vegan
Title: Community Ecology Package
-Version: 2.1-99
-Date: 2014-11-06
+Version: 2.2-0
+Date: 2014-11-07
Author: Jari Oksanen, F. Guillaume Blanchet, Roeland Kindt, Pierre Legendre,
Peter R. Minchin, R. B. O'Hara, Gavin L. Simpson, Peter Solymos,
M. Henry H. Stevens, Helene Wagner
@@ -11,5 +11,6 @@
Imports: MASS, cluster, mgcv
Description: Ordination methods, diversity analysis and other
functions for community and vegetation ecologists.
-License: GPL-2
-URL: http://vegan.r-forge.r-project.org/
+License: GPL-2
+BugReports: https://github.com/vegandevs/vegan/issues
+URL: http://cran.r-project.org, https://github.com/vegandevs/vegan
Deleted: pkg/vegan/tests/Examples/vegan-Ex.Rout.save
===================================================================
--- pkg/vegan/tests/Examples/vegan-Ex.Rout.save 2014-11-06 13:44:14 UTC (rev 2908)
+++ pkg/vegan/tests/Examples/vegan-Ex.Rout.save 2014-11-07 14:12:27 UTC (rev 2909)
@@ -1,8417 +0,0 @@
-
-R Under development (unstable) (2014-11-03 r66928) -- "Unsuffered Consequences"
-Copyright (C) 2014 The R Foundation for Statistical Computing
-Platform: x86_64-unknown-linux-gnu (64-bit)
-
-R is free software and comes with ABSOLUTELY NO WARRANTY.
-You are welcome to redistribute it under certain conditions.
-Type 'license()' or 'licence()' for distribution details.
-
- Natural language support but running in an English locale
-
-R is a collaborative project with many contributors.
-Type 'contributors()' for more information and
-'citation()' on how to cite R or R packages in publications.
-
-Type 'demo()' for some demos, 'help()' for on-line help, or
-'help.start()' for an HTML browser interface to help.
-Type 'q()' to quit R.
-
-> pkgname <- "vegan"
-> source(file.path(R.home("share"), "R", "examples-header.R"))
-> options(warn = 1)
-> library('vegan')
-Loading required package: permute
-Loading required package: lattice
-This is vegan 2.1-43
->
-> base::assign(".oldSearch", base::search(), pos = 'CheckExEnv')
-> cleanEx()
-> nameEx("BCI")
-> ### * BCI
->
-> flush(stderr()); flush(stdout())
->
-> ### Name: BCI
-> ### Title: Barro Colorado Island Tree Counts
-> ### Aliases: BCI
-> ### Keywords: datasets
->
-> ### ** Examples
->
-> data(BCI)
-> ## UTM Coordinates (in metres)
-> UTM.EW <- rep(seq(625754, 626654, by=100), each=5)
-> UTM.NS <- rep(seq(1011569, 1011969, by=100), len=50)
->
->
->
-> cleanEx()
-> nameEx("CCorA")
-> ### * CCorA
->
-> flush(stderr()); flush(stdout())
->
-> ### Name: CCorA
-> ### Title: Canonical Correlation Analysis
-> ### Aliases: CCorA biplot.CCorA
-> ### Keywords: multivariate
->
-> ### ** Examples
->
-> # Example using two mite groups. The mite data are available in vegan
-> data(mite)
-> # Two mite species associations (Legendre 2005, Fig. 4)
-> group.1 <- c(1,2,4:8,10:15,17,19:22,24,26:30)
-> group.2 <- c(3,9,16,18,23,25,31:35)
-> # Separate Hellinger transformations of the two groups of species
-> mite.hel.1 <- decostand(mite[,group.1], "hel")
-> mite.hel.2 <- decostand(mite[,group.2], "hel")
-> rownames(mite.hel.1) = paste("S",1:nrow(mite),sep="")
-> rownames(mite.hel.2) = paste("S",1:nrow(mite),sep="")
-> out <- CCorA(mite.hel.1, mite.hel.2)
-> out
-
-Canonical Correlation Analysis
-
-Call:
-CCorA(Y = mite.hel.1, X = mite.hel.2)
-
- Y X
-Matrix Ranks 24 11
-
-Pillai's trace: 4.573009
-
-Significance of Pillai's trace:
-from F-distribution: 0.0032737
- CanAxis1 CanAxis2 CanAxis3 CanAxis4 CanAxis5 CanAxis6
-Canonical Correlations 0.92810 0.82431 0.81209 0.74981 0.70795 0.65950
- CanAxis7 CanAxis8 CanAxis9 CanAxis10 CanAxis11
-Canonical Correlations 0.50189 0.48179 0.41089 0.37823 0.28
-
- Y | X X | Y
-RDA R squares 0.33224 0.5376
-adj. RDA R squares 0.20560 0.2910
-
-> biplot(out, "ob") # Two plots of objects
-> biplot(out, "v", cex=c(0.7,0.6)) # Two plots of variables
-> biplot(out, "ov", cex=c(0.7,0.6)) # Four plots (2 for objects, 2 for variables)
-> biplot(out, "b", cex=c(0.7,0.6)) # Two biplots
-> biplot(out, xlabs = NA, plot.axes = c(3,5)) # Plot axes 3, 5. No object names
-> biplot(out, plot.type="biplots", xlabs = NULL) # Replace object names by numbers
->
-> # Example using random numbers. No significant relationship is expected
-> mat1 <- matrix(rnorm(60),20,3)
-> mat2 <- matrix(rnorm(100),20,5)
-> out2 = CCorA(mat1, mat2, permutations=99)
-> out2
-
-Canonical Correlation Analysis
-
-Call:
-CCorA(Y = mat1, X = mat2, permutations = 99)
-
- Y X
-Matrix Ranks 3 5
-
-Pillai's trace: 0.6455578
-
-Significance of Pillai's trace:
-from F-distribution: 0.70352
-based on permutations: 0.69
-Permutation: free
-Number of permutations: 99
-
- CanAxis1 CanAxis2 CanAxis3
-Canonical Correlations 0.69691 0.38140 0.12
-
- Y | X X | Y
-RDA R squares 0.17066 0.1368
-adj. RDA R squares -0.12553 -0.0250
-
-> biplot(out2, "b")
->
->
->
-> cleanEx()
-> nameEx("MDSrotate")
-> ### * MDSrotate
->
-> flush(stderr()); flush(stdout())
->
-> ### Name: MDSrotate
-> ### Title: Rotate First MDS Dimension Parallel to an External Variable
-> ### Aliases: MDSrotate
-> ### Keywords: multivariate
->
-> ### ** Examples
->
-> data(varespec)
-> data(varechem)
-> mod <- monoMDS(vegdist(varespec))
-> mod <- with(varechem, MDSrotate(mod, pH))
-> plot(mod)
-> ef <- envfit(mod ~ pH, varechem, permutations = 0)
-> plot(ef)
-> ordisurf(mod ~ pH, varechem, knots = 1, add = TRUE)
-
-Family: gaussian
-Link function: identity
-
-Formula:
-y ~ poly(x1, 1) + poly(x2, 1)
-
-Total model degrees of freedom 3
-
-REML score: -3.185099
->
->
->
-> cleanEx()
-> nameEx("MOStest")
-> ### * MOStest
->
-> flush(stderr()); flush(stdout())
->
-> ### Name: MOStest
-> ### Title: Mitchell-Olds & Shaw Test for the Location of Quadratic Extreme
-> ### Aliases: MOStest plot.MOStest fieller.MOStest profile.MOStest
-> ### confint.MOStest
-> ### Keywords: models regression
->
-> ### ** Examples
->
-> ## The Al-Mufti data analysed in humpfit():
-> mass <- c(140,230,310,310,400,510,610,670,860,900,1050,1160,1900,2480)
-> spno <- c(1, 4, 3, 9, 18, 30, 20, 14, 3, 2, 3, 2, 5, 2)
-> mod <- MOStest(mass, spno)
-> ## Insignificant
-> mod
-
-Mitchell-Olds and Shaw test
-Null: hump of a quadratic linear predictor is at min or max
-
-Family: gaussian
-Link function: identity
-
- hump min max
- 46.89749 140.00000 2480.00000
-***** Caution: hump/pit not bracketed by the data ******
-
- min/max F Pr(>F)
-hump at min 140 0.0006 0.9816
-hump at max 2480 0.3161 0.5852
-Combined 0.9924
-> ## ... but inadequate shape of the curve
-> op <- par(mfrow=c(2,2), mar=c(4,4,1,1)+.1)
-> plot(mod)
-> ## Looks rather like log-link with Poisson error and logarithmic biomass
-> mod <- MOStest(log(mass), spno, family=quasipoisson)
-> mod
-
-Mitchell-Olds and Shaw test
-Null: hump of a quadratic linear predictor is at min or max
-
-Family: quasipoisson
-Link function: log
-
- min hump max
-4.941642 6.243371 7.816014
-
- min/max F Pr(>F)
-hump at min 4.9416 7.1367 0.02174 *
-hump at max 7.8160 9.0487 0.01191 *
-Combined 0.03338 *
----
-Signif. codes: 0 ?***? 0.001 ?**? 0.01 ?*? 0.05 ?.? 0.1 ? ? 1
-> plot(mod)
-> par(op)
-> ## Confidence Limits
-> fieller.MOStest(mod)
- 2.5 % 97.5 %
-5.255827 6.782979
-> confint(mod)
- 2.5 % 97.5 %
-5.816021 6.574378
-> plot(profile(mod))
->
->
->
-> graphics::par(get("par.postscript", pos = 'CheckExEnv'))
-> cleanEx()
-> nameEx("RsquareAdj")
-> ### * RsquareAdj
->
-> flush(stderr()); flush(stdout())
->
-> ### Name: RsquareAdj
-> ### Title: Adjusted R-square
-> ### Aliases: RsquareAdj RsquareAdj.default RsquareAdj.rda RsquareAdj.cca
-> ### RsquareAdj.lm RsquareAdj.glm
-> ### Keywords: univar multivariate
->
-> ### ** Examples
->
-> data(mite)
-> data(mite.env)
-> ## rda
-> m <- rda(decostand(mite, "hell") ~ ., mite.env)
-> RsquareAdj(m)
-$r.squared
-[1] 0.5265047
-
-$adj.r.squared
-[1] 0.4367038
-
-> ## default method
-> RsquareAdj(0.8, 20, 5)
-[1] 0.7285714
->
->
->
-> cleanEx()
-> nameEx("SSarrhenius")
-> ### * SSarrhenius
->
-> flush(stderr()); flush(stdout())
->
-> ### Name: SSarrhenius
-> ### Title: Self-Starting nls Species-Area Models
-> ### Aliases: SSarrhenius SSlomolino SSgitay SSgleason
-> ### Keywords: models
->
-> ### ** Examples
->
-> ## Get species area data: sipoo.area gives the areas of islands
-> example(sipoo)
-
-sipoo> data(sipoo)
-
-sipoo> ## Areas of the islands in hectares
-sipoo> sipoo.area <- c(1.1, 2.1, 2.2, 3.1, 3.5, 5.8, 6, 6.1, 6.5, 11.4, 13,
-sipoo+ 14.5, 16.1 ,17.5, 28.7, 40.5, 104.5, 233)
-> S <- specnumber(sipoo)
-> plot(S ~ sipoo.area, xlab = "Island Area (ha)", ylab = "Number of Species",
-+ ylim = c(1, max(S)))
-> ## The Arrhenius model
-> marr <- nls(S ~ SSarrhenius(sipoo.area, k, z))
-> marr
-Nonlinear regression model
- model: S ~ SSarrhenius(sipoo.area, k, z)
- data: parent.frame()
- k z
-3.4062 0.4364
- residual sum-of-squares: 78.1
-
-Number of iterations to convergence: 5
-Achieved convergence tolerance: 1.056e-06
-> ## confidence limits from profile likelihood
-> confint(marr)
-Waiting for profiling to be done...
- 2.5% 97.5%
-k 2.6220312 4.3033906
-z 0.3813576 0.4944693
-> ## draw a line
-> xtmp <- seq(min(sipoo.area), max(sipoo.area), len=51)
-> lines(xtmp, predict(marr, newdata=data.frame(sipoo.area = xtmp)), lwd=2)
-> ## The normal way is to use linear regression on log-log data,
-> ## but this will be different from the previous:
-> mloglog <- lm(log(S) ~ log(sipoo.area))
-> mloglog
-
-Call:
-lm(formula = log(S) ~ log(sipoo.area))
-
-Coefficients:
- (Intercept) log(sipoo.area)
- 1.0111 0.4925
-
-> lines(xtmp, exp(predict(mloglog, newdata=data.frame(sipoo.area=xtmp))),
-+ lty=2)
-> ## Gleason: log-linear
-> mgle <- nls(S ~ SSgleason(sipoo.area, k, slope))
-> lines(xtmp, predict(mgle, newdata=data.frame(sipoo.area=xtmp)),
-+ lwd=2, col=2)
-> ## Gitay: quadratic of log-linear
-> mgit <- nls(S ~ SSgitay(sipoo.area, k, slope))
-> lines(xtmp, predict(mgit, newdata=data.frame(sipoo.area=xtmp)),
-+ lwd=2, col = 3)
-> ## Lomolino: using original names of the parameters (Lomolino 2000):
-> mlom <- nls(S ~ SSlomolino(sipoo.area, Smax, A50, Hill))
-> mlom
-Nonlinear regression model
- model: S ~ SSlomolino(sipoo.area, Smax, A50, Hill)
- data: parent.frame()
- Smax A50 Hill
-53.493 94.697 2.018
- residual sum-of-squares: 55.37
-
-Number of iterations to convergence: 6
-Achieved convergence tolerance: 9.715e-07
-> lines(xtmp, predict(mlom, newdata=data.frame(sipoo.area=xtmp)),
-+ lwd=2, col = 4)
-> ## One canned model of standard R:
-> mmic <- nls(S ~ SSmicmen(sipoo.area, slope, Asym))
-> lines(xtmp, predict(mmic, newdata = data.frame(sipoo.area=xtmp)),
-+ lwd =2, col = 5)
-> legend("bottomright", c("Arrhenius", "log-log linear", "Gleason", "Gitay",
-+ "Lomolino", "Michaelis-Menten"), col=c(1,1,2,3,4,5), lwd=c(2,1,2,2,2,2),
-+ lty=c(1,2,1,1,1,1))
-> ## compare models (AIC)
-> allmods <- list(Arrhenius = marr, Gleason = mgle, Gitay = mgit,
-+ Lomolino = mlom, MicMen= mmic)
-> sapply(allmods, AIC)
-Arrhenius Gleason Gitay Lomolino MicMen
- 83.49847 96.94018 80.54984 79.30718 83.02003
->
->
->
-> cleanEx()
-> nameEx("add1.cca")
-> ### * add1.cca
->
-> flush(stderr()); flush(stdout())
->
-> ### Name: add1.cca
-> ### Title: Add or Drop Single Terms to a Constrained Ordination Model
-> ### Aliases: add1.cca drop1.cca
-> ### Keywords: multivariate models
->
-> ### ** Examples
->
-> data(dune)
-> data(dune.env)
-> ## Automatic model building based on AIC but with permutation tests
-> step(cca(dune ~ 1, dune.env), reformulate(names(dune.env)), test="perm")
-Start: AIC=87.66
-dune ~ 1
-
- Df AIC F Pr(>F)
-+ Moisture 3 86.608 2.2536 0.005 **
-+ Management 3 86.935 2.1307 0.005 **
-+ A1 1 87.411 2.1400 0.025 *
- 87.657
-+ Manure 4 88.832 1.5251 0.045 *
-+ Use 2 89.134 1.1431 0.295
----
-Signif. codes: 0 ?***? 0.001 ?**? 0.01 ?*? 0.05 ?.? 0.1 ? ? 1
-
-Step: AIC=86.61
-dune ~ Moisture
-
- Df AIC F Pr(>F)
- 86.608
-+ Management 3 86.813 1.4565 0.045 *
-+ A1 1 86.992 1.2624 0.150
-+ Use 2 87.259 1.2760 0.120
-+ Manure 4 87.342 1.3143 0.040 *
-- Moisture 3 87.657 2.2536 0.010 **
----
-Signif. codes: 0 ?***? 0.001 ?**? 0.01 ?*? 0.05 ?.? 0.1 ? ? 1
-Call: cca(formula = dune ~ Moisture, data = dune.env)
-
- Inertia Proportion Rank
-Total 2.1153 1.0000
-Constrained 0.6283 0.2970 3
-Unconstrained 1.4870 0.7030 16
-Inertia is mean squared contingency coefficient
-
-Eigenvalues for constrained axes:
- CCA1 CCA2 CCA3
-0.4187 0.1330 0.0766
-
-Eigenvalues for unconstrained axes:
- CA1 CA2 CA3 CA4 CA5 CA6 CA7 CA8 CA9 CA10 CA11
-0.4098 0.2259 0.1761 0.1234 0.1082 0.0908 0.0859 0.0609 0.0566 0.0467 0.0419
- CA12 CA13 CA14 CA15 CA16
-0.0201 0.0143 0.0099 0.0085 0.0080
-
-> ## see ?ordistep to do the same, but based on permutation P-values
-> ## Not run:
-> ##D ordistep(cca(dune ~ 1, dune.env), reformulate(names(dune.env)), perm.max=200)
-> ## End(Not run)
-> ## Manual model building
-> ## -- define the maximal model for scope
-> mbig <- rda(dune ~ ., dune.env)
-> ## -- define an empty model to start with
-> m0 <- rda(dune ~ 1, dune.env)
-> ## -- manual selection and updating
-> add1(m0, scope=formula(mbig), test="perm")
- Df AIC F Pr(>F)
- 89.620
-A1 1 89.591 1.9217 0.060 .
-Moisture 3 87.707 2.5883 0.005 **
-Management 3 87.082 2.8400 0.005 **
-Use 2 91.032 1.1741 0.280
-Manure 4 89.232 1.9539 0.015 *
----
-Signif. codes: 0 ?***? 0.001 ?**? 0.01 ?*? 0.05 ?.? 0.1 ? ? 1
-> m0 <- update(m0, . ~ . + Management)
-> add1(m0, scope=formula(mbig), test="perm")
- Df AIC F Pr(>F)
- 87.082
-A1 1 87.424 1.2965 0.175
-Moisture 3 85.567 1.9764 0.005 **
-Use 2 88.284 1.0510 0.440
-Manure 3 87.517 1.3902 0.095 .
----
-Signif. codes: 0 ?***? 0.001 ?**? 0.01 ?*? 0.05 ?.? 0.1 ? ? 1
-> m0 <- update(m0, . ~ . + Moisture)
-> ## -- included variables still significant?
-> drop1(m0, test="perm")
- Df AIC F Pr(>F)
- 85.567
-Management 3 87.707 2.1769 0.010 **
-Moisture 3 87.082 1.9764 0.005 **
----
-Signif. codes: 0 ?***? 0.001 ?**? 0.01 ?*? 0.05 ?.? 0.1 ? ? 1
-> add1(m0, scope=formula(mbig), test="perm")
- Df AIC F Pr(>F)
- 85.567
-A1 1 86.220 0.8359 0.645
-Use 2 86.842 0.8027 0.700
-Manure 3 85.762 1.1225 0.320
->
->
->
-> cleanEx()
-> nameEx("adipart")
-> ### * adipart
->
-> flush(stderr()); flush(stdout())
->
-> ### Name: adipart
-> ### Title: Additive Diversity Partitioning and Hierarchical Null Model
-> ### Testing
-> ### Aliases: adipart adipart.default adipart.formula hiersimu
-> ### hiersimu.default hiersimu.formula
-> ### Keywords: multivariate
->
-> ### ** Examples
->
-> ## NOTE: 'nsimul' argument usually needs to be >= 99
-> ## here much lower value is used for demonstration
->
-> data(mite)
-> data(mite.xy)
-> data(mite.env)
-> ## Function to get equal area partitions of the mite data
-> cutter <- function (x, cut = seq(0, 10, by = 2.5)) {
-+ out <- rep(1, length(x))
-+ for (i in 2:(length(cut) - 1))
-+ out[which(x > cut[i] & x <= cut[(i + 1)])] <- i
-+ return(out)}
-> ## The hierarchy of sample aggregation
-> levsm <- with(mite.xy, data.frame(
-+ l1=1:nrow(mite),
-+ l2=cutter(y, cut = seq(0, 10, by = 2.5)),
-+ l3=cutter(y, cut = seq(0, 10, by = 5)),
-+ l4=cutter(y, cut = seq(0, 10, by = 10))))
-> ## Let's see in a map
-> par(mfrow=c(1,3))
-> plot(mite.xy, main="l1", col=as.numeric(levsm$l1)+1, asp = 1)
-> plot(mite.xy, main="l2", col=as.numeric(levsm$l2)+1, asp = 1)
-> plot(mite.xy, main="l3", col=as.numeric(levsm$l3)+1, asp = 1)
-> par(mfrow=c(1,1))
-> ## Additive diversity partitioning
-> adipart(mite, index="richness", nsimul=19)
-adipart object
-
-Call: adipart(y = mite, index = "richness", nsimul = 19)
-
-nullmodel method ?r2dtable? with 19 simulations
-options: index richness, weights unif
-alternative hypothesis: statistic is less or greater than simulated values
-
- statistic z mean 2.5% 50% 97.5% Pr(sim.)
-alpha.1 15.114 -38.43 22.344 22.032 22.300 22.608 0.05 *
-gamma 35.000 0.00 35.000 35.000 35.000 35.000 1.00
-beta.1 19.886 38.43 12.656 12.392 12.700 12.968 0.05 *
----
-Signif. codes: 0 ?***? 0.001 ?**? 0.01 ?*? 0.05 ?.? 0.1 ? ? 1
-> adipart(mite ~ ., levsm, index="richness", nsimul=19)
-adipart object
-
-Call: adipart(formula = mite ~ ., data = levsm, index = "richness",
-nsimul = 19)
-
-nullmodel method ?r2dtable? with 19 simulations
-options: index richness, weights unif
-alternative hypothesis: statistic is less or greater than simulated values
-
- statistic z mean 2.5% 50% 97.5% Pr(sim.)
-alpha.1 15.114 -46.2370 22.39624 22.12571 22.44286 22.6236 0.05 *
-alpha.2 29.750 -21.7076 34.81579 34.36250 35.00000 35.0000 0.05 *
-alpha.3 33.000 0.0000 35.00000 35.00000 35.00000 35.0000 0.05 *
-gamma 35.000 0.0000 35.00000 35.00000 35.00000 35.0000 1.00
-beta.1 14.636 9.0407 12.41955 12.00750 12.42857 12.8743 0.05 *
-beta.2 3.250 13.1373 0.18421 0.00000 0.00000 0.6375 0.05 *
-beta.3 2.000 0.0000 0.00000 0.00000 0.00000 0.0000 0.05 *
----
-Signif. codes: 0 ?***? 0.001 ?**? 0.01 ?*? 0.05 ?.? 0.1 ? ? 1
-> ## Hierarchical null model testing
-> ## diversity analysis (similar to adipart)
-> hiersimu(mite, FUN=diversity, relative=TRUE, nsimul=19)
-hiersimu object
-
-Call: hiersimu(y = mite, FUN = diversity, relative = TRUE, nsimul = 19)
-
-nullmodel method ?r2dtable? with 19 simulations
-
-alternative hypothesis: statistic is less or greater than simulated values
-
- statistic z mean 2.5% 50% 97.5% Pr(sim.)
-level_1 0.76064 -71.195 0.93904 0.93487 0.93856 0.9444 0.05 *
-leve_2 1.00000 0.000 1.00000 1.00000 1.00000 1.0000 1.00
----
-Signif. codes: 0 ?***? 0.001 ?**? 0.01 ?*? 0.05 ?.? 0.1 ? ? 1
-> hiersimu(mite ~., levsm, FUN=diversity, relative=TRUE, nsimul=19)
-hiersimu object
-
-Call: hiersimu(formula = mite ~ ., data = levsm, FUN = diversity,
-relative = TRUE, nsimul = 19)
-
-nullmodel method ?r2dtable? with 19 simulations
-
-alternative hypothesis: statistic is less or greater than simulated values
-
- statistic z mean 2.5% 50% 97.5% Pr(sim.)
-l1 0.76064 -75.139 0.93833 0.93389 0.93819 0.9427 0.05 *
-l2 0.89736 -110.968 0.99811 0.99699 0.99814 0.9999 0.05 *
-l3 0.92791 -417.338 0.99940 0.99904 0.99943 0.9996 0.05 *
-l4 1.00000 0.000 1.00000 1.00000 1.00000 1.0000 1.00
----
-Signif. codes: 0 ?***? 0.001 ?**? 0.01 ?*? 0.05 ?.? 0.1 ? ? 1
-> ## Hierarchical testing with the Morisita index
-> morfun <- function(x) dispindmorisita(x)$imst
-> hiersimu(mite ~., levsm, morfun, drop.highest=TRUE, nsimul=19)
-hiersimu object
-
-Call: hiersimu(formula = mite ~ ., data = levsm, FUN = morfun,
-drop.highest = TRUE, nsimul = 19)
-
-nullmodel method ?r2dtable? with 19 simulations
-
-alternative hypothesis: statistic is less or greater than simulated values
-
- statistic z mean 2.5% 50% 97.5% Pr(sim.)
-l1 0.52070 8.5216 0.353253 0.322624 0.351073 0.3848 0.05 *
-l2 0.60234 14.3854 0.153047 0.096700 0.150434 0.1969 0.05 *
-l3 0.67509 20.3162 -0.182473 -0.234793 -0.195937 -0.0988 0.05 *
----
-Signif. codes: 0 ?***? 0.001 ?**? 0.01 ?*? 0.05 ?.? 0.1 ? ? 1
->
->
->
-> graphics::par(get("par.postscript", pos = 'CheckExEnv'))
-> cleanEx()
-> nameEx("adonis")
-> ### * adonis
->
-> flush(stderr()); flush(stdout())
->
-> ### Name: adonis
-> ### Title: Permutational Multivariate Analysis of Variance Using Distance
-> ### Matrices
-> ### Aliases: adonis
-> ### Keywords: multivariate nonparametric
->
-> ### ** Examples
->
-> data(dune)
-> data(dune.env)
-> adonis(dune ~ Management*A1, data=dune.env, permutations=99)
-
-Call:
-adonis(formula = dune ~ Management * A1, data = dune.env, permutations = 99)
-
-Permutation: free
-Number of permutations: 99
-
-Terms added sequentially (first to last)
-
- Df SumsOfSqs MeanSqs F.Model R2 Pr(>F)
-Management 3 1.4686 0.48953 3.2629 0.34161 0.01 **
-A1 1 0.4409 0.44089 2.9387 0.10256 0.04 *
-Management:A1 3 0.5892 0.19639 1.3090 0.13705 0.23
-Residuals 12 1.8004 0.15003 0.41878
-Total 19 4.2990 1.00000
----
-Signif. codes: 0 ?***? 0.001 ?**? 0.01 ?*? 0.05 ?.? 0.1 ? ? 1
->
->
-> ### Example of use with strata, for nested (e.g., block) designs.
->
-> dat <- expand.grid(rep=gl(2,1), NO3=factor(c(0,10)),field=gl(3,1) )
-> dat
- rep NO3 field
-1 1 0 1
-2 2 0 1
-3 1 10 1
-4 2 10 1
-5 1 0 2
-6 2 0 2
-7 1 10 2
-8 2 10 2
-9 1 0 3
-10 2 0 3
-11 1 10 3
-12 2 10 3
-> Agropyron <- with(dat, as.numeric(field) + as.numeric(NO3)+2) +rnorm(12)/2
-> Schizachyrium <- with(dat, as.numeric(field) - as.numeric(NO3)+2) +rnorm(12)/2
-> total <- Agropyron + Schizachyrium
-> dotplot(total ~ NO3, dat, jitter.x=TRUE, groups=field,
-+ type=c('p','a'), xlab="NO3", auto.key=list(columns=3, lines=TRUE) )
->
-> Y <- data.frame(Agropyron, Schizachyrium)
-> mod <- metaMDS(Y)
-Run 0 stress 0.08556586
-Run 1 stress 0.1560544
-Run 2 stress 0.08556586
-... New best solution
-... procrustes: rmse 1.09439e-06 max resid 1.88838e-06
-*** Solution reached
-> plot(mod)
-> ### Hulls show treatment
-> with(dat, ordihull(mod, group=NO3, show="0"))
-> with(dat, ordihull(mod, group=NO3, show="10", col=3))
-> ### Spider shows fields
-> with(dat, ordispider(mod, group=field, lty=3, col="red"))
->
-> ### Correct hypothesis test (with strata)
-> adonis(Y ~ NO3, data=dat, strata=dat$field, perm=999)
-
-Call:
-adonis(formula = Y ~ NO3, data = dat, permutations = 999, strata = dat$field)
-
-Blocks: strata
-Permutation: free
-Number of permutations: 999
-
-Terms added sequentially (first to last)
-
- Df SumsOfSqs MeanSqs F.Model R2 Pr(>F)
-NO3 1 0.055856 0.055856 4.0281 0.28714 0.009 **
-Residuals 10 0.138667 0.013867 0.71286
-Total 11 0.194524 1.00000
----
-Signif. codes: 0 ?***? 0.001 ?**? 0.01 ?*? 0.05 ?.? 0.1 ? ? 1
->
-> ### Incorrect (no strata)
-> adonis(Y ~ NO3, data=dat, perm=999)
-
-Call:
-adonis(formula = Y ~ NO3, data = dat, permutations = 999)
-
-Permutation: free
-Number of permutations: 999
-
-Terms added sequentially (first to last)
-
- Df SumsOfSqs MeanSqs F.Model R2 Pr(>F)
-NO3 1 0.055856 0.055856 4.0281 0.28714 0.005 **
-Residuals 10 0.138667 0.013867 0.71286
-Total 11 0.194524 1.00000
----
-Signif. codes: 0 ?***? 0.001 ?**? 0.01 ?*? 0.05 ?.? 0.1 ? ? 1
->
->
->
-> cleanEx()
-> nameEx("anosim")
-> ### * anosim
->
-> flush(stderr()); flush(stdout())
->
-> ### Name: anosim
-> ### Title: Analysis of Similarities
-> ### Aliases: anosim summary.anosim plot.anosim
-> ### Keywords: multivariate nonparametric htest
->
-> ### ** Examples
->
-> data(dune)
-> data(dune.env)
-> dune.dist <- vegdist(dune)
-> attach(dune.env)
-> dune.ano <- anosim(dune.dist, Management)
-> summary(dune.ano)
-
-Call:
-anosim(dat = dune.dist, grouping = Management)
-Dissimilarity: bray
-
-ANOSIM statistic R: 0.2579
- Significance: 0.017
-
-Permutation: free
-Number of permutations: 999
-
-Upper quantiles of permutations (null model):
- 90% 95% 97.5% 99%
-0.121 0.174 0.222 0.276
-
-Dissimilarity ranks between and within classes:
- 0% 25% 50% 75% 100% N
-Between 4 58.50 104.00 145.500 188.0 147
-BF 5 15.25 25.50 41.250 57.0 3
-HF 1 7.25 46.25 68.125 89.5 10
-NM 6 64.75 124.50 156.250 181.0 15
-SF 3 32.75 53.50 99.250 184.0 15
-
-> plot(dune.ano)
-Warning in bxp(list(stats = c(4, 58.5, 104, 145.5, 188, 5, 15.25, 25.5, :
- some notches went outside hinges ('box'): maybe set notch=FALSE
->
->
->
-> cleanEx()
-
-detaching ?dune.env?
-
-> nameEx("anova.cca")
-> ### * anova.cca
->
-> flush(stderr()); flush(stdout())
->
-> ### Name: anova.cca
-> ### Title: Permutation Test for Constrained Correspondence Analysis,
-> ### Redundancy Analysis and Constrained Analysis of Principal Coordinates
-> ### Aliases: anova.cca permutest permutest.cca
-> ### Keywords: multivariate htest
->
-> ### ** Examples
->
-> data(varespec)
-> data(varechem)
-> vare.cca <- cca(varespec ~ Al + P + K, varechem)
-> ## overall test
-> anova(vare.cca)
-Permutation test for cca under reduced model
-Permutation: free
-Number of permutations: 999
-
-Model: cca(formula = varespec ~ Al + P + K, data = varechem)
- Df ChiSquare F Pr(>F)
-Model 3 0.64413 2.984 0.001 ***
-Residual 20 1.43906
----
-Signif. codes: 0 ?***? 0.001 ?**? 0.01 ?*? 0.05 ?.? 0.1 ? ? 1
->
->
->
-> cleanEx()
-> nameEx("as.mlm")
-> ### * as.mlm
->
-> flush(stderr()); flush(stdout())
->
-> ### Name: as.mlm.cca
-> ### Title: Refit Constrained Ordination as a Multiple Response Linear Model
-> ### Aliases: as.mlm as.mlm.cca as.mlm.rda
-> ### Keywords: models multivariate
->
-> ### ** Examples
->
-> data(varespec)
-> data(varechem)
-> mod <- cca(varespec ~ Al + P + K, data=varechem)
-> lmod <- as.mlm(mod)
-> ## Coefficients
-> lmod
-
-Call:
-lm(formula = wa ~ . - 1, data = as.data.frame(X))
-
-Coefficients:
- CCA1 CCA2 CCA3
-Al 0.007479 -0.001884 0.003381
-P -0.006491 -0.102190 -0.022307
-K -0.006756 0.015344 0.017067
-
-> coef(mod)
- CCA1 CCA2 CCA3
-Al 0.007478556 -0.001883637 0.003380774
-P -0.006491081 -0.102189737 -0.022306682
-K -0.006755568 0.015343662 0.017067351
-> ## Influential observations
-> influence.measures(lmod)
-Influence measures of
- lm(formula = wa ~ . - 1, data = as.data.frame(X)) :
-
- dfb.Al dfb.P dfb.K CCA1 CCA2 CCA3 cov.r CCA1.1
-18 -0.251387 0.00976 -0.06310 0.27401 0.1806 -0.118754 0.0265 7.38e-03
-15 0.099858 0.13864 -0.11781 -0.16542 -0.0935 0.006898 0.0319 2.86e-03
-24 -0.003448 -0.44078 0.20788 -0.48239 -0.1750 -0.260788 0.0307 2.33e-02
-27 0.071682 -0.01707 -0.03516 -0.10185 -0.1676 0.022271 0.0406 1.13e-03
-23 -0.116533 0.06900 -0.02545 0.14407 0.2918 -0.220457 0.0355 2.23e-03
-19 -0.007394 -0.01169 0.01080 0.01360 -0.2318 -0.000417 0.0359 2.02e-05
-22 0.150916 0.14845 -0.13091 -0.20466 0.3815 0.168914 0.0376 4.50e-03
-16 0.107456 0.17900 -0.09917 -0.21196 0.2250 0.194432 0.0338 4.75e-03
-28 0.332161 -0.34398 -0.05414 -0.67745 0.0742 0.620990 0.0364 4.65e-02
-13 0.366880 -1.00834 1.23685 1.33919 0.4102 0.277067 0.1124 1.89e-01
-14 0.024147 0.02512 -0.01161 -0.03608 0.1491 0.053638 0.0355 1.42e-04
-20 0.000747 -0.00560 0.00205 -0.00661 0.2935 -0.190351 0.0368 4.77e-06
-25 0.166736 -0.11049 0.09341 -0.20954 -0.1627 -0.070753 0.0346 4.66e-03
-7 -0.397145 0.15747 0.15662 -0.59116 0.5842 -0.838287 0.0327 3.51e-02
-5 -0.279996 -0.09119 -0.35616 0.73579 0.3694 -0.326563 0.0281 5.18e-02
-6 0.003191 -0.00168 -0.01550 0.02590 0.3447 0.201072 0.0400 7.34e-05
-3 -0.302851 -0.07889 0.25932 -0.41958 -0.2766 0.536017 0.0386 1.85e-02
-4 -0.058151 -0.02719 0.00870 -0.06644 0.8199 0.131003 0.0486 4.83e-04
-2 0.020380 0.00416 -0.00373 0.02055 -0.4158 -0.160401 0.0395 4.62e-05
-9 0.074217 0.09551 -0.10857 0.12712 -0.3481 0.644579 0.0383 1.75e-03
-12 -0.097825 -0.20830 0.04637 0.28644 -0.6601 0.270324 0.0280 8.19e-03
-10 0.149178 0.66594 -0.12975 0.89348 -0.2510 0.000571 0.0118 5.90e-02
-11 0.014687 0.00691 0.00105 0.01913 0.1838 -0.301086 0.0377 4.00e-05
-21 0.148213 0.15461 -0.02915 -0.25306 -0.1892 -0.318491 0.0361 6.81e-03
- CCA2.1 CCA3.1 hat inf
-18 0.003207 1.39e-03 0.0321
-15 0.000915 4.98e-06 0.0295
-24 0.003071 6.82e-03 0.1135
-27 0.003062 5.41e-05 0.1375
-23 0.009151 5.22e-03 0.0555
-19 0.005873 1.90e-08 0.0176
-22 0.015648 3.07e-03 0.1077
-16 0.005348 3.99e-03 0.0594
-28 0.000559 3.91e-02 0.2256
-13 0.017773 8.11e-03 0.7168 *
-14 0.002424 3.13e-04 0.0158
-20 0.009421 3.96e-03 0.0393
-25 0.002810 5.31e-04 0.0670
-7 0.034274 7.06e-02 0.1635
-5 0.013057 1.02e-02 0.1588
-6 0.012996 4.42e-03 0.1169
-3 0.008056 3.02e-02 0.1833
-4 0.073491 1.88e-03 0.2741
-2 0.018909 2.81e-03 0.1063
-9 0.013158 4.51e-02 0.0978
-12 0.043487 7.29e-03 0.0409
-10 0.004658 2.41e-08 0.0768
-11 0.003694 9.91e-03 0.0632
-21 0.003807 1.08e-02 0.1009
-> plot(mod, type = "n")
-> points(mod, cex = 10*hatvalues(lmod), pch=16, xpd = TRUE)
-> text(mod, display = "bp", col = "blue")
->
->
->
-> cleanEx()
-> nameEx("beals")
-> ### * beals
->
-> flush(stderr()); flush(stdout())
->
-> ### Name: beals
-> ### Title: Beals Smoothing and Degree of Absence
-> ### Aliases: beals swan
-> ### Keywords: manip smooth
->
-> ### ** Examples
->
-> data(dune)
-> ## Default
-> x <- beals(dune)
-> ## Remove target species
-> x <- beals(dune, include = FALSE)
-> ## Smoothed values against presence or absence of species
-> pa <- decostand(dune, "pa")
-> boxplot(as.vector(x) ~ unlist(pa), xlab="Presence", ylab="Beals")
-> ## Remove the bias of tarbet species: Yields lower values.
-> beals(dune, type =3, include = FALSE)
- Achimill Agrostol Airaprae Alopgeni Anthodor Bellpere Bromhord
-1 0.49590853 0.38333415 0.01157407 0.4923280 0.30827883 0.4935662 0.43263047
-2 0.47083676 0.39501120 0.03361524 0.4718807 0.34723984 0.4917791 0.42000984
-3 0.34063019 0.52738394 0.01520046 0.5309152 0.21609954 0.4033301 0.33010938
-4 0.30816435 0.51198853 0.02876960 0.5971801 0.21542662 0.4398775 0.35732610
-5 0.59949785 0.27622698 0.06632771 0.3349203 0.48876285 0.4322142 0.44309579
-6 0.58819821 0.26299306 0.05967771 0.2700508 0.53154426 0.3696613 0.39760652
-7 0.56496165 0.29412293 0.05329633 0.3403047 0.48010987 0.4051777 0.40471531
-8 0.21230502 0.66906674 0.02588333 0.5187956 0.16247716 0.2720122 0.21219877
-9 0.30323659 0.59744543 0.02213662 0.5792855 0.21896113 0.3292320 0.28613526
-10 0.54083871 0.26902092 0.07349127 0.3372958 0.42671693 0.4705094 0.42934344
-11 0.40509331 0.31656550 0.10259239 0.3185489 0.38766111 0.3713794 0.31413659
-12 0.21008725 0.66278454 0.03625297 0.5753377 0.20078932 0.2802946 0.22974415
-13 0.21850759 0.68239707 0.02191119 0.6404427 0.16737280 0.2939740 0.24942466
-14 0.13570397 0.76284476 0.02298398 0.4107645 0.12128973 0.1682755 0.13757552
-15 0.09168815 0.79412733 0.02538032 0.4505613 0.10117099 0.1420251 0.09794548
-16 0.06335463 0.87877202 0.00742115 0.5232448 0.05538377 0.1516354 0.09458531
-17 0.55254140 0.07330247 0.29233391 0.1013889 0.69331132 0.3129358 0.34982363
-18 0.37751017 0.34451209 0.08535723 0.2838834 0.36918166 0.3676424 0.30478244
-19 0.29826049 0.25952255 0.35137675 0.1934048 0.51929869 0.2237843 0.18074796
-20 0.05429986 0.76675441 0.06144615 0.4063662 0.10738280 0.1450721 0.06706410
- Chenalbu Cirsarve Comapalu Eleopalu Elymrepe Empenigr
-1 0.025132275 0.09504980 0.000000000 0.05592045 0.4667439 0.00000000
-2 0.043866562 0.08570299 0.026548839 0.08656209 0.4407282 0.01829337
-3 0.065338638 0.08967477 0.031898812 0.16099072 0.4137888 0.01074444
-4 0.057970906 0.12920228 0.039859621 0.16112450 0.4399661 0.02527165
-5 0.026434737 0.05520104 0.015892090 0.05419613 0.3575948 0.03029752
-6 0.021256367 0.03223112 0.030347896 0.08784329 0.3138879 0.03093489
-7 0.038467708 0.04706743 0.017083997 0.06694311 0.3586644 0.02304603
-8 0.063278453 0.06688407 0.100703044 0.29777644 0.3046956 0.02102222
-9 0.069879277 0.07647268 0.045830682 0.19018562 0.3523460 0.01838883
-10 0.025686639 0.06037513 0.029746617 0.07787078 0.3736128 0.03425596
-11 0.021234732 0.05778318 0.035740922 0.11146095 0.2884798 0.07310076
-12 0.103543341 0.07799259 0.045375827 0.19518888 0.3354080 0.03413656
-13 0.122547745 0.07905124 0.056084315 0.22437598 0.3511708 0.01840390
-14 0.042990591 0.03618335 0.241811837 0.55982776 0.1428372 0.01989756
-15 0.035609053 0.04022968 0.198176675 0.53973883 0.1462975 0.02215971
-16 0.056246994 0.05184498 0.201352298 0.51523810 0.1832397 0.00742115
-17 0.007716049 0.01049383 0.009876543 0.02777778 0.1929470 0.21968254
[TRUNCATED]
To get the complete diff run:
svnlook diff /svnroot/vegan -r 2909
From noreply at r-forge.r-project.org Mon Nov 10 11:41:55 2014
From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org)
Date: Mon, 10 Nov 2014 11:41:55 +0100 (CET)
Subject: [Vegan-commits] r2910 - in pkg/vegan: . R
Message-ID: <20141110104155.C4BA5187296@r-forge.r-project.org>
Author: jarioksa
Date: 2014-11-10 11:41:55 +0100 (Mon, 10 Nov 2014)
New Revision: 2910
Modified:
pkg/vegan/DESCRIPTION
pkg/vegan/R/anova.cca.R
pkg/vegan/R/getPermuteMatrix.R
Log:
Squashed commit of the following:
commit 65e815f0f4e49ce728e88f128af5e00bc68e97f4
Author: Jari Oksanen
Date: Mon Nov 10 12:26:54 2014 +0200
Update DESCRIPTION date
Cherry-picked fixes to 'strata' handling in anova.cca from
master/fix-strata-redefinition
commit 4436bcb8dbb530e38cb0a541926d0606b55109e4
Author: Jari Oksanen
Date: Mon Nov 10 11:06:09 2014 +0200
anova.cca passes permutationMatrix: no need to pass 'strata'
anova.cca alwyas passes a permutation matrix to permutest.cca
and there is no need to pass 'strata' (which will be ingored).
commit 3e14e65e8d70332b35818f3c4ac7f1c4849d4289
Author: Jari Oksanen
Date: Sun Nov 9 20:23:28 2014 +0200
Do not set strata if they appear to have been set earlier
anova.cca generated permutation matrix with strata in
getPermuteMatrix and passed that on to other functions (like
permutest.cca). This was broken in efd575f1 which passed
strata from anova.cca (unnecessarily), but we fix it in
getPermuteMatrix so that the solution is more general (and
strata are to be deprecated in the next releases in any case).
Modified: pkg/vegan/DESCRIPTION
===================================================================
--- pkg/vegan/DESCRIPTION 2014-11-07 14:12:27 UTC (rev 2909)
+++ pkg/vegan/DESCRIPTION 2014-11-10 10:41:55 UTC (rev 2910)
@@ -1,7 +1,7 @@
Package: vegan
Title: Community Ecology Package
Version: 2.2-0
-Date: 2014-11-07
+Date: 2014-11-10
Author: Jari Oksanen, F. Guillaume Blanchet, Roeland Kindt, Pierre Legendre,
Peter R. Minchin, R. B. O'Hara, Gavin L. Simpson, Peter Solymos,
M. Henry H. Stevens, Helene Wagner
Modified: pkg/vegan/R/anova.cca.R
===================================================================
--- pkg/vegan/R/anova.cca.R 2014-11-07 14:12:27 UTC (rev 2909)
+++ pkg/vegan/R/anova.cca.R 2014-11-10 10:41:55 UTC (rev 2910)
@@ -53,10 +53,10 @@
attr(sol, "control") <- control
return(sol)
}
- ## basic overall test
+ ## basic overall test: pass other arguments except 'strata'
+ ## because 'permutations' already is a permutationMatrix
tst <- permutest.cca(object, permutations = permutations,
- model = model, parallel = parallel,
- strata = strata, ...)
+ model = model, parallel = parallel, ...)
Fval <- c(tst$F.0, NA)
Pval <- (sum(tst$F.perm >= tst$F.0) + 1)/(tst$nperm + 1)
Pval <- c(Pval, NA)
Modified: pkg/vegan/R/getPermuteMatrix.R
===================================================================
--- pkg/vegan/R/getPermuteMatrix.R 2014-11-07 14:12:27 UTC (rev 2909)
+++ pkg/vegan/R/getPermuteMatrix.R 2014-11-10 10:41:55 UTC (rev 2910)
@@ -14,13 +14,10 @@
if (length(perm) == 1) {
perm <- how(nperm = perm)
}
- ## apply 'strata'
+ ## apply 'strata', but only if possible: ignore silently other cases
if (!missing(strata) && !is.null(strata)) {
- if (!inherits(perm, "how")) # 'perm' is a matrix
- stop("'strata' can be used only with simple permutation or with 'how()'")
- if (!is.null(getBlocks(perm)))
- stop("'strata' cannot be applied when 'blocks' are defined in 'how()'")
- setBlocks(perm) <- strata
+ if (inherits(perm, "how") && is.null(getBlocks(perm)))
+ setBlocks(perm) <- strata
}
## now 'perm' is either a how() or a matrix
if (inherits(perm, "how"))
From noreply at r-forge.r-project.org Tue Nov 11 15:58:23 2014
From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org)
Date: Tue, 11 Nov 2014 15:58:23 +0100 (CET)
Subject: [Vegan-commits] r2911 - in pkg/vegan: R vignettes
Message-ID: <20141111145823.86769187689@r-forge.r-project.org>
Author: jarioksa
Date: 2014-11-11 15:58:23 +0100 (Tue, 11 Nov 2014)
New Revision: 2911
Modified:
pkg/vegan/R/plot.envfit.R
pkg/vegan/vignettes/decision-vegan.Rnw
Log:
Squashed commit of the following:
commit ad5f0dac7e52c2e0c85bd863dd8a47fd88f50975
Author: Jari Oksanen
Date: Tue Nov 11 13:46:06 2014 +0200
Fix labelling envfit plots with a vector of labels
Fixes bug report #74 at github.com: it was documented that you
do not need to use a list(vectors=, factors=) to relabel plotted
items if there is only one type of items (vectors or factors).
commit a2f6b3b49ad94a14b6aa9319830133977a6e502f
Merge: 65e815f a6d876b
Author: Gavin Simpson
Date: Mon Nov 10 10:43:22 2014 -0600
Merge branch 'typo-design-vignette' into cran-2.2
commit a6d876b70b2f91017e84793dea0e2a18560d0ad2
Author: Gavin Simpson
Date: Mon Nov 10 09:31:11 2014 -0600
typo had symbolic forms for species and site scores swapped in table caption?
Modified: pkg/vegan/R/plot.envfit.R
===================================================================
--- pkg/vegan/R/plot.envfit.R 2014-11-10 10:41:55 UTC (rev 2910)
+++ pkg/vegan/R/plot.envfit.R 2014-11-11 14:58:23 UTC (rev 2911)
@@ -21,7 +21,7 @@
stop("needs a list with both 'vectors' and 'factors' labels")
## need to handle the case where both sets of labels are NULL
## such as when used with the default interface and single x
- ln <- sapply(labs, is.null)
+ ln <- !sapply(labs, is.null)
if (ln["v"])
labs$v <- labels
if (ln["f"])
Modified: pkg/vegan/vignettes/decision-vegan.Rnw
===================================================================
--- pkg/vegan/vignettes/decision-vegan.Rnw 2014-11-10 10:41:55 UTC (rev 2910)
+++ pkg/vegan/vignettes/decision-vegan.Rnw 2014-11-11 14:58:23 UTC (rev 2911)
@@ -428,8 +428,8 @@
in the functions \code{prcomp} and \code{princomp}, and the
one used in the \pkg{vegan} function \code{rda}
and the proprietary software \proglang{Canoco}
- scores in terms of orthonormal species ($u_{ik}$) and site scores
- ($v_{jk}$), eigenvalues ($\lambda_k$), number of sites ($n$) and
+ scores in terms of orthonormal species ($v_{ik}$) and site scores
+ ($u_{jk}$), eigenvalues ($\lambda_k$), number of sites ($n$) and
species standard deviations ($s_j$). In \code{rda},
$\mathrm{const} = \sqrt[4]{(n-1) \sum \lambda_k}$. Corresponding
negative scaling in \pkg{vegan}
From noreply at r-forge.r-project.org Tue Nov 18 08:48:41 2014
From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org)
Date: Tue, 18 Nov 2014 08:48:41 +0100 (CET)
Subject: [Vegan-commits] r2912 - in pkg/vegan: . R
Message-ID: <20141118074842.1131A18770A@r-forge.r-project.org>
Author: jarioksa
Date: 2014-11-18 08:48:41 +0100 (Tue, 18 Nov 2014)
New Revision: 2912
Modified:
pkg/vegan/.Rbuildignore
pkg/vegan/DESCRIPTION
pkg/vegan/R/plot.envfit.R
Log:
Squashed commit of the following:
commit 9dfb167c47599a319b49e81056655bbb1206f825
Author: Jari Oksanen
Date: Tue Nov 18 09:33:42 2014 +0200
Do not put github README.md to the R package
(cherry picked from commit 06f649426a44e065c5e435bbdfaf4d113ece9a22)
commit 546eeac33cc904b0d0e2def40a68c80fcf7f4053
Author: Jari Oksanen
Date: Tue Nov 18 09:35:36 2014 +0200
vegan 2.2-0 was released: everything goes to 2.2-1 from now on
commit 454a6247af58ba9f6b92a85485687681c00effbd
Author: Jari Oksanen
Date: Mon Nov 17 11:07:46 2014 +0200
Update DATE for the last change in the released version
commit c0b78834b076f194556401702c78a36a870d3ddb
Author: Jari Oksanen
Date: Wed Nov 12 12:42:33 2014 +0200
Better fix than 83d3bf1 and cca3f27 for resetting labels in envfit
Previous fix only looked at the null of internal labels, but these
can be null because the item (vectors or factors) was missing, or
the item was there but names were missing. Fix cca3f27 failed
in the first case and 83d3bf1 in latter case. Now we check for
the existence of factors/vectors, and if only one them is present,
we reset it labels whether they existed or were null.
commit ad5f0dac7e52c2e0c85bd863dd8a47fd88f50975
Author: Jari Oksanen
Date: Tue Nov 11 13:46:06 2014 +0200
Fix labelling envfit plots with a vector of labels
Fixes bug report #74 at github.com: it was documented that you
do not need to use a list(vectors=, factors=) to relabel plotted
items if there is only one type of items (vectors or factors).
Modified: pkg/vegan/.Rbuildignore
===================================================================
--- pkg/vegan/.Rbuildignore 2014-11-11 14:58:23 UTC (rev 2911)
+++ pkg/vegan/.Rbuildignore 2014-11-18 07:48:41 UTC (rev 2912)
@@ -1,5 +1,5 @@
LICENSE
+^README\.md$
^\.travis\.yml$
^travis-tool\.sh
^appveyor\.yml$
-
Modified: pkg/vegan/DESCRIPTION
===================================================================
--- pkg/vegan/DESCRIPTION 2014-11-11 14:58:23 UTC (rev 2911)
+++ pkg/vegan/DESCRIPTION 2014-11-18 07:48:41 UTC (rev 2912)
@@ -1,7 +1,7 @@
Package: vegan
Title: Community Ecology Package
-Version: 2.2-0
-Date: 2014-11-10
+Version: 2.2-1
+Date: 2014-11-18
Author: Jari Oksanen, F. Guillaume Blanchet, Roeland Kindt, Pierre Legendre,
Peter R. Minchin, R. B. O'Hara, Gavin L. Simpson, Peter Solymos,
M. Henry H. Stevens, Helene Wagner
Modified: pkg/vegan/R/plot.envfit.R
===================================================================
--- pkg/vegan/R/plot.envfit.R 2014-11-11 14:58:23 UTC (rev 2911)
+++ pkg/vegan/R/plot.envfit.R 2014-11-18 07:48:41 UTC (rev 2912)
@@ -17,15 +17,14 @@
} else {
## input vector: either vectors or factors must be NULL,
## and the existing set of labels is replaced
- if (!is.null(labs$v) && !is.null(labs$f))
+ if (!is.null(x$vectors) && !is.null(x$factors))
stop("needs a list with both 'vectors' and 'factors' labels")
## need to handle the case where both sets of labels are NULL
## such as when used with the default interface and single x
- ln <- !sapply(labs, is.null)
- if (ln["v"])
- labs$v <- labels
- if (ln["f"])
+ if (!is.null(x$factors))
labs$f <- labels
+ else
+ labs$v <- labels
}
}
vect <- NULL
From noreply at r-forge.r-project.org Mon Nov 24 11:44:01 2014
From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org)
Date: Mon, 24 Nov 2014 11:44:01 +0100 (CET)
Subject: [Vegan-commits] r2913 - in pkg/vegan: . R man
Message-ID: <20141124104401.B91B41801A5@r-forge.r-project.org>
Author: jarioksa
Date: 2014-11-24 11:44:01 +0100 (Mon, 24 Nov 2014)
New Revision: 2913
Modified:
pkg/vegan/NAMESPACE
pkg/vegan/R/alias.cca.R
pkg/vegan/R/as.mlm.R
pkg/vegan/R/biplot.rda.R
pkg/vegan/R/coef.cca.R
pkg/vegan/R/coef.rda.R
pkg/vegan/R/fitted.capscale.R
pkg/vegan/R/fitted.cca.R
pkg/vegan/R/fitted.rda.R
pkg/vegan/R/intersetcor.R
pkg/vegan/R/linestack.R
pkg/vegan/R/tolerance.cca.R
pkg/vegan/R/vif.cca.R
pkg/vegan/man/linestack.Rd
Log:
Squashed commit of the following:
commit 465dc0303fe4a756b9a0680457a28e474c546eed
Author: Gavin Simpson
Date: Sat Nov 22 15:41:52 2014 -0600
linestack now handles labels arg without setting names(x); allows expressions as labels for example
commit 59564fb5e9a93b8a6b724b32ff77c18f8d183bae
Author: Gavin Simpson
Date: Sat Nov 22 11:44:47 2014 -0600
fix bug in labels length conditional test
commit c9f6b8a93d4fe8bc8ec26352ebe8772263a925a8
Author: Jari Oksanen
Date: Wed Nov 19 13:38:05 2014 +0200
Fix reconstruction of response matrix in CA (no CCA) for tolerance.cca
(cherry picked from commit 0434ac4e653aeccb9b3f903a30a9fdfa55f6d7ee)
commit c9817cb9bd315847db10bb257085b206e4499530
Author: Jari Oksanen
Date: Tue Nov 18 15:04:36 2014 +0200
More comprehensible error message when user asks biplots of CA
There is no biplot for CA, and its results were handled by
biplot.default that gave weird error messages. Now biplot.cca() was
added to give an informative error message. An alternative to this
would be to rename biplot.rda to biplot.cca: it already has an
error message for non-rda objects, and would only handle rda.
(cherry picked from commit 543ead1092a37e5791408bfc771d66a9f89efe28)
commit dcf2399a79043b520f76a78b4beff85fea38a758
Author: Jari Oksanen
Date: Tue Nov 18 13:45:18 2014 +0200
Fail informatively if support functions for CCA are used with CA
Several cca/rda/capscale support functions only worked with
constrained ordination, but did not check their input. This resulted
in cryptic error messages such as
Error in chol2inv(Q$qr, size = rank) :
'size' argument must be a positive integer
Now they fail with more informative error message that tells that
the method can be used only with constrained models.
(cherry picked from commit 4d98639b1cd10a84ed41182a6e7123b84315e441)
Modified: pkg/vegan/NAMESPACE
===================================================================
--- pkg/vegan/NAMESPACE 2014-11-18 07:48:41 UTC (rev 2912)
+++ pkg/vegan/NAMESPACE 2014-11-24 10:44:01 UTC (rev 2913)
@@ -123,6 +123,7 @@
S3method(bioenv, formula)
# biplot: stats
S3method(biplot, CCorA)
+S3method(biplot, cca)
S3method(biplot, rda)
# boxplot: graphics
S3method(boxplot, betadisper)
Modified: pkg/vegan/R/alias.cca.R
===================================================================
--- pkg/vegan/R/alias.cca.R 2014-11-18 07:48:41 UTC (rev 2912)
+++ pkg/vegan/R/alias.cca.R 2014-11-24 10:44:01 UTC (rev 2913)
@@ -1,6 +1,8 @@
`alias.cca` <-
function (object, names.only = FALSE, ...)
{
+ if (is.null(object$CCA$alias))
+ stop("no constrained component, 'alias' cannot be applied")
if (names.only)
return(object$CCA$alias)
CompPatt <- function(x, ...) {
Modified: pkg/vegan/R/as.mlm.R
===================================================================
--- pkg/vegan/R/as.mlm.R 2014-11-18 07:48:41 UTC (rev 2912)
+++ pkg/vegan/R/as.mlm.R 2014-11-24 10:44:01 UTC (rev 2913)
@@ -1,3 +1,6 @@
`as.mlm` <-
-function(x) UseMethod("as.mlm")
-
+function(x) {
+ if (is.null(x$CCA))
+ stop("'as.mlm' can be used only for constrained ordination")
+ UseMethod("as.mlm")
+}
Modified: pkg/vegan/R/biplot.rda.R
===================================================================
--- pkg/vegan/R/biplot.rda.R 2014-11-18 07:48:41 UTC (rev 2912)
+++ pkg/vegan/R/biplot.rda.R 2014-11-24 10:44:01 UTC (rev 2913)
@@ -3,7 +3,16 @@
## draws pca biplots with species as arrows
##
-biplot.rda <- function(x, choices = c(1, 2), scaling = 2,
+`biplot.cca` <-
+ function(x, ...)
+{
+ if (!inherits(x, "rda"))
+ stop("biplot can be used only with linear ordination (e.g., PCA)")
+ else
+ NextMethod("biplot", x, ...)
+}
+
+`biplot.rda` <- function(x, choices = c(1, 2), scaling = 2,
display = c("sites", "species"),
type, xlim, ylim, col = c(1,2), const, ...) {
if(!inherits(x, "rda"))
Modified: pkg/vegan/R/coef.cca.R
===================================================================
--- pkg/vegan/R/coef.cca.R 2014-11-18 07:48:41 UTC (rev 2912)
+++ pkg/vegan/R/coef.cca.R 2014-11-24 10:44:01 UTC (rev 2913)
@@ -1,9 +1,11 @@
"coef.cca" <-
function (object, ...)
{
- Q <- object$CCA$QR
- u <- object$CCA$u
- u <- sweep(u, 1, sqrt(object$rowsum), "*")
- qr.coef(Q, u)
+ if(is.null(object$CCA))
+ stop("unconstrained models do not have coefficients")
+ Q <- object$CCA$QR
+ u <- object$CCA$u
+ u <- sweep(u, 1, sqrt(object$rowsum), "*")
+ qr.coef(Q, u)
}
Modified: pkg/vegan/R/coef.rda.R
===================================================================
--- pkg/vegan/R/coef.rda.R 2014-11-18 07:48:41 UTC (rev 2912)
+++ pkg/vegan/R/coef.rda.R 2014-11-24 10:44:01 UTC (rev 2913)
@@ -1,7 +1,9 @@
"coef.rda" <-
function (object, ...)
{
- Q <- object$CCA$QR
- qr.coef(Q, object$CCA$u)
+ if(is.null(object$CCA))
+ stop("unconstrained models do not have coefficients")
+ Q <- object$CCA$QR
+ qr.coef(Q, object$CCA$u)
}
Modified: pkg/vegan/R/fitted.capscale.R
===================================================================
--- pkg/vegan/R/fitted.capscale.R 2014-11-18 07:48:41 UTC (rev 2912)
+++ pkg/vegan/R/fitted.capscale.R 2014-11-24 10:44:01 UTC (rev 2913)
@@ -3,6 +3,8 @@
type = c("response", "working"), ...)
{
model <- match.arg(model)
+ if (is.null(object[[model]]))
+ stop("component ", model, " does not exist")
type <- match.arg(type)
## Return scaled eigenvalues
U <- switch(model,
Modified: pkg/vegan/R/fitted.cca.R
===================================================================
--- pkg/vegan/R/fitted.cca.R 2014-11-18 07:48:41 UTC (rev 2912)
+++ pkg/vegan/R/fitted.cca.R 2014-11-24 10:44:01 UTC (rev 2913)
@@ -4,6 +4,8 @@
{
type <- match.arg(type)
model <- match.arg(model)
+ if (is.null(object[[model]]))
+ stop("component ", model, " does not exist")
gtot <- object$grand.total
rc <- object$rowsum %o% object$colsum
if (model == "pCCA")
Modified: pkg/vegan/R/fitted.rda.R
===================================================================
--- pkg/vegan/R/fitted.rda.R 2014-11-18 07:48:41 UTC (rev 2912)
+++ pkg/vegan/R/fitted.rda.R 2014-11-24 10:44:01 UTC (rev 2913)
@@ -3,6 +3,8 @@
{
type <- match.arg(type)
model <- match.arg(model)
+ if (is.null(object[[model]]))
+ stop("component ", model, " does not exist")
if (model == "pCCA")
Xbar <- object$pCCA$Fit
else
Modified: pkg/vegan/R/intersetcor.R
===================================================================
--- pkg/vegan/R/intersetcor.R 2014-11-18 07:48:41 UTC (rev 2912)
+++ pkg/vegan/R/intersetcor.R 2014-11-24 10:44:01 UTC (rev 2913)
@@ -2,6 +2,8 @@
{
if (!inherits(object, "cca"))
stop("can be used only with objects inheriting from 'cca'")
+ if (is.null(object$CCA))
+ stop("can be used only with constrained ordination")
wa <- object$CCA$wa
if (!inherits(object, "rda")) { # is CCA
w <- object$rowsum
Modified: pkg/vegan/R/linestack.R
===================================================================
--- pkg/vegan/R/linestack.R 2014-11-18 07:48:41 UTC (rev 2912)
+++ pkg/vegan/R/linestack.R 2014-11-24 10:44:01 UTC (rev 2913)
@@ -1,23 +1,30 @@
"linestack" <-
- function (x, labels, cex = 0.8, side = "right", hoff = 2, air = 1.1,
- at = 0, add = FALSE, axis = FALSE, ...)
+ function (x, labels, cex = 0.8, side = "right", hoff = 2, air = 1.1,
+ at = 0, add = FALSE, axis = FALSE, ...)
{
- if (!missing(labels) && length(labels == 1) && pmatch(labels,
- c("right", "left"), nomatch = FALSE)) {
+ x <- drop(x)
+ n <- length(x)
+ misslab <- missing(labels)
+ if (misslab) {
+ labels <- names(x)
+ }
+ nlab <- length(labels)
+ if (!misslab && nlab == 1L && pmatch(labels, c("right", "left"), nomatch = FALSE)) {
side <- labels
labels <- NULL
warning("argument 'label' is deprecated: use 'side'")
}
+ if (!misslab && n != nlab) {
+ msg <- paste("Wrong number of supplied 'labels'.\nExpected:",
+ n, "Got:", nlab, sep = " ")
+ stop(msg)
+ }
side <- match.arg(side, c("right", "left"))
- x <- drop(x)
- if (!missing(labels) && !is.null(labels))
- names(x) <- labels
- else if (is.null(names(x)))
- names(x) <- rep("", length(x))
op <- par(xpd = TRUE)
+ on.exit(par(op))
ord <- order(x)
x <- x[ord]
- n <- length(x)
+ labels <- labels[ord]
pos <- numeric(n)
if (!add) {
plot(pos, x, type = "n", axes = FALSE, xlab = "", ylab = "", ...)
@@ -38,19 +45,18 @@
}
segments(at, x[1], at, x[n])
if (side == "right") {
- text(at + hoff, pos, names(x), pos = 4, cex = cex, offset = 0.2,
+ text(at + hoff, pos, labels, pos = 4, cex = cex, offset = 0.2,
...)
segments(at, x, at + hoff, pos)
}
else if (side == "left") {
- text(at - hoff, pos, names(x), pos = 2, cex = cex, offset = 0.2,
+ text(at - hoff, pos, labels, pos = 2, cex = cex, offset = 0.2,
...)
segments(at, x, at - hoff, pos)
}
- if (axis)
- axis(if (side == "right")
+ if (axis)
+ axis(if (side == "right")
2
else 4, pos = at, las = 2)
- par(op)
invisible(pos[order(ord)])
}
Modified: pkg/vegan/R/tolerance.cca.R
===================================================================
--- pkg/vegan/R/tolerance.cca.R 2014-11-18 07:48:41 UTC (rev 2912)
+++ pkg/vegan/R/tolerance.cca.R 2014-11-24 10:44:01 UTC (rev 2913)
@@ -32,7 +32,11 @@
which <- "species"
## reconstruct species/response matrix Y - up to machine precision!
partialFit <- ifelse(is.null(x$pCCA$Fit), 0, x$pCCA$Fit)
- Y <- ((partialFit + x$CCA$Xbar) * sqrt(x$rowsum %o% x$colsum) +
+ if (is.null(x$CCA))
+ Xbar <- x$CA$Xbar
+ else
+ Xbar <- x$CCA$Xbar
+ Y <- ((partialFit + Xbar) * sqrt(x$rowsum %o% x$colsum) +
x$rowsum %o% x$colsum) * x$grand.total
which <- match.arg(which)
siteScrTypes <- if(is.null(x$CCA)){ "sites" } else {"lc"}
Modified: pkg/vegan/R/vif.cca.R
===================================================================
--- pkg/vegan/R/vif.cca.R 2014-11-18 07:48:41 UTC (rev 2912)
+++ pkg/vegan/R/vif.cca.R 2014-11-24 10:44:01 UTC (rev 2913)
@@ -1,6 +1,8 @@
`vif.cca` <-
function(object)
{
+ if (is.null(object$CCA))
+ stop("can be used only with constrained ordination")
Q <- object$CCA$QR
out <- rep(NA, NCOL(Q$qr))
names(out)[Q$pivot] <- colnames(Q$qr)
Modified: pkg/vegan/man/linestack.Rd
===================================================================
--- pkg/vegan/man/linestack.Rd 2014-11-18 07:48:41 UTC (rev 2912)
+++ pkg/vegan/man/linestack.Rd 2014-11-24 10:44:01 UTC (rev 2913)
@@ -9,18 +9,20 @@
}
\usage{
linestack(x, labels, cex = 0.8, side = "right", hoff = 2, air = 1.1,
- at = 0, add = FALSE, axis = FALSE, ...)
+ at = 0, add = FALSE, axis = FALSE, ...)
}
\arguments{
\item{x}{Numeric vector to be plotted. }
- \item{labels}{Text labels used instead of default (names of \code{x}).}
+ \item{labels}{Labels used instead of default (names of \code{x}). May
+ be expressions to be drawn with \code{\link{plotmath}}.}
\item{cex}{Size of the labels. }
- \item{side}{Put labels to the \code{"right"} or
- \code{"left"} of the axis. }
+ \item{side}{Put labels to the \code{"right"} or \code{"left"} of the
+ axis.}
\item{hoff}{Distance from the vertical axis to the label in units of
the width of letter \dQuote{m}. }
- \item{air}{Multiplier to string height to leave empty space between labels. }
+ \item{air}{Multiplier to string height to leave empty space between
+ labels.}
\item{at}{Position of plot in horizontal axis. }
\item{add}{Add to an existing plot. }
\item{axis}{Add axis to the plot. }
@@ -30,7 +32,7 @@
The function returns invisibly the shifted positions of labels in
user coordinates.
}
-\author{Jari Oksanen }
+\author{Jari Oksanen with modifications by Gavin L. Simpson}
\note{ The function always draws labelled diagrams. If you want to have
unlabelled diagrams, you can use, e.g., \code{\link{plot}},
\code{\link{stripchart}} or \code{\link{rug}}.
@@ -43,6 +45,23 @@
linestack(scores(ord, choices=1, display="sp"))
linestack(scores(ord, choices=1, display="si"), side="left", add=TRUE)
title(main="DCA axis 1")
+
+## Expressions as labels
+N <- 10 # Number of sites
+df <- data.frame(Ca = rlnorm(N, 2), NO3 = rlnorm(N, 4),
+ SO4 = rlnorm(N, 10), K = rlnorm(N, 3))
+ord <- rda(df, scale = TRUE)
+### vector of expressions for labels
+labs <- expression(Ca^{2+phantom()},
+ NO[3]^{-phantom()},
+ SO[4]^{-2},
+ K^{+phantom()})
+scl <- 1
+linestack(scores(ord, choices = 1, display = "species", scaling = scl),
+ labels = labs, air = 2)
+linestack(scores(ord, choices = 1, display = "site", scaling = scl),
+ side = "left", add = TRUE)
+title(main = "PCA axis 1")
}
\keyword{ hplot }
\keyword{ aplot }