[Robast-commits] r258 - in pkg/RobLoxBioC: R man

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Tue Mar 3 08:52:34 CET 2009


Author: stamats
Date: 2009-03-03 08:52:34 +0100 (Tue, 03 Mar 2009)
New Revision: 258

Added:
   pkg/RobLoxBioC/R/AllGeneric.R
   pkg/RobLoxBioC/man/robloxbioc.Rd
Modified:
   pkg/RobLoxBioC/R/robloxAffyBatch.R
   pkg/RobLoxBioC/R/robloxMatrix.R
Log:
first version which installs and checks without any errors or warnings

Added: pkg/RobLoxBioC/R/AllGeneric.R
===================================================================
--- pkg/RobLoxBioC/R/AllGeneric.R	                        (rev 0)
+++ pkg/RobLoxBioC/R/AllGeneric.R	2009-03-03 07:52:34 UTC (rev 258)
@@ -0,0 +1,9 @@
+############# preparations ################
+.onLoad <- function(lib, pkg) {
+    require("methods", character = TRUE, quietly = TRUE)
+}
+
+if(!isGeneric("robloxbioc")){
+    setGeneric("robloxbioc", 
+        function(x, ...) standardGeneric("robloxbioc"))
+}

Modified: pkg/RobLoxBioC/R/robloxAffyBatch.R
===================================================================
--- pkg/RobLoxBioC/R/robloxAffyBatch.R	2009-03-02 14:19:35 UTC (rev 257)
+++ pkg/RobLoxBioC/R/robloxAffyBatch.R	2009-03-03 07:52:34 UTC (rev 258)
@@ -3,7 +3,7 @@
 ###############################################################################
 setMethod("robloxbioc", signature(x = "AffyBatch"),
     function(x, pmcorrect = "roblox", verbose = TRUE,
-            eps, eps.lower = 0, eps.upper = 0.1, steps = 1L, mad0 = 1e-4,
+            eps = NULL, eps.lower = 0, eps.upper = 0.1, steps = 1L, mad0 = 1e-4,
             contrast.tau = 0.03, scale.tau = 10, delta = 2^(-20)) {
         n <- length(x)
         ids <- featureNames(x)
@@ -37,8 +37,8 @@
                 ind <- which(NROW == k)
                 temp <- matrix(do.call(rbind, res[ind]), nrow = k)
                 ind1 <-  as.vector(sapply(seq_len(n)-1, function(x, ind, m){ ind + x*m }, ind = ind, m = m))
-                rob.est1[ind1, 1:2] <- robloxEM(t(temp), eps = eps, eps.lower = eps.lower, k = steps,
-                                                mad0 = mad0)
+                rob.est1[ind1, 1:2] <- robloxbioc(t(temp), eps = eps, eps.lower = eps.lower, eps.upper = eps.upper, 
+                                                  steps = steps, mad0 = mad0)
             }
             sb <- matrix(rob.est1[,1], nrow = m)
             for(k in seq_len(m)){
@@ -71,7 +71,8 @@
             ind <- which(NROW == k)
             temp <- matrix(do.call(rbind, res[ind]), nrow = k)
             ind1 <-  as.vector(sapply(seq_len(n)-1, function(x, ind, m){ ind + x*m }, ind = ind, m = m))
-            rob.est[ind1, 1:2] <- robloxEM(log2(t(temp)), eps = eps, eps.lower = eps.lower, k = steps, mad0 = mad0)
+            rob.est[ind1, 1:2] <- robloxbioc(log2(t(temp)), eps = eps, eps.lower = eps.lower, 
+                                             eps.upper = eps.upper, steps = steps, mad0 = mad0)
         }
         if(verbose) cat(" done.\n")
         exp.mat <- 2^matrix(rob.est[,1], nrow = m)

Modified: pkg/RobLoxBioC/R/robloxMatrix.R
===================================================================
--- pkg/RobLoxBioC/R/robloxMatrix.R	2009-03-02 14:19:35 UTC (rev 257)
+++ pkg/RobLoxBioC/R/robloxMatrix.R	2009-03-03 07:52:34 UTC (rev 258)
@@ -38,26 +38,8 @@
 ## matrix
 ###############################################################################
 setMethod("robloxbioc", signature(x = "matrix"),
-    function(x, eps, eps.lower = 0, eps.upper = 0.1, steps = 1L, mad0 = 1e-4){
-        if(missing(x))
-            stop("'x' is missing with no default")
-        if(is.data.frame(x))
-            x <- data.matrix(x)
-        else
-            x <- as.matrix(x)
-        if(!is.matrix(x))
-            stop("'x' has to be a matrix resp. convertable to a matrix by 'as.matrix'
-                  or 'data.matrix'")
-
-        if(missing(eps) && missing(eps.lower) && missing(eps.upper)){
-            eps.lower <- 0
-            eps.upper <- 0.5
-        }
-        if(missing(eps)){
-            if(!missing(eps.lower) && missing(eps.upper))
-                eps.upper <- 0.5
-            if(missing(eps.lower) && !missing(eps.upper))
-                eps.lower <- 0
+    function(x, eps = NULL, eps.lower = 0, eps.upper = 0.1, steps = 1L, mad0 = 1e-4){
+        if(is.null(eps)){
             if(length(eps.lower) != 1 || length(eps.upper) != 1)
                 stop("'eps.lower' and 'eps.upper' have to be of length 1")
             if(!is.numeric(eps.lower) || !is.numeric(eps.upper) || eps.lower >= eps.upper) 
@@ -65,8 +47,12 @@
             if((eps.lower < 0) || (eps.upper > 0.5))
                 stop("'eps.lower' and 'eps.upper' have to be in [0, 0.5]")
         }else{
-            if(length(eps) != 1)
-                stop("'eps' has to be of length 1")
+            if(length(eps) != 1){
+                warning("'eps' has to be of length 1 => only first element is used")
+                eps <- eps[1]
+            }
+            if(!is.numeric(eps))
+                stop("'eps' has to be a double in (0, 0.5]")
             if(eps == 0)
                 stop("'eps = 0'! => use functions 'mean' and 'sd' for estimation")
             if((eps < 0) || (eps > 0.5))
@@ -76,9 +62,9 @@
             warning("'steps' has to be of length 1 => only first element is used!")
             steps <- steps[1]
         }
-        if(steps < 1){
+        if(steps < 1)
             stop("'steps' has to be some positive integer value")
-        }
+
         steps <- as.integer(steps)
 
         mean <- rowMedians(x, na.rm = TRUE)
@@ -88,7 +74,7 @@
             sd[sd == 0] <- mad0
         }
 
-        if(!missing(eps)){
+        if(!is.null(eps)){
             r <- sqrt(ncol(x))*eps
             if(r > 10){
                 b <- sd*1.618128043

Added: pkg/RobLoxBioC/man/robloxbioc.Rd
===================================================================
--- pkg/RobLoxBioC/man/robloxbioc.Rd	                        (rev 0)
+++ pkg/RobLoxBioC/man/robloxbioc.Rd	2009-03-03 07:52:34 UTC (rev 258)
@@ -0,0 +1,126 @@
+\name{robloxbioc}
+\alias{robloxbioc}
+\alias{robloxbioc-methods}
+\alias{robloxbioc,matrix-method}
+\alias{robloxbioc,AffyBatch-method}
+
+\title{Generic Function for Preprocessing Biological Data}
+\description{
+  Generic function for preprocessing biological data using optimally robust
+  (rmx) estimators; confer Rieder (1994), Kohl (2005), Rieder et al (2008).
+}
+\usage{
+robloxbioc(x, ...)
+
+\S4method{robloxbioc}{matrix}(x, eps = NULL, eps.lower = 0, eps.upper = 0.1, steps = 1L, mad0 = 1e-4)
+
+\S4method{robloxbioc}{AffyBatch}(x, pmcorrect = "roblox", verbose = TRUE,  
+                                 eps = NULL, eps.lower = 0, eps.upper = 0.1, steps = 1L, mad0 = 1e-4,
+                                 contrast.tau = 0.03, scale.tau = 10, delta = 2^(-20))
+}
+\arguments{
+  \item{x}{ biological data. }
+  \item{\dots}{ additional parameters. }
+  \item{eps}{ positive real (0 < \code{eps} <= 0.5): amount of gross errors. 
+        See details below. }
+  \item{eps.lower}{ positive real (0 <= \code{eps.lower} <= \code{eps.upper}): 
+        lower bound for the amount of gross errors. See details below. }
+  \item{eps.upper}{ positive real (\code{eps.lower} <= \code{eps.upper} <= 0.5): 
+        upper bound for the amount of gross errors. See details below. }
+  \item{steps}{ positive integer. k-step is used to compute the optimally robust estimator. }
+  \item{mad0}{ scale estimate used if computed MAD is equal to zero}
+  \item{pmcorrect}{ method used for PM correction; so far only "roblox" and \code{pm.only} 
+    are implemented. The algorithm is comparable to the algorithm of MAS 5.0; confer
+    \code{\link[affy]{pmcorrect.mas}}. }
+  \item{contrast.tau}{ a number denoting the contrast tau parameter; confer the MAS 5.0 
+    PM correction algorithm. }
+  \item{scale.tau}{ a number denoting the scale tau parameter; confer the MAS 5.0 
+    PM correction algorithm. }
+  \item{delta}{ a number denoting the delta parameter; confer the MAS 5.0 
+    PM correction algorithm. }
+  \item{verbose}{ logical: if \code{TRUE}, some messages are printed }
+}
+\details{
+  The optimally-robust resp. the radius-minimax (rmx) estimator for normal location 
+  and scale is used to preprocess biological data. The computation uses a k-step 
+  construction with median and MAD as starting estimators; cf. Rieder (1994) and 
+  Kohl (2005).
+
+  If the amount of gross errors (contamination) is known, it can be 
+  specified by \code{eps}. The radius of the corresponding infinitesimal 
+  contamination neighborhood (infinitesimal version of Tukey's gross error model) 
+  is obtained by multiplying \code{eps} by the square root of the sample size. 
+
+  If the amount of gross errors (contamination) is unknown, which is typically
+  the case, try to find a rough estimate for the amount of gross errors, such that 
+  it lies between \code{eps.lower} and \code{eps.upper}.
+
+  If \code{eps} is missing, the radius-minimax (rmx) estimator in sense of 
+  Rieder et al. (2001, 2008), respectively Section 2.2 of Kohl (2005) is used.
+  
+  The algorithm used for Affymetrix data is similar to MAS 5.0 (cf. Affymetrix (2002)).
+  The main difference is the substitution of the Tukey one-step estimator by our rmx 
+  k-step (k >= 1) estimator.
+}
+\value{ Return value depends on the class of \code{x}. 
+  In case of \code{"matrix"} a matrix with columns "mean" and "sd" is returned.
+  In case of \code{"AffyBatch"} an object of class \code{"ExpressionSet"} is returned. 
+}
+\references{
+  Affymetrix, Inc. (2002). \emph{Statistical Algorithms Description Document}.
+  Affymetrix, Santa Clara.
+
+  Kohl, M. (2005) \emph{Numerical Contributions to the Asymptotic Theory of Robustness}. 
+  Bayreuth: Dissertation.
+
+  Rieder, H. (1994) \emph{Robust Asymptotic Statistics}. New York: Springer.
+
+  Rieder, H., Kohl, M. and Ruckdeschel, P. (2008) The Costs of not Knowing
+  the Radius. Statistical Methods and Applications \emph{17}(1) 13-40.
+
+  Rieder, H., Kohl, M. and Ruckdeschel, P. (2001) The Costs of not Knowing
+  the Radius. Submitted. Appeared as discussion paper Nr. 81. 
+  SFB 373 (Quantification and Simulation of Economic Processes),
+  Humboldt University, Berlin; also available under
+  \url{www.uni-bayreuth.de/departments/math/org/mathe7/RIEDER/pubs/RR.pdf}
+}
+\author{Matthias Kohl \email{Matthias.Kohl at stamats.de}}
+%\note{}
+\seealso{\code{\link[RobLox]{roblox}}, \code{\link[RobLox]{rowRoblox}},
+         \code{\link[affy]{AffyBatch-class}}, 
+         \code{\link[affy]{generateExprVal.method.mas}},
+         \code{\link[Biobase]{ExpressionSet-class}} }
+\examples{
+## similar to rowRoblox of package RobLox
+ind <- rbinom(200, size=1, prob=0.05) 
+X <- matrix(rnorm(200, mean=ind*3, sd=(1-ind) + ind*9), nrow = 2)
+robloxbioc(X)
+robloxbioc(X, steps = 3)
+robloxbioc(X, eps = 0.05)
+robloxbioc(X, eps = 0.05, steps = 3)
+
+## the function is designed for large scale problems
+X <- matrix(rnorm(50000*20, mean = 1), nrow = 50000)
+system.time(robloxbioc(X))
+
+## using Affymetrix-Data
+## confer example to generateExprVal.method.mas
+data(SpikeIn)
+probes <- pm(SpikeIn) 
+mas <- generateExprVal.method.mas(probes)
+rl <- 2^robloxbioc(log2(t(probes)))
+concentrations <- as.numeric(sampleNames(SpikeIn))
+plot(concentrations, mas$exprs, log="xy", ylim=c(50,10000), type="b",
+     ylab = "expression measures")
+points(concentrations, rl[,1], pch = 20, col="orange", type="b")
+legend("topleft", c("MAS", "roblox"), pch = c(1, 20))
+
+if(require(affydata)){
+    data(Dilution)
+    eset <- robloxbioc(Dilution)
+}
+}
+\concept{normal location and scale}
+\concept{infinitesimal robustness}
+\concept{radius-minimax estimator}
+\keyword{robust}



More information about the Robast-commits mailing list