[Vegan-commits] r1566 - in pkg/vegan: R inst man

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Sun Apr 3 10:50:05 CEST 2011


Author: jarioksa
Date: 2011-04-03 10:50:04 +0200 (Sun, 03 Apr 2011)
New Revision: 1566

Modified:
   pkg/vegan/R/monoMDS.R
   pkg/vegan/inst/ChangeLog
   pkg/vegan/man/monoMDS.Rd
Log:
R API to Fortran features in monoMDS

Modified: pkg/vegan/R/monoMDS.R
===================================================================
--- pkg/vegan/R/monoMDS.R	2011-04-01 13:15:12 UTC (rev 1565)
+++ pkg/vegan/R/monoMDS.R	2011-04-03 08:50:04 UTC (rev 1566)
@@ -1,16 +1,21 @@
 monoMDS <-
     function(dist, y, k = 2,
-             model = c("global", "local", "hybrid"), threshold = 0.8,
-             maxit = 200, tol = 0.0001, ...) 
+             model = c("global", "local", "linear", "hybrid"),
+             threshold = 0.8, maxit = 200, weakties = TRUE, stress = 1,
+             scaling = TRUE, smin = 0.00001, sfgrmin = 0.00001,
+             sratmax=0.99999, ...) 
 {
     model <- match.arg(model)
-    if (model == "global") {
+    if (model %in% c("global", "linear")) {
         ## global NMDS: lower triangle
         mat <- as.matrix(dist)
         dist <- mat[lower.tri(mat)]
         iidx <- row(mat)[lower.tri(mat)]
         jidx <- col(mat)[lower.tri(mat)]
-        iregn <- 1
+        if (model == "global")
+            iregn <- 1
+        else
+            iregn <- 2
         ngrp <- 1
         nobj <- nrow(mat)
         istart <- 1
@@ -52,17 +57,22 @@
     }
     ## y to vector
     y <- as.vector(as.matrix(y))
+    ## translate R args to Fortran call
+    if (weakties)
+        ities <- 1
+    else
+        ities <- 2
     ## Fortran call
     sol <- .Fortran("monoMDS", nobj = as.integer(nobj), nfix=as.integer(0),
                  ndim = as.integer(k), ndis = as.integer(ndis),
                  ngrp = as.integer(ngrp), diss = as.double(dist),
                  iidx = as.integer(iidx), jidx = as.integer(jidx),
                  xinit = as.double(y), istart = as.integer(istart),
-                 isform = as.integer(1), ities = as.integer(1),
-                 iregn = as.integer(iregn), iscal = as.integer(1),
+                 isform = as.integer(stress), ities = as.integer(ities),
+                 iregn = as.integer(iregn), iscal = as.integer(scaling),
                  maxits = as.integer(maxit),
-                 sratmx = as.double(0.99999), strmin = as.double(tol),
-                 sfgrmn = as.double(1e-7), dist = double(ndis),
+                 sratmx = as.double(sratmax), strmin = as.double(smin),
+                 sfgrmn = as.double(sfgrmin), dist = double(ndis),
                  dhat = double(ndis), points = double(k*nobj),
                  stress = double(1), iters = integer(1),
                  icause = integer(1), PACKAGE = "vegan")

Modified: pkg/vegan/inst/ChangeLog
===================================================================
--- pkg/vegan/inst/ChangeLog	2011-04-01 13:15:12 UTC (rev 1565)
+++ pkg/vegan/inst/ChangeLog	2011-04-03 08:50:04 UTC (rev 1566)
@@ -11,10 +11,10 @@
 	MDS, configurable and valid tie treatment, handles missing values,
 	and allows adding new points to existing ordinations. The Fortran
 	code is highly tuned, and much faster than other alternatives in
-	R. The current R interface allows only access to a subset of the
-	capabilities of the Fortran90 code, but the missing pieces will be
-	added gradually. The function will eventually replaces isoMDS() of
-	the MASS package as the main NMDS engine in metaMDS().
+	R. The R interfaces allows access to most features of the Fortan90
+	code, except adding new points to the ordination (which will need
+	a separate function). The function will eventually replaces
+	isoMDS() of the MASS package as the main NMDS engine in metaMDS().
 	
 Version 1.18-27 (closed April 1, 2011)
 

Modified: pkg/vegan/man/monoMDS.Rd
===================================================================
--- pkg/vegan/man/monoMDS.Rd	2011-04-01 13:15:12 UTC (rev 1565)
+++ pkg/vegan/man/monoMDS.Rd	2011-04-03 08:50:04 UTC (rev 1566)
@@ -9,8 +9,9 @@
   using monotone regression and primary (\dQuote{weak}) treatment of ties.
 }
 \usage{
-monoMDS(dist, y, k = 2, model = c("global", "local", "hybrid"), 
-    threshold = 0.8, maxit = 200, tol = 1e-04, ...)
+monoMDS(dist, y, k = 2, model = c("global", "local", "linear", "hybrid"), 
+    threshold = 0.8, maxit = 200, weakties = TRUE, stress = 1,
+    scaling = TRUE, smin = 0.00001, sfgrmin = 0.00001, sratmax=0.99999, ...) 
 }
 
 \arguments{
@@ -18,15 +19,32 @@
   \item{y}{Starting configuration. A random configuration will be
     generated if this is missing.}
   \item{k}{Number of dimensions.}
+
   \item{model}{MDS model: \code{"global"} is normal non-metric MDS
     with a monotone regression, \code{"local"} is non-metric MDS with
-    separate regressions for each point, and \code{"hybrid"} uses
-    linear MDS for dissimilarities below the threshold, and global
-    non-metric MDS for dissimilarities above the threshold. }
+    separate regressions for each point, \code{"linear"} uses linear
+    regression, and \code{"hybrid"} uses linear MDS for
+    dissimilarities below the threshold, and global non-metric MDS for
+    dissimilarities above the threshold. }
+
   \item{threshold}{Dissimilarity above which monotone regression is
     used instead of linear regression. }
   \item{maxit}{Maximum number of iterations.}
-  \item{tol}{Convergence tolerance.}
+  
+  \item{weakties}{Use primary or weak tie treatment, where equal
+    observed dissimilarities care allowed to have different fitted
+    values. if \code{FALSE}, then secondary (strong) tie treatment are
+    used, and tied values are not broken.}
+  
+  \item{stress}{Use Kruskal's stress type 1 or 2.}
+
+  \item{scaling}{Scale final scores to unit root mean squares.}
+
+  \item{smin, sfgrmin, sratmax}{Convergence criteria: iterations stop
+    when stress drops below \code{smin}, scale factor of the gradient
+    drops below \code{sfgrmin}, or stress ratio goes over
+    \code{sratmax} (but is still \eqn{< 1}).}
+
   \item{\dots}{Other parameters to the functions (ignored).}
 }
 



More information about the Vegan-commits mailing list