[med-svn] [r-bioc-genefilter] 12/14: New upstream version 1.58.1

Andreas Tille tille at debian.org
Mon Oct 2 13:13:39 UTC 2017


This is an automated email from the git hooks/post-receive script.

tille pushed a commit to branch master
in repository r-bioc-genefilter.

commit 4aba7da43212b355e28fed86a88902ee44703b5f
Author: Andreas Tille <tille at debian.org>
Date:   Mon Oct 2 15:07:40 2017 +0200

    New upstream version 1.58.1
---
 .Rinstignore                              |    1 +
 DESCRIPTION                               |   23 +
 NAMESPACE                                 |  129 ++
 NEWS                                      |    7 +
 R/AllClasses.R                            |   35 +
 R/AllGenerics.R                           |   43 +
 R/all.R                                   |  183 +++
 R/dist2.R                                 |   21 +
 R/eSetFilter.R                            |  320 +++++
 R/fastT.R                                 |   32 +
 R/filter_volcano.R                        |   57 +
 R/filtered_p.R                            |   37 +
 R/genefinder.R                            |  143 +++
 R/half.range.mode.R                       |   51 +
 R/kappa_p.R                               |   10 +
 R/nsFilter.R                              |  264 ++++
 R/rejection_plot.R                        |   79 ++
 R/rowROC-accessors.R                      |  153 +++
 R/rowSds.R                                |    9 +
 R/rowpAUCs-methods.R                      |   86 ++
 R/rowttests-methods.R                     |  215 ++++
 R/shorth.R                                |   48 +
 R/zzz.R                                   |    9 +
 build/vignette.rds                        |  Bin 0 -> 480 bytes
 data/tdata.R                              | 1952 +++++++++++++++++++++++++++++
 debian/README.test                        |    8 -
 debian/changelog                          |   49 -
 debian/compat                             |    1 -
 debian/control                            |   26 -
 debian/copyright                          |  107 --
 debian/examples                           |    1 -
 debian/rules                              |    4 -
 debian/source/format                      |    1 -
 debian/tests/control                      |    3 -
 debian/tests/run-unit-test                |   18 -
 debian/watch                              |    3 -
 docs/Cluster.pdf                          |  Bin 0 -> 370 bytes
 docs/gcluster.tex                         |   30 +
 docs/gfilter.tex                          |  252 ++++
 inst/doc/howtogenefilter.R                |  107 ++
 inst/doc/howtogenefilter.Rnw              |  212 ++++
 inst/doc/howtogenefilter.pdf              |  Bin 0 -> 115979 bytes
 inst/doc/howtogenefinder.R                |   28 +
 inst/doc/howtogenefinder.Rnw              |  111 ++
 inst/doc/howtogenefinder.pdf              |  Bin 0 -> 153021 bytes
 inst/doc/independent_filtering.R          |  152 +++
 inst/doc/independent_filtering.Rnw        |  468 +++++++
 inst/doc/independent_filtering.pdf        |  Bin 0 -> 623647 bytes
 inst/doc/independent_filtering_plots.R    |   79 ++
 inst/doc/independent_filtering_plots.Rnw  |  238 ++++
 inst/doc/independent_filtering_plots.pdf  |  Bin 0 -> 441792 bytes
 inst/wFun/Anova.xml                       |   30 +
 inst/wFun/coxfilter.xml                   |   30 +
 inst/wFun/cv.xml                          |   30 +
 inst/wFun/gapFilter.xml                   |   46 +
 inst/wFun/kOverA.xml                      |   30 +
 inst/wFun/maxA.xml                        |   22 +
 inst/wFun/pOverA.xml                      |   30 +
 inst/wFun/ttest.xml                       |   30 +
 man/Anova.Rd                              |   44 +
 man/coxfilter.Rd                          |   38 +
 man/cv.Rd                                 |   37 +
 man/dist2.Rd                              |   67 +
 man/eSetFilter.Rd                         |   58 +
 man/filter_volcano.Rd                     |   81 ++
 man/filtered_p.Rd                         |   87 ++
 man/filterfun.Rd                          |   37 +
 man/findLargest.Rd                        |   45 +
 man/gapFilter.Rd                          |   51 +
 man/genefilter.Rd                         |   54 +
 man/genefinder.Rd                         |   98 ++
 man/genescale.Rd                          |   42 +
 man/half.range.mode.Rd                    |  105 ++
 man/kOverA.Rd                             |   31 +
 man/kappa_p.Rd                            |   42 +
 man/maxA.Rd                               |   33 +
 man/nsFilter.Rd                           |  206 +++
 man/pOverA.Rd                             |   39 +
 man/rejection_plot.Rd                     |  111 ++
 man/rowFtests.Rd                          |  188 +++
 man/rowROC-class.Rd                       |  103 ++
 man/rowSds.Rd                             |   37 +
 man/rowpAUCs.Rd                           |  133 ++
 man/shorth.Rd                             |   75 ++
 man/tdata.Rd                              |   22 +
 man/ttest.Rd                              |   53 +
 src/genefilter.h                          |    9 +
 src/half_range_mode.cpp                   |  125 ++
 src/init.c                                |   15 +
 src/nd.c                                  |  346 +++++
 src/pAUC.c                                |  179 +++
 src/rowPAUCs.c                            |  225 ++++
 src/rowttests.c                           |  218 ++++
 src/ttest.f                               |   64 +
 vignettes/howtogenefilter.Rnw             |  212 ++++
 vignettes/howtogenefinder.Rnw             |  111 ++
 vignettes/independent_filtering.Rnw       |  468 +++++++
 vignettes/independent_filtering_plots.Rnw |  238 ++++
 vignettes/library.bib                     |  172 +++
 99 files changed, 10131 insertions(+), 221 deletions(-)

diff --git a/.Rinstignore b/.Rinstignore
new file mode 100644
index 0000000..1b7a1b9
--- /dev/null
+++ b/.Rinstignore
@@ -0,0 +1 @@
+doc/whbiocvignette.sty
diff --git a/DESCRIPTION b/DESCRIPTION
new file mode 100644
index 0000000..e75b9ba
--- /dev/null
+++ b/DESCRIPTION
@@ -0,0 +1,23 @@
+Package: genefilter
+Title: genefilter: methods for filtering genes from high-throughput
+        experiments
+Version: 1.58.1
+Author: R. Gentleman, V. Carey, W. Huber, F. Hahne
+Description: Some basic functions for filtering genes
+Maintainer: Bioconductor Package Maintainer
+ <maintainer at bioconductor.org>
+Suggests: class, hgu95av2.db, tkWidgets, ALL, ROC, DESeq, pasilla,
+        BiocStyle, knitr
+Imports: S4Vectors (>= 0.9.42), AnnotationDbi, annotate, Biobase,
+        graphics, methods, stats, survival
+License: Artistic-2.0
+LazyLoad: yes
+LazyData: yes
+Collate: AllClasses.R AllGenerics.R all.R dist2.R eSetFilter.R fastT.R
+        filter_volcano.R filtered_p.R genefinder.R half.range.mode.R
+        kappa_p.R nsFilter.R rejection_plot.R rowROC-accessors.R
+        rowSds.R rowpAUCs-methods.R rowttests-methods.R shorth.R zzz.R
+biocViews: Microarray
+VignetteBuilder: knitr
+NeedsCompilation: yes
+Packaged: 2017-05-05 22:16:55 UTC; biocbuild
diff --git a/NAMESPACE b/NAMESPACE
new file mode 100644
index 0000000..51ec645
--- /dev/null
+++ b/NAMESPACE
@@ -0,0 +1,129 @@
+useDynLib(genefilter)
+
+importClassesFrom(Biobase,
+                  ExpressionSet)
+
+importClassesFrom(methods,
+                  ANY,
+                  character,
+                  factor,
+                  matrix,
+                  missing,
+                  numeric,
+                  vector)
+
+importMethodsFrom(AnnotationDbi,
+                  as.list,
+                  colnames,
+                  get,
+                  mget,
+                  ncol,
+                  nrow,
+                  sample)
+
+importMethodsFrom(Biobase,
+                  annotation,
+                  exprs,
+                  featureNames,
+                  pData,
+                  rowQ,
+                  varLabels)
+
+importMethodsFrom(methods,
+                  "body<-",
+                  show)
+
+importFrom(S4Vectors,
+           rowSums,
+           colSums,
+           rowMeans,
+           colMeans)
+
+importFrom(Biobase,
+           addVigs2WinMenu,
+           subListExtract)
+
+importFrom(annotate,
+           getAnnMap)
+
+importFrom(graphics,
+           abline,
+           lines,
+           par,
+           plot,
+           points,
+           polygon,
+           rect,
+           strheight,
+           strwidth,
+           text)
+
+importFrom(methods,
+           is,
+           new)
+
+importFrom(stats,
+           IQR,
+           anova,
+           lm,
+           pchisq,
+           pf,
+           pt,
+           quantile,
+           sd,
+           t.test)
+
+importFrom(survival,
+           coxph)
+
+export(Anova, 
+       coxfilter,
+       cv, 
+       eSetFilter, 
+       varFilter, 
+       featureFilter,
+       fastT, 
+       ttest, 
+       shorth, 
+       half.range.mode,
+       rowttests, 
+       colttests, 
+       rowFtests, 
+       colFtests,
+       rowSds, 
+       rowVars, 
+       dist2,
+       filterfun, 
+       findLargest, 
+       gapFilter, 
+       genefilter, 
+       genescale, 
+       getFilterNames,
+       getFuncDesc, 
+       getRdAsText, 
+       isESet, 
+       kOverA, 
+       maxA, 
+       pOverA,
+       parseArgs, 
+       parseDesc, 
+       setESetArgs, 
+       showESet,
+       kappa_t, kappa_p,
+       filtered_p, filtered_R,
+       rejection_plot,
+       filter_volcano) 
+
+exportClasses(rowROC)
+
+exportMethods(genefinder, 
+	      show, 
+	      plot, 
+	      "[", 
+	      sens, 
+	      spec,
+              area, 
+	      pAUC, 
+	      AUC, 
+	      rowpAUCs, 
+	      nsFilter)
diff --git a/NEWS b/NEWS
new file mode 100644
index 0000000..4943e01
--- /dev/null
+++ b/NEWS
@@ -0,0 +1,7 @@
+CHANGES IN VERSION 1.54.0
+------------------------
+
+DEPRECATED AND DEFUNCT
+
+    o remove deprecated anyNA(); contradicted base::anyNA
+    o remove deprecated allNA()
diff --git a/R/AllClasses.R b/R/AllClasses.R
new file mode 100644
index 0000000..a53a21f
--- /dev/null
+++ b/R/AllClasses.R
@@ -0,0 +1,35 @@
+## Classes for package genefilter
+
+## ==========================================================================
+## class rowROC: objects model result of call to function rowpAUCs,
+##               pAUC or AUC
+## - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
+setClass("rowROC",
+         representation(data = "matrix",
+                        ranks = "matrix",
+                        sens = "matrix",
+                        spec = "matrix",
+                        pAUC = "numeric",
+                        AUC = "numeric",
+                        factor = "factor",
+                        cutpoints = "matrix",
+                        caseNames = "character",
+                        p = "numeric"),
+         validity=function(object){
+           if(any(dim(object at sens) != dim(object at spec)))
+             return("\n'sens' and 'spec' must be matrices with equal dimensions")
+           if(length(object at pAUC) != nrow(object at sens))
+             return("\n'pAUC' must be numeric of length equal to nrow(sens)")
+           if(length(object at factor)!=ncol(object at data) ||
+              length(levels(object at factor))!=2)
+             return("'factor' must be factor object with two levels and length = ncol(data)")
+           if(length(object at pAUC) != length(object at AUC))
+             return("'pAUC' and 'AUC' must be numeric vectors of equal length")
+           if(nrow(object at cutpoints) != length(object at pAUC))
+             return("'cutpoints' must be matrix with nrow=length(pAUC)")
+           if(length(object at caseNames)!=2)
+             return("'caseNames' must be character vector of length 2")
+           return(TRUE)
+         }
+         )
+## ==========================================================================
diff --git a/R/AllGenerics.R b/R/AllGenerics.R
new file mode 100644
index 0000000..11a5a3b
--- /dev/null
+++ b/R/AllGenerics.R
@@ -0,0 +1,43 @@
+## Generic functions for package genefilter
+
+setGeneric("rowFtests", function(x, fac, var.equal=TRUE)
+           standardGeneric("rowFtests"))
+setGeneric("colFtests", function(x, fac, var.equal=TRUE)
+           standardGeneric("colFtests"))
+setGeneric("rowttests", function(x, fac, tstatOnly=FALSE)
+           standardGeneric("rowttests"))
+setGeneric("colttests", function(x, fac, tstatOnly=FALSE)
+           standardGeneric("colttests"))
+
+
+setGeneric("genefinder", function(X, ilist, numResults=25, scale="none",
+    weights, method="euclidean" )
+    standardGeneric("genefinder"))
+
+
+setGeneric("pAUC", function(object, p, flip=TRUE) standardGeneric("pAUC"))
+
+setGeneric("AUC", function(object) standardGeneric("AUC"))
+
+setGeneric("sens", function(object) standardGeneric("sens"))
+
+setGeneric("spec", function(object) standardGeneric("spec"))
+
+setGeneric("area", function(object, total=FALSE) standardGeneric("area"))
+
+setGeneric("rowpAUCs", function(x, fac, p=0.1, flip=TRUE, caseNames=c("1", "2"))
+           standardGeneric("rowpAUCs"))
+
+setGeneric("nsFilter", signature="eset",
+           function(eset,
+                    require.entrez=TRUE,
+                    require.GOBP=FALSE,
+                    require.GOCC=FALSE,
+                    require.GOMF=FALSE,
+                    require.CytoBand=FALSE,
+                    remove.dupEntrez=TRUE,
+                    var.func=IQR, var.cutoff=0.5, var.filter=TRUE,
+                    filterByQuantile=TRUE,
+                    feature.exclude="^AFFX", ...)
+           standardGeneric("nsFilter"))
+
diff --git a/R/all.R b/R/all.R
new file mode 100644
index 0000000..618f854
--- /dev/null
+++ b/R/all.R
@@ -0,0 +1,183 @@
+#copyright 2001 R. Gentleman
+
+#FILTER FUNCTIONS -- some trivial changes
+
+kOverA <- function(k, A=100, na.rm = TRUE) {
+  function(x) {
+      if(na.rm)
+	x <- x[!is.na(x)]
+      sum( x > A ) >= k
+  }
+}
+
+maxA <- function(A=75, na.rm=TRUE) {
+    function(x) {max(x, na.rm=na.rm) >= A }
+}
+
+
+pOverA <-  function(p=0.05, A=100, na.rm = TRUE) {
+  function(x) {
+      if(na.rm)
+	 x<-x[!is.na(x)]
+      sum( x > A )/length(x) >= p
+  }
+}
+
+
+cv <- function(a=1, b=Inf, na.rm=TRUE) {
+    function(x) {
+        	sdx <- sd(x, na.rm=na.rm)
+        if(is.na(sdx) || sdx == 0 ) return(FALSE)
+	val <- sdx/abs(mean(x, na.rm=na.rm))
+        if(val < a ) return(FALSE)
+        if(val > b ) return(FALSE)
+        return(TRUE)
+            }
+}
+
+Anova <- function(cov, p=0.05, na.rm=TRUE)
+{
+    function(x) {
+        if( na.rm ) {
+            drop <- is.na(x)
+            x <- x[!drop]
+            cov <- cov[!drop]
+        }
+        m1 <- lm(x~cov)
+        m2 <- lm(x~1)
+        av <- anova(m2,m1)
+        fstat <- av[["Pr(>F)"]][2]
+        if( fstat < p )
+            return(TRUE)
+        return(FALSE)
+    }
+}
+
+coxfilter <- function(surt, cens, p) {
+   autoload("coxph", "survival")
+   function(x) {
+       srvd <- try(coxph(Surv(surt,cens)~x))
+       if( inherits(srvd, "try-error") )
+           return(FALSE)
+       ltest <- -2*(srvd$loglik[1] - srvd$loglik[2])
+       pv <- 1 - pchisq(ltest, 1)
+       if( pv < p )
+           return(TRUE)
+       return(FALSE)
+   }
+}
+
+ttest <- function(m, p=0.05, na.rm=TRUE) {
+    if( length(m) == 1)
+        function(x) {
+            n <- length(x)
+            if( m>n ) stop("m is larger than the number of samples")
+            sub1 <- x[1:m]
+            sub2 <- x[(m+1):n]
+            if(na.rm) {
+                drop <- is.na(x)
+                sub1 <- sub1[!drop[1:m]]
+                sub2 <- sub2[!drop[(m+1):n]]
+            }
+            t.test(sub1, sub2 )$p.value < p
+        }
+    else
+        function(x) {
+            if(na.rm) {
+                drop <- is.na(x) | is.na(m)
+                x<- x[!drop]
+                m<- m[!drop]
+            }
+            t.test(x~m)$p.value < p
+        }
+  }
+
+
+##a filter based on gaps
+
+gapFilter <- function(Gap, IQR, Prop, na.rm=TRUE, neg.rm=TRUE) {
+  function(x) {
+     if(na.rm) x <- x[!is.na(x)]
+     if(neg.rm) x <- x[x>0]
+     lenx <- length(x)
+     if( lenx < 4 || lenx < Prop+1 )
+       return(FALSE)
+     srtd <- sort(x)
+     lq <- lenx*.25
+     uq <- lenx*.75
+     if( (srtd[uq] - srtd[lq]) > IQR )
+        return(TRUE)
+     if(Prop < 1)
+        bot <- lenx*Prop
+     else
+        bot <- Prop
+     top <- lenx - bot
+     lag1 <- srtd[2:lenx]-srtd[1:(lenx-1)]
+     if( max(lag1[bot:top]) > Gap )
+       return(TRUE)
+    return(FALSE)
+  }
+}
+
+
+# Apply type functions
+
+
+genefilter <- function(expr, flist)
+    {
+     if(is(expr, "ExpressionSet"))
+       expr <- exprs(expr)
+     apply(expr, 1, flist)
+}
+
+filterfun <- function(...) {
+     flist <- list(...)
+ #let the user supply a list
+     if( length(flist) == 1 && is.list(flist[[1]]) )
+         flist <- flist[[1]]
+     f <- function( x ) {
+         for( fun in flist ) {
+             fval <- fun(x)
+             if( is.na(fval) || ! fval )
+                 return(FALSE)
+         }
+             return(TRUE)
+     }
+     class(f) <- "filterfun"
+     return(f)
+ }
+
+.findDBMeta <- function(chip, item) {
+    connfunc <- getAnnMap("_dbconn", chip)
+    dbmeta(connfunc(), item)
+}
+
+.isOrgSchema <- function(chip){
+    schema <- .findDBMeta(chip, "DBSCHEMA")
+    length(grep("CHIP", schema)) == 0
+}
+
+.findCentralMap<- function(chip){
+    centID <- .findDBMeta(chip, "CENTRALID")
+    if(!.isOrgSchema(chip) && centID == "TAIR") {
+        "ACCNUM" ## a peculiar exception with historical causes
+    } else {
+        centID   ## should cover EVERYTHING else
+    }
+}
+
+
+findLargest = function(gN, testStat, data="hgu133plus2") {
+    lls = if(.isOrgSchema(data)){
+        gN ##not a chip package so try the IDs presented.
+    } else {
+        map = .findCentralMap(data)
+        unlist(mget(gN, getAnnMap(map, data)), use.names=FALSE)
+    }
+    if(length(testStat) != length(gN) )
+        stop("testStat and gN must be the same length")
+    if( is.null(names(testStat)) )
+        names(testStat) = gN
+    tSsp = split.default(testStat, lls)
+    sapply(tSsp, function(x) names(which.max(x)))
+}
diff --git a/R/dist2.R b/R/dist2.R
new file mode 100644
index 0000000..1194d8d
--- /dev/null
+++ b/R/dist2.R
@@ -0,0 +1,21 @@
+dist2 = function (x,
+                  fun = function(a, b) mean(abs(a - b), na.rm = TRUE),
+                  diagonal = 0) {
+
+  if (!(is.numeric(diagonal) && (length(diagonal) == 1)))
+    stop("'diagonal' must be a numeric scalar.")
+
+  if (missing(fun)) {
+    res = apply(x, 2, function(w) colMeans(abs(x-w), na.rm=TRUE))
+  } else {
+    res = matrix(diagonal, ncol = ncol(x), nrow = ncol(x))
+    if (ncol(x) >= 2) {
+      for (j in 2:ncol(x))
+        for (i in 1:(j - 1))
+          res[i, j] = res[j, i] = fun(x[, i], x[, j])
+    } # if
+  } # else
+
+  colnames(res) = rownames(res) = colnames(x)
+  return(res)
+}
diff --git a/R/eSetFilter.R b/R/eSetFilter.R
new file mode 100644
index 0000000..08c282f
--- /dev/null
+++ b/R/eSetFilter.R
@@ -0,0 +1,320 @@
+# This widget allows users to pick filters in the order they are going
+# to be used to filer genes and set the parameters for
+# each filter.
+#
+# Copyright 2003, J. Zhang. All rights reserved.
+#
+
+eSetFilter <- function(eSet){
+    require("tkWidgets", character.only = TRUE) ||
+    stop(paste("eSetFilter requires the tkWidgets",
+                                "package. Please have it installed"))
+
+    descList <- getFuncDesc()
+
+    buildGUI <- function(){
+        END <<- FALSE
+
+        selectedNames <- NULL
+        filterWithArgs <- list()
+
+        setFilter <- function(){
+            currentFilter <- as.character(tkget(filters,
+                                             (tkcurselection(filters))))
+            args <- setESetArgs(currentFilter)
+            if(!is.null(args)){
+                expression <- paste(currentFilter, "(",
+                    paste(names(args), args, sep = "=", collapse = ","),
+                    ")", sep = "")
+                filterWithArgs[[currentFilter]] <<- eval(parse(text =
+                                                               expression))
+                selectedNames <<- unique(c(selectedNames, currentFilter))
+                writeList(pickedF, selectedNames)
+                tkconfigure(selectBut, state = "disabled")
+            }
+        }
+        cancel <- function(){
+            tkdestroy(base)
+        }
+        finish <- function(){
+            END <<- TRUE
+            tkdestroy(base)
+        }
+        viewFilter <- function(){
+            currentFilter <- as.character(tkget(filters,
+                                             (tkcurselection(filters))))
+            tkconfigure(description, state = "normal")
+            writeText(description, descList[[currentFilter]])
+            tkconfigure(description, state = "disabled")
+            tkconfigure(selectBut, state = "normal")
+        }
+        pickedSel <- function(){
+            tkconfigure(remBut, state = "normal")
+        }
+        remove <- function(){
+             filter <- as.character(tkget(pickedF,
+                                             (tkcurselection(pickedF))))
+             selectedNames <<- setdiff(selectedNames, filter)
+             writeList(pickedF, selectedNames)
+             tkconfigure(remBut, state = "disabled")
+
+        }
+
+        base <- tktoplevel()
+        tktitle(base) <- "BioC Filter Master"
+        # Pack the top frame with a brief description
+        introText <- tktext(base, width = 30, height = 4, wrap = "word")
+        text <- paste("Bioconductor's gene filtering functons are",
+                      "listed below. Select one from the list to view the",
+                      "description and formal arguments for each filter.",
+                      "A filter can be selected to the set of filters",
+                      "for filtering genes using the select button.")
+        writeText(introText, text)
+        tkconfigure(introText, state = "disabled")
+        tkpack(introText, expand = FALSE, fill  = "both", padx = 5)
+        # Pack a frame with a list box for selected filters and
+        # buttons manipulate the selected filters
+        infoFrame <- tkframe(base)
+        filterFrame <- tkframe(infoFrame)
+        tkpack(tklabel(filterFrame, text = "Filters"), expand = FALSE,
+               fill = "x")
+        listFrame <- tkframe(filterFrame)
+        filters <- makeViewer(listFrame, vHeight = 10, vWidth = 12,
+                                vScroll = TRUE, hScroll = TRUE,
+                                what = "list")
+        tkbind(filters, "<B1-ButtonRelease>", viewFilter)
+        tkbind(filters, "<Double-Button-1>", setFilter)
+        writeList(filters, getFilterNames())
+        tkpack(listFrame, expand = TRUE, fill = "both")
+        selectBut <- tkbutton(filterFrame, text = "Select",
+                              command = setFilter, state = "disabled")
+        tkpack(selectBut, expand = FALSE, fill = "x")
+        tkpack(filterFrame, side = "left", expand = FALSE, fill = "both")
+        descFrame <- tkframe(infoFrame)
+        tkpack(tklabel(descFrame, text = "Description"), expand = FALSE,
+               fill = "x")
+        dListFrame <- tkframe(descFrame)
+        description <- makeViewer(dListFrame, vHeight = 10, vWidth = 30,
+                                vScroll = TRUE, hScroll = TRUE,
+                                what = "text")
+        tkconfigure(description, wrap = "word", state = "disabled")
+        tkpack(dListFrame, expand = TRUE, fill = "both")
+        tkpack(descFrame, side = "left", expand = TRUE, fill = "both")
+        selFrame <- tkframe(infoFrame)
+        tkpack(tklabel(selFrame, text = "Selected"),
+               expand = FALSE, fill = "x")
+        selFFrame <- tkframe(selFrame)
+        pickedF <- makeViewer(selFFrame, vHeight = 10, vWidth = 12,
+                                vScroll = TRUE, hScroll = TRUE,
+                                what = "list")
+        tkbind(pickedF, "<B1-ButtonRelease>", pickedSel)
+        tkbind(pickedF, "<Double-Button-1>", remove)
+        tkpack(selFFrame, expand = TRUE, fill = "both")
+        remBut <- tkbutton(selFrame, text = "Remove", command = remove,
+                           state = "disabled")
+        tkpack(remBut, expand = FALSE, fill = "x")
+        tkpack(selFrame, expand = FALSE, fill = "both")
+        tkpack(infoFrame, expand = TRUE, fill = "both", padx = 5)
+        # Pack the bottom frame with cancel and finish buttons
+        endFrame <- tkframe(base)
+        cancelBut <- tkbutton(endFrame, width = 8, text = "Cancel",
+                           command = cancel)
+        tkpack(cancelBut, side = "left", expand = TRUE, fill = "x",
+               padx = 10)
+        finishBut <- tkbutton(endFrame, width = 8, text = "finish",
+                           command = finish)
+        tkpack(finishBut, side = "left", expand = TRUE, fill = "x",
+               padx = 10)
+        tkpack(endFrame, expand = FALSE, fill = "x", pady = 5)
+
+        showESet(eSet)
+        tkwait.window(base)
+
+        if(END){
+            tempList <- list()
+            for(i in  selectedNames){
+                tempList[[i]] <- filterWithArgs[[i]]
+            }
+            return(tempList)
+        }else{
+            return(NULL)
+        }
+    }
+
+    filters <- buildGUI()
+    if(!is.null(filters)){
+        filters <- filterfun(unlist(filters))
+        return(genefilter(exprs(eSet), filters))
+    }else{
+        return(NULL)
+    }
+}
+
+getFilterNames <- function(){
+    return(sort(c("Anova", "coxfilter", "cv", "gapFilter", "kOverA",
+    "maxA", "pOverA", "ttest")))
+}
+
+getFuncDesc <- function(lib = "genefilter", funcs = getFilterNames()){
+    descList <- list()
+
+    lines <- getRdAsText(lib)
+    for(i in funcs){
+        rd <- lines[grep(paste("\\\\name\\{", i, "\\}", sep = ""), lines)]
+        desc <- parseDesc(rd)
+        args <- parseArgs(rd)
+        if(length(args) > 0){
+            temp <- "\n\nArguments:"
+            for(j in names(args)){
+                temp <- c(temp, paste(j, "-", args[[j]]))
+            }
+            args <- paste(temp, sep = "", collapse = "\n")
+        }
+        descList[[i]] <- paste(desc, args, sep = "", collapse = "")
+    }
+    return(descList)
+}
+
+getRdAsText <- function(lib){
+    fileName <- gzfile(file.path(.path.package(lib), "man",
+                          paste(lib, ".Rd.gz", sep = "")), open = "r")
+    lines <- readLines(fileName)
+
+    lines <- paste(lines, sep = "", collapse = " ")
+    lines <- unlist(strsplit(lines, "\\\\eof"))
+    return(lines)
+}
+
+parseDesc <- function(text){
+    descRExp <- ".*\\\\description\\{(.*)\\}.*\\\\usage\\{.*"
+    text <- gsub(descRExp, "\\1", text)
+    text <- gsub("(\\\\[a-zA-Z]*\\{|\\})", "", text)
+    return(text)
+}
+
+parseArgs <- function(text){
+    argsList <- list()
+    text <- gsub(".*\\\\arguments\\{(.*)\\}.*\\\\details\\{.*", "\\1", text)
+    text <- gsub(".*\\\\arguments\\{(.*)\\}.*\\\\value\\{.*", "\\1", text)
+    text <- unlist(strsplit(text, "\\\\item\\{"))
+    text <- gsub("(\\\\[a-zA-Z]*\\{|\\})", "", text)
+    for(i in text){
+        i <- unlist(strsplit(i, "\\{"))
+        if(length(i) > 1){
+            argsList[[i[1]]] <- i[2]
+        }
+    }
+    return(argsList)
+}
+
+showESet <- function(eSet){
+    end <- function(){
+        tkdestroy(base)
+    }
+    if(!is(eSet, "eSet")){
+        stop()
+    }
+    colNRow <- dim(exprs(eSet))
+    vl <- varLabels(eSet)
+    text <- c(paste("Genes: ", colNRow[1]),
+              paste("Samples: ", colNRow[2], sep = ""),
+              "Variable labels:",
+              paste(names(vl), ": ", vl[1:length(vl)], sep = ""))
+
+    base <- tktoplevel()
+    tktitle(base) <- "BioC ExpressionSet viewer"
+    dataDescFrame <- tkframe(base)
+    data <- makeViewer(dataDescFrame, vHeight = 10, vWidth = 25,
+                       vScroll = TRUE, hScroll = TRUE,
+                       what = "list")
+    writeList(data, text)
+    tkpack(dataDescFrame, expand = TRUE, fill = "both")
+    endBut <- tkbutton(base, text = "Finish", command = end)
+    tkpack(endBut, expand = FALSE, fill = "x", pady = 5)
+}
+
+setESetArgs <- function(filter){
+    on.exit(tkdestroy(base))
+
+    cancel <- function(){
+        tkdestroy(base)
+    }
+    end <- function(){
+        END <<- TRUE
+        tkdestroy(base)
+    }
+    END <- FALSE
+    argsVar <- list()
+    desc <- list()
+    entries <- list()
+    ftFun <- list()
+
+    args <- getRdAsText("genefilter")
+    args <- args[grep(paste("\\\\name\\{", filter, "\\}", sep = ""), args)]
+    args <- parseArgs(args)
+    argValues <- formals(filter)
+
+    base <- tktoplevel()
+    tktitle(base) <- "BioC Filter Argument input"
+
+    tkgrid(tklabel(base, text = "Arguments"),
+           tklabel(base, text = "Descriptions"),
+           tklabel(base, text = "Values"))
+    for(i in names(args)){
+        argsVar[[i]] <- tclVar(as.character(argValues[[i]]))
+        tempFrame <- tkframe(base)
+        desc[[i]] <- makeViewer(tempFrame, vHeight = 3, vWidth = 55,
+                                vScroll = FALSE, hScroll = FALSE,
+                                what = "text")
+        writeText(desc[[i]], args[[i]])
+        tkconfigure(desc[[i]], wrap = "word", state = "disabled")
+        entries[[i]] <- tkentry(base, textvariable = argsVar[[i]],
+                                    width = 10)
+        tkgrid(tklabel(base, text = i), tempFrame, entries[[i]])
+        if(any(as.character(argValues[[i]]) == c("FALSE", "TRUE"))){
+             ftFun[[i]] <- function(){}
+             body <- list(as.name("{"),
+                          substitute(eval(if(tclvalue(argsVar[[j]]) ==
+                                                      "TRUE"){
+                              writeList(entries[[j]], "FALSE")}else{
+                                  writeList(entries[[j]], "TRUE")}),
+                                     list(j = i)))
+             body(ftFun[[i]]) <- as.call(body)
+             tkbind(entries[[i]],"<B1-ButtonRelease>", ftFun[[i]])
+        }
+        tkgrid.configure(tempFrame, sticky = "eswn")
+    }
+
+    butFrame <- tkframe(base)
+    canBut <- tkbutton(butFrame, text = "cancel", width = 8,
+                       command = cancel)
+    endBut <- tkbutton(butFrame, text = "Finish", width = 8,
+                       comman = end)
+    tkpack(canBut, side = "left", expand = FALSE, fill = "x")
+    tkpack(endBut, side = "left", expand = FALSE, fill = "x")
+    tkgrid(butFrame, columnspan = 3)
+
+    tkwait.window(base)
+    if(END){
+        for(i in names(argValues)){
+            argValues[[i]] <- tkWidgets:::formatArg(tclvalue(argsVar[[i]]))
+        }
+        return(argValues)
+    }else{
+        return(NULL)
+    }
+}
+
+isESet <- function(eSet){
+    if(missing(eSet) ||
+       (!is(eSet, "ExpressionSet"))) {
+        tkmessageBox(title = "Input Error",
+                     message = paste("filterMaster has to take",
+                     "an object of class ExpressionSet"),
+                     icon = "warning",
+                     type = "ok")
+        return(FALSE)
+    }else{
+        return(TRUE)
+    }
+}
diff --git a/R/fastT.R b/R/fastT.R
new file mode 100644
index 0000000..58be86d
--- /dev/null
+++ b/R/fastT.R
@@ -0,0 +1,32 @@
+
+##FIXME: this could replace the code further below at some point,
+## but only when it has the var.equal option
+##--------------------------------------------------
+## fastT
+##--------------------------------------------------
+#fastT = function(x, ig1, ig2, var.equal=TRUE) {
+#  fac      = rep(NA, ncol(x))
+#  fac[ig1] = 0
+#  fac[ig2] = 1
+#  .Call("rowcolttests", x, as.integer(fac), as.integer(2),
+#               as.integer(0), PACKAGE="genefilter")
+#}
+
+
+
+fastT = function(x, ig1, ig2, var.equal=TRUE) {
+    ng1=length(ig1)
+    ng2 = length(ig2)
+    if( ncol(x) != ng1+ng2)
+        stop("wrong sets of columns")
+
+    outd = x[,c(ig1, ig2),drop=FALSE]
+    nr = nrow(outd)
+    z = rep(0, nr)
+    dm = rep(0, nr)
+    Z = .Fortran("fastt", d=as.single(outd), as.integer(nr),
+           as.integer(ng1+ng2), as.integer(ng1), z = as.single(z),
+         dm = as.single(dm), var.equal=as.integer(var.equal),
+         ratio = as.integer(as.integer(0)), PACKAGE="genefilter")
+    return(list(z = Z$z, dm=Z$dm, var.equal=Z$var.equal))
+}
diff --git a/R/filter_volcano.R b/R/filter_volcano.R
new file mode 100644
index 0000000..c211a65
--- /dev/null
+++ b/R/filter_volcano.R
@@ -0,0 +1,57 @@
+filter_volcano <- function(
+                           d, p, S,
+                           n1, n2,
+                           alpha, S_cutoff,
+                           cex = .5, pch = 19,
+                           xlab = expression( paste( log[2], " fold change" ) ),
+                           ylab = expression( paste( "-", log[10], " p" ) ),
+                           cols = c( "grey80", "grey50", "black" ),
+                           ltys = c( 1, 3 ),
+                           use_legend = TRUE,
+                           ...
+                           )
+{
+
+  f <- S < S_cutoff
+  
+  col <- rep( cols[1], length(d) )
+  col[ !f & p >= alpha ] <- cols[2]
+  col[ !f & p < alpha ] <- cols[3]  
+
+  plot(
+       d,
+       -log10( p ),
+       cex = cex,
+       pch = pch,
+       xlab = xlab,
+       ylab = ylab,
+       col = col,
+       ...
+       )
+
+  k_grid <- seq( 0, max( -log10( p ) ), length = 100 )
+  p_grid <- 10^( -k_grid )
+  
+  lines( kappa_p( p_grid, n1, n2 ) * S_cutoff, k_grid, lty = ltys[1] )
+  lines( -1 * kappa_p( p_grid, n1, n2 ) * S_cutoff, k_grid, lty = ltys[1] )
+
+  segments(
+           c( par("usr")[1], kappa_p( alpha, n1, n2 ) * S_cutoff ),
+           -log10( alpha ),
+           c( -kappa_p( alpha, n1, n2 ) * S_cutoff, par("usr")[2] ),
+           -log10( alpha ),
+           lty = ltys[2]
+           )
+
+  if ( use_legend )
+    legend(
+           "topleft",
+           c( "Filtered", "Insig.", "Sig." ),
+           pch = pch,
+           col = cols,
+           inset = .025,
+           bg = "white"
+           )
+
+}
+
diff --git a/R/filtered_p.R b/R/filtered_p.R
new file mode 100644
index 0000000..e4a5253
--- /dev/null
+++ b/R/filtered_p.R
@@ -0,0 +1,37 @@
+filtered_p <- function( filter, test, theta, data, method = "none" ) {
+
+  if ( is.function( filter ) )
+    U1 <- filter( data )
+  else
+    U1 <- filter
+
+  cutoffs <- quantile( U1, theta )
+
+  result <- matrix( NA_real_, length( U1 ), length( cutoffs ) )
+  colnames( result ) <- names( cutoffs )
+  
+  for ( i in 1:length( cutoffs ) ) {    
+    use <- U1 >= cutoffs[i]
+    if( any( use ) ) {
+      if( is.function( test ) )
+        U2 <- test( data[use,] )
+      else
+        U2 <- test[use]
+      result[use,i] <- p.adjust( U2, method )
+    }
+  }
+
+  return( result )
+  
+}
+
+
+
+
+filtered_R <- function( alpha, filter, test, theta, data, method = "none" ) {
+
+  p <- filtered_p( filter, test, theta, data, method )
+
+  return( apply( p, 2, function(x) sum( x < alpha, na.rm = TRUE ) ) )
+
+}
diff --git a/R/genefinder.R b/R/genefinder.R
new file mode 100644
index 0000000..4437c57
--- /dev/null
+++ b/R/genefinder.R
@@ -0,0 +1,143 @@
+# genefinder.R
+#
+# genefinder functions.
+
+
+genescale <- function (m, axis=2, method=c("Z", "R"), na.rm=TRUE) {
+    ##scale by the range
+    RscaleVector <- function(v, na.rm) {
+        mm <- range(v, na.rm=na.rm)
+        (v - mm[1]) / (mm[2] - mm[1])
+    }
+    ##scale using Zscore
+    ZscaleVector <- function(v, na.rm)
+        (v - mean(v, na.rm=na.rm))/sd(v, na.rm=na.rm)
+#
+# scales a matrix using the scaleVector function.
+#
+    which <- match.arg(method)
+    method <- switch(which,
+                     Z = ZscaleVector,
+                     R = RscaleVector)
+    if( is.matrix(m) || is.data.frame(m) ) {
+        rval <- apply (m, axis, method, na.rm=na.rm)
+        if( axis==1 ) return(t(rval))
+        return(rval)
+    }
+    else
+	method(m, na.rm=na.rm)
+}
+
+
+setMethod("genefinder", c("ExpressionSet", "vector", "ANY", "ANY", "ANY",
+          "ANY"),
+          function(X, ilist, numResults, scale, weights,
+                   method) {
+              gN <- featureNames(X)
+              if (is.character(ilist))
+                  ilist <- match(ilist,gN)
+              ans <- genefinder(exprs(X), ilist, numResults, scale, weights,
+                        method=method)
+              names(ans) <- gN[ilist]
+              ans
+      })
+
+setMethod("genefinder", c("matrix", "vector", "ANY", "ANY", "ANY", "ANY"),
+         function (X, ilist, numResults, scale, weights,
+                        method) {
+    X <- as.matrix(X)
+    METHOD <- c("euclidean", "maximum", "manhattan",
+                        "canberra", "correlation", "binary")
+    method<-pmatch(method, METHOD)
+    if (is.na(method))
+        stop ("The distance method is invalid.")
+
+    SCALE <- c("none", "range", "zscore")
+    scale <- SCALE[pmatch(scale, SCALE)]
+
+    # perform scaling if requested.
+    #
+    X <- switch(scale,
+                none=X,
+                range=genescale(X),
+                zscore=scale(X),
+                stop("The scaling method is invalid")
+                )
+    N <- nrow(X)
+    C <- ncol(X)
+
+    if( !is.vector(ilist) )
+        stop("the genes to be compared to must be in a vector")
+
+    ninterest <- length(ilist);
+
+    if( is.character(ilist) ) {
+        iRows <- match(ilist, row.names(X))
+        names(iRows) <- ilist
+    }
+    else if ( is.numeric(ilist) ) {
+        iRows <- ilist
+        names(iRows) <- row.names(X)[ilist]
+    }
+    else
+        stop("invalid genes selected")
+
+    if( any(is.na(iRows)) )
+        stop("invalid genes selected")
+
+    if (missing(weights))
+        weights <- rep(1,C)
+    else if (length(weights) != C)
+        stop("Supplied weights do not match number of columns")
+
+    ## Do a sanity check on the requested genes in ilist -> if the
+    ## gene exceeds the # of rows in the matrix, can not be processed.
+    if (max(iRows) > N)
+        stop("Requested genes exceed the dimensions of the supplied matrix.")
+
+
+    Genes <- array(as.integer(NA), dim=c(ninterest, numResults))
+    Dists <- array(as.integer(NA), dim=c(ninterest, numResults))
+    extCall <- .C("gf_distance",
+                  X = as.double(X),
+                  nr= as.integer(N),
+                  nc= ncol(X),
+                  g = as.integer(Genes),
+                  d = as.double(Dists),
+                  iRow  = as.integer(iRows),
+                  nInterest = as.integer(ninterest),
+                  nResults = as.integer(numResults),
+                  method= as.integer(method),
+                  weights = as.double(weights),
+                  NAOK=TRUE, PACKAGE="genefilter")
+
+    Genes <- extCall$g+1
+    Dists <- extCall$d
+    Which <- vector()
+
+    ## Get the number of genes/dists per selection.  There should
+    ## always be a number of total genes such that they are a multiple
+    ## of ninterest
+    numPerList <- length(Genes) / ninterest
+
+    Which <- rep(iRows, rep(numPerList, ninterest))
+
+    byGene <- split(Genes, Which)
+    names(byGene) <- rep("indices", length(byGene))
+    byDists <- split(Dists, Which)
+    names(byDists) <- rep("dists", length(byDists))
+    ## Need a better way to stuff these together
+    retList <- list()
+    for (i in 1:ninterest) {
+        retList[[i]] <- list(indices=byGene[[i]], dists=byDists[[i]])
+    }
+
+    return(retList)
+})
+
+
+
+
+
+
+
diff --git a/R/half.range.mode.R b/R/half.range.mode.R
new file mode 100755
index 0000000..b791578
--- /dev/null
+++ b/R/half.range.mode.R
@@ -0,0 +1,51 @@
+half.range.mode <- function( data, B, B.sample, beta = .5, diag = FALSE ) {
+
+  if ( length( data ) == 0 ) return( NA_real_ )
+
+  if (missing( B ) ) {
+
+    # Just one run on the full set...
+    
+    if ( is.unsorted( data ) ) data <- sort( data )
+    
+    .C(
+       "half_range_mode",
+       data = as.double( data ),
+       n = as.integer( length( data ) ),
+       beta = as.double( beta ),
+       diag = as.integer( diag ),
+       M = double(1),
+       PACKAGE = "genefilter"
+       )$M
+
+  }
+
+  else {
+
+    # Bootstrapped
+
+    if ( missing( B.sample ) )
+      B.sample <- length( data )
+
+    M <- sapply(
+                1:B,
+                function (x) {
+                  d <- sort( sample( data, B.sample, replace = T ) )
+                  .C(
+                     "half_range_mode",
+                     data = as.double( d ),
+                     n = as.integer( B.sample ),
+                     beta = as.double( beta ),
+                     diag = as.integer( diag ),
+                     M = double(1),
+                     PACKAGE = "genefilter"
+                     )$M
+                }
+                )
+
+    mean( M )
+    
+  }
+
+}
+
diff --git a/R/kappa_p.R b/R/kappa_p.R
new file mode 100644
index 0000000..40e542a
--- /dev/null
+++ b/R/kappa_p.R
@@ -0,0 +1,10 @@
+kappa_p <- function( p, n1, n2 = n1 ) {
+  n <- n1 + n2
+  t <- qt( 1 - p/2, df = n - 2 )
+  kappa_t( t, n1, n2 )
+}
+
+kappa_t <- function( t, n1, n2 = n1 ) {
+  n <- n1 + n2
+  sqrt( n * (n-1) * t^2 / ( n1 * n2 * ( n - 2 + t^2 ) ) )
+}
diff --git a/R/nsFilter.R b/R/nsFilter.R
new file mode 100644
index 0000000..97016ff
--- /dev/null
+++ b/R/nsFilter.R
@@ -0,0 +1,264 @@
+##RG introduces two new functions, varFilter that does what nsFilter
+##was supposed to, but never did, and featureFilter that does the only
+##useful stuff that nsFilter does
+rowIQRs <- function(eSet) {
+  numSamp <- ncol(eSet)
+  lowQ <- rowQ(eSet, floor(0.25 * numSamp))
+  upQ <- rowQ(eSet, ceiling(0.75 * numSamp))
+  upQ - lowQ
+}
+
+
+##For NOW, we will need to check the schema from within nsFilter and
+##featureFilter to decide what the internal ID is that needs to be used.
+##LATER, when we haev annotation packages that will make this sort of access
+##easier, it will make more sense to just access the central ID for those
+##packages.
+
+## It looks like I can take care of both nsFilter and featureFilter in this
+## way by just altering what the helper function findLargest() does
+
+
+
+
+
+
+varFilter <- function(eset, var.func=IQR, var.cutoff=0.5,filterByQuantile=TRUE
+)
+{
+    if (deparse(substitute(var.func)) == "IQR") {
+        vars <- rowIQRs(eset)
+    } else {
+        vars <- apply(exprs(eset), 1, var.func)
+    }
+    if (filterByQuantile) {
+        if ( 0 < var.cutoff && var.cutoff < 1 ) {
+            quant = quantile(vars, probs = var.cutoff)
+            selected = !is.na(vars) & vars > quant
+        } else stop("Cutoff Quantile has to be between 0 and 1.")
+    } else {
+        selected <- !is.na(vars) & vars > var.cutoff
+    }
+    eset <- eset[selected, ]
+}
+
+
+.getRequiredIDs <- function(eset, map){
+  annChip <- annotation(eset)
+  if(.isOrgSchema(annChip)){
+    IDs <- featureNames(eset)
+    names(IDs) <- featureNames(eset)
+  }else{
+    IDs <- mget(featureNames(eset), envir=getAnnMap(map, annChip), ifnotfound=NA)
+  }
+  IDs
+}
+
+featureFilter <- function(eset, require.entrez=TRUE,
+                   require.GOBP=FALSE, require.GOCC=FALSE,
+                   require.GOMF=FALSE, require.CytoBand=FALSE,
+                   remove.dupEntrez=TRUE,
+                   feature.exclude="^AFFX") {
+
+    annChip <- annotation(eset)
+    if (nchar(annChip) == 0) stop("'eset' must have a valid annotation slot")
+    
+    nfeat <- function(eset) length(featureNames(eset))
+    requireID <- function(eset, map) {
+        IDs <- .getRequiredIDs(eset, map)
+        haveID <- names(IDs)[sapply(IDs, function(x) !is.na(x))]
+        eset[haveID, ]
+    }
+
+    
+    if (require.entrez) {
+        map <- .findCentralMap(annChip)
+        eset <- requireID(eset, map)
+    }
+    
+    filterGO <- function(eset, ontology) {
+        haveGo <- sapply(mget(featureNames(eset), getAnnMap("GO", annChip), ifnotfound=NA),
+                         function(x) {
+                             if (length(x) == 1 && is.na(x))
+                                 FALSE
+                             else {
+                                 onts <- subListExtract(x, "Ontology", simplify=TRUE)
+                                 ontology %in% onts
+                             }
+                         })
+        eset[haveGo, ]
+    }
+    
+    if (require.GOBP) 
+        eset <- filterGO(eset, "BP")
+    if (require.GOCC) 
+        eset <- filterGO(eset, "CC")
+    if (require.GOMF) 
+        eset <- filterGO(eset, "MF")
+
+    if (length(feature.exclude)) {
+        fnms <- featureNames(eset)
+        badIdx <- integer(0)
+        for (pat in feature.exclude) {
+            if (nchar(pat) == 0)
+                next
+            badIdx <- c(grep(pat, fnms), badIdx)
+        }
+        if (length(badIdx)) {
+            badIdx <- unique(badIdx)
+            eset <- eset[-badIdx, ]
+        }
+    }
+    if (remove.dupEntrez ) {
+     ## Reduce to unique probe <--> gene mapping here by keeping largest IQR
+     ## We will want "unique genes" in the non-specific filtered gene
+     ## set.
+        uniqGenes <- findLargest(featureNames(eset), rowIQRs(eset),
+                                 annotation(eset))
+        eset <- eset[uniqGenes, ]
+    }
+
+    requireCytoBand <- function(eset) {
+        MAPs <- mget(featureNames(eset), envir=getAnnMap("MAP", annChip), ifnotfound=NA)
+        haveMAP <- names(MAPs)[sapply(MAPs, function(x) !is.na(x[1]))]
+        eset[haveMAP, ]
+    }
+
+    if (require.CytoBand)
+        eset <- requireCytoBand(eset)
+    
+    eset
+}
+
+
+setMethod("nsFilter", "ExpressionSet",
+          function(eset,
+                   require.entrez=TRUE,
+                   require.GOBP=FALSE,
+                   require.GOCC=FALSE,
+                   require.GOMF=FALSE,
+                   require.CytoBand=FALSE,
+                   remove.dupEntrez=TRUE,
+                   var.func=IQR, var.cutoff=0.5,
+                   var.filter=TRUE,
+                   filterByQuantile=TRUE,
+                   feature.exclude="^AFFX", ...)
+          {
+              if (!is.function(var.func))
+                stop("'var.func' must be a function")
+
+              annChip <- annotation(eset)
+              if (nchar(annChip) == 0)
+                stop("'eset' must have a valid annotation slot")
+
+              nfeat <- function(eset) length(featureNames(eset))
+              filter.log <- new.env(parent=emptyenv())
+
+              requireID <- function(eset, map) {
+                IDs <- .getRequiredIDs(eset, map)
+                  haveID <- names(IDs)[sapply(IDs, function(x) !is.na(x))]
+                  logvar <- paste("numRemoved", map, sep=".")
+                  assign(logvar, nfeat(eset) - length(haveID), envir=filter.log)
+                  eset[haveID, ]
+              }
+
+              if (require.entrez) {
+                  map <- .findCentralMap(annChip)
+                  eset <- requireID(eset, map)
+              }
+
+              filterGO <- function(eset, ontology) {
+                  haveGo <- sapply(mget(featureNames(eset), getAnnMap("GO", annChip), ifnotfound=NA),
+                                   function(x) {
+                                       if (length(x) == 1 && is.na(x))
+                                         FALSE
+                                       else {
+                                           onts <- subListExtract(x, "Ontology", simplify=TRUE)
+                                           ontology %in% onts
+                                       }
+                                   })
+                  logvar <- paste("numNoGO", ontology, sep=".")
+                  assign(logvar, sum(!haveGo), envir=filter.log)
+                  eset[haveGo, ]
+              }
+
+              if (require.GOBP) {
+                  eset <- filterGO(eset, "BP")
+              }
+
+              if (require.GOCC) {
+                  eset <- filterGO(eset, "CC")
+              }
+
+              if (require.GOMF) {
+                  eset <- filterGO(eset, "MF")
+              }
+
+              if (length(feature.exclude)) {
+                  fnms <- featureNames(eset)
+                  badIdx <- integer(0)
+                  for (pat in feature.exclude) {
+                      if (nchar(pat) == 0)
+                        next
+                      badIdx <- c(grep(pat, fnms), badIdx)
+                  }
+                  if (length(badIdx)) {
+                      badIdx <- unique(badIdx)
+                      eset <- eset[-badIdx, ]
+                      logvar <- "feature.exclude"
+                      assign(logvar, length(badIdx), filter.log)
+                  }
+              }
+
+
+              if (remove.dupEntrez) {
+                  ## Reduce to unique probe <--> gene mapping here by keeping largest IQR
+                  ## We will want "unique genes" in the non-specific filtered gene
+                  ## set.
+                  if (deparse(substitute(var.func)) == "IQR") {
+                      esetIqr <- rowIQRs(exprs(eset))
+                  } else {
+                      esetIqr <- apply(exprs(eset), 1, var.func)
+                  }
+                  numNsWithDups <- nfeat(eset)
+                  uniqGenes <- findLargest(featureNames(eset), esetIqr,
+                                           annotation(eset))
+                  eset <- eset[uniqGenes, ]
+                  logvar <- "numDupsRemoved"
+                  assign(logvar, numNsWithDups - nfeat(eset), envir=filter.log)
+              }
+
+
+              if (var.filter) {
+                  if (deparse(substitute(var.func)) == "IQR") {
+                      esetIqr <- rowIQRs(exprs(eset))
+                  } else {
+                      esetIqr <- apply(exprs(eset), 1, var.func)
+                  }
+                  ##note this was not happening in the first
+                  ##version - despite the documentation
+                  if (filterByQuantile) {
+                      if ( 0 < var.cutoff && var.cutoff < 1 ) {
+                          var.cutoff = quantile(esetIqr, var.cutoff)
+                      } else stop("Cutoff Quantile has to be between 0 and 1.")
+                  }
+                  selected <- esetIqr > var.cutoff
+                  eset <- eset[selected, ]
+                  logvar <- "numLowVar"
+                  assign(logvar, sum(!selected), filter.log)
+              }
+
+              requireCytoBand <- function(eset) {
+                  MAPs <- mget(featureNames(eset), envir=getAnnMap("MAP", annChip), ifnotfound=NA)
+                  haveMAP <- names(MAPs)[sapply(MAPs, function(x) !is.na(x[1]))]
+                  logvar <- paste("numRemoved", "MAP", sep=".")
+                  assign(logvar, nfeat(eset) - length(haveMAP), envir=filter.log)
+                  eset[haveMAP, ]
+              }
+
+              if (require.CytoBand)
+                  eset <- requireCytoBand(eset)
+
+              numSelected <- length(featureNames(eset))
+              list(eset=eset, filter.log=as.list(filter.log))
+          })
diff --git a/R/rejection_plot.R b/R/rejection_plot.R
new file mode 100644
index 0000000..a217eac
--- /dev/null
+++ b/R/rejection_plot.R
@@ -0,0 +1,79 @@
+rejection_plot <- function(p,
+                           col, lty = 1, lwd = 1,
+                           xlab = "p cutoff", ylab = "number of rejections",
+                           xlim = c( 0, 1 ), ylim,
+                           legend = names(p),
+                           at = c( "all", "sample" ),
+                           n_at = 100,
+                           probability = FALSE,
+                           ...
+                           )
+{
+
+  if ( is.matrix( p ) ) {
+    legend <- colnames( p )
+    p <- lapply( 1:ncol(p), function(i) p[,i] )
+  }
+
+  if ( missing( col ) )
+    col <- rainbow( length( p ), v = .7 )
+
+  col <- rep( col, length.out = length( p ) )
+  lty <- rep( lty, length.out = length( p ) )
+  lwd <- rep( lwd, length.out = length( p ) )
+    
+  if ( missing( ylim ) )
+    ylim <- c( 0, ifelse( probability, 1, max( sapply( p, length ) ) ) )
+
+  at <- match.arg( at )
+  
+  steps <- lapply(
+                  p,
+                  function(x) {
+                    x <- na.omit(x)
+                    stepfun(
+                            sort( x ),
+                            ( 0:length(x) ) / ifelse( probability, length(x), 1 )
+                            )
+                  }
+                  )
+
+  plot(
+       0,
+       type = "n",
+       xaxs = "i", yaxs = "i",
+       xlim = xlim, ylim = ylim,
+       xlab = xlab, ylab = ylab,
+       ...
+       )
+
+  if ( at == "all" ) {
+    for ( i in 1:length( steps ) )
+      lines(
+            steps[[i]],
+            xlim = xlim,
+            col = col[i], lty = lty[i], lwd = lwd[i],
+            do.points = FALSE
+            )
+  }
+  
+  else {
+    x <- seq( xlim[1], xlim[2], length = n_at )
+    for ( i in 1:length( steps ) )
+      lines(
+            x, steps[[i]](x),
+            col = col[i], lty = lty[i], lwd = lwd[i]
+            )
+  }
+
+  if ( !is.null( legend ) )
+    legend(
+           "topleft", 
+           legend,
+           col = col, lty = lty, lwd = lwd,           
+           inset = .05
+           )
+  
+  invisible( steps )
+
+}
diff --git a/R/rowROC-accessors.R b/R/rowROC-accessors.R
new file mode 100644
index 0000000..4160019
--- /dev/null
+++ b/R/rowROC-accessors.R
@@ -0,0 +1,153 @@
+## ==========================================================================
+## show method for objects of class rowROC
+## - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
+setMethod("show", signature(object="rowROC"), function(object){
+    cat("matrix of ROC curves for", nrow(object at data), "genes/rows",
+        "with", max(0,ncol(object at cutpoints)), "cutpoints\n")
+    cat("  size of class ", object at caseNames[1] ,": ",
+        sum(object at factor==levels(object at factor)[1]), "\n", sep="")
+    cat("  size of class ", object at caseNames[2] ,": ",
+        sum(object at factor==levels(object at factor)[2]), "\n", sep="")
+    cat("partial areas under curve calculated for p=",
+        object at p, "\n", sep="")
+})
+## ==========================================================================
+
+
+## ==========================================================================
+## subsetting method for objects of class rowROC
+## - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
+setMethod("[",
+          signature="rowROC",
+          definition=function(x, i, j="missing", drop="missing") {
+              x at sens <- x at sens[i,,drop=FALSE]
+              x at spec <- x at spec[i,,drop=FALSE]
+              x at pAUC <- x at pAUC[i]
+              x at AUC <- x at AUC[i]
+              x at data <- x at data[i,,drop=FALSE]
+              x at cutpoints <- x at cutpoints[i,,drop=FALSE]
+              x at ranks <- x at ranks[i,,drop=FALSE]
+              return(x)
+          },
+          valueClass="rowROC")
+## ==========================================================================
+
+
+## ==========================================================================
+## plot method for objects of class rowROC
+## - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
+setMethod("plot", signature(x="rowROC", y="missing"),
+          function(x, pch=20, cex=0.7, xlab="1 - specificity",
+                   ylab="sensitivity",
+                   main=NULL,
+                   sub=paste("class ", x at caseNames[1], " (",
+                   sum(x at factor==levels(x at factor)[1]),
+                   " cases) | class ", x at caseNames[2], " (",
+                   sum(x at factor==levels(x at factor)[2]), " cases)", sep=""),
+                   ...){
+              sx <- sort(1-x at spec[1,])
+              sy <- sort(x at sens[1,])
+              spx <- c(sx[sx<=x at p & sy>0],x at p)
+              spy <- sy[sx<=x at p & sy>0]
+              if(!length(spy)){
+                  spy <- 0
+                  spx <- c(0,spx)
+              }
+              spy <- c(spy, max(spy))
+              len <- length(sx)
+              nn <-  names(area(x)[1])
+              if(is.null(main))
+                  main <- paste("ROC-Curve", ifelse(length(nn),
+                                                    paste("(", nn, ")", sep=""), ""))
+              plot(sx, sy, pch=pch, cex=cex, xlab=xlab,
+                   ylab=ylab, main=main, sub=sub, ...)
+              if(mean(x at data)==1 || all(sx==sy))
+                  polygon(c(0,1,1), c(0,0,1), col="#ececec", lty=0)
+              else{
+                  rect(spx[-1], 0, spx[-1] - diff(spx),spy[-1],
+                       col="#ececec", lty=0)       
+                  lines(sx, sy, type="s")
+              }
+              points(sx, sy, pch=pch, cex=cex, ...)
+              lines(0:1, 0:1, lty=3, col="darkgray")
+              atext <- paste("AUC:  ", signif(x at AUC[1],3))
+              tw <- strwidth(atext)
+              w <- diff(par("usr")[1:2])
+              cex <- min(1, (w/2+w/10)/tw)
+              th <- strheight(atext, cex=cex)*1.1
+              if(x at p<1){
+                  ptext <- paste("pAUC: ", signif(x at pAUC[1],3), " (p=", x at p,  ")",
+                                 sep="")
+                  tw <- max(tw, strwidth(ptext))
+                  cex <- min(1, (w/2+w/10)/tw)
+                  abline(v=x at p, col="darkblue", lty=2) 
+                  text(x=1-tw*cex*1.1, y=0.02+th*cex, atext, pos=4, cex=cex)
+                  text(x=1-tw*cex*1.1, y=0.02, ptext, pos=4, cex=cex)
+              }else{
+                  text(x=1-tw*cex*1.1, y=0.02, atext, pos=4, cex=cex)
+              }
+          })
+## ==========================================================================
+
+
+## ==========================================================================
+## pAUC method for objects of class rowROC
+## - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
+setMethod("pAUC", signature(object="rowROC", p="numeric"),
+          function(object, p, flip=TRUE){
+              if(length(flip)!=1 || !(is.logical(flip)))
+                  stop("'flip' must be logical scalar")
+              flip <- as.integer(flip)
+              res <- .Call("pAUC", object at spec, object at sens, p, flip)
+              names(res$pAUC) <-  names(res$AUC) <- names(object at AUC)
+              object at pAUC <- res$pAUC
+              object at AUC <- res$AUC
+              object at p <- p
+              return(object)
+          })
+## ==========================================================================
+
+
+## ==========================================================================
+## AUC method for objects of class rowROC
+## - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
+setMethod("AUC", signature(object="rowROC"),          
+          function(object){
+              object at pAUC <- object at AUC
+              object at p <- 1
+              return(object)
+          })
+## ==========================================================================
+
+
+## ==========================================================================
+## accessor method to slot 'sens' for objects of class rowROC
+## - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
+setMethod("sens", signature(object="rowROC"),          
+          function(object)
+          return(object at sens)
+          )
+## ==========================================================================
+
+
+## ==========================================================================
+## accessor method to slot 'spec' for objects of class rowROC
+## - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
+setMethod("spec", signature(object="rowROC"),          
+          function(object)
+          return(object at spec)
+          )
+## ==========================================================================
+
+
+## ==========================================================================
+## accessor method to slots 'AUC' or 'pAUC' for objects of class rowROC
+## - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
+setMethod("area", signature(object="rowROC"),          
+          function(object, total=FALSE){
+              if(total)
+                  return(object at AUC)
+              else
+                  return(object at pAUC)
+          })
+## ==========================================================================
diff --git a/R/rowSds.R b/R/rowSds.R
new file mode 100644
index 0000000..8230da8
--- /dev/null
+++ b/R/rowSds.R
@@ -0,0 +1,9 @@
+rowVars = function(x, ...) {
+  sqr     = function(x)  x*x
+  n       = rowSums(!is.na(x))
+  n[n<=1] = NA
+  return(rowSums(sqr(x-rowMeans(x, ...)), ...)/(n-1))
+}
+
+rowSds = function(x, ...)
+  sqrt(rowVars(x, ...))
diff --git a/R/rowpAUCs-methods.R b/R/rowpAUCs-methods.R
new file mode 100644
index 0000000..cb2bc03
--- /dev/null
+++ b/R/rowpAUCs-methods.R
@@ -0,0 +1,86 @@
+## ==========================================================================
+## core rowpAUCs method for objects of class matrix
+## - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
+setMethod("rowpAUCs", signature(x="matrix", fac="factor"),
+          function(x, fac, p=0.1, flip=TRUE, caseNames=c("1", "2")){  
+            ##check argument 'p'
+            if(!is.numeric(p) || length(p)>1)
+              stop("'p' must be numeric of length 1")
+            ## check argument 'fac'
+            f <- checkfac(fac)
+            if(f$nrgrp != 2 || length(f$fac) != ncol(x) ||
+               length(unique(f$fac)) !=2 )
+                stop("'fac' must be factor with 2 levels and length 'ncol(x)'")
+            ## check argument 'flip'
+            if(length(flip)!=1 || !(is.logical(flip)))
+                stop("'flip' must be logical scalar")
+            flip <- as.integer(flip)
+            ## compute cutpoints
+            cutpts <- matrix((0:ncol(x))+0.5, ncol=ncol(x)+1, 
+                             nrow=nrow(x), byrow=TRUE,
+                             dimnames=list(rownames(x), NULL))
+            
+            ## rank data
+            xr <- t(apply(x, 1, rank))
+            mode(xr) <- "numeric"
+            ## call C function and return object of class 'rowROC'
+            res <- .Call("ROCpAUC", xr, cutpts, as.integer(f$fac), p,
+                         PACKAGE="genefilter", flip)
+            sens <- res$sens
+            spec <- res$spec
+            rownames(sens) <- rownames(spec) <- rownames(x)
+            pAUC <- res$pAUC
+            AUC <- res$AUC
+            names(AUC) <- names(pAUC) <- rownames(x)
+            object <- new("rowROC", data=x, sens=sens,
+                          spec=spec, pAUC=pAUC, AUC=AUC,
+                          factor=factor(f$fac), p=p, ranks=xr,
+                          caseNames=as.character(caseNames),
+                          cutpoints=cutpts)
+            return(object)
+          })
+## ==========================================================================
+
+
+## ==========================================================================
+## rowpAUCs method with signature x=matrix, fac=numeric
+## - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
+setMethod("rowpAUCs", signature(x="matrix", fac="numeric"),
+          function(x, fac, p=0.1, flip=TRUE, caseNames=c("1", "2")){
+            cutpts <- matrix((0:ncol(x))+0.5, ncol=ncol(x)+1, 
+                             nrow=nrow(x), byrow=TRUE)
+            rowpAUCs(x=x, fac=factor(fac), p=p, flip=flip,
+                   caseNames=caseNames) 
+          })
+## ==========================================================================
+
+
+## ==========================================================================
+## rowpAUCs method with signature x=ExpressionSet
+## - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -  
+setMethod("rowpAUCs", signature(x="ExpressionSet"),        
+          function(x, fac, p=0.1, flip=TRUE, caseNames=c("1", "2")){
+            rowpAUCs(x=exprs(x), fac=fac, p=p, flip=flip,
+                     caseNames=caseNames) 
+          })
+## ==========================================================================
+
+
+## ==========================================================================
+## rowpAUCs method with signature x=ExpressionSet fac=character
+## - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -  
+setMethod("rowpAUCs", signature(x="ExpressionSet", fac="character"),        
+          function(x, fac, p=0.1, flip=TRUE, caseNames=c("1", "2")){
+            if (length(fac) == 1){
+                if(!fac %in% colnames(pData(x)))
+                    stop("fac must be length 1 character indicating a ",
+                         "covariate in the phenoData slot of the expressionSet")
+                cn <- as.character(levels(pData(x)[[fac]]))
+                fac = factor(as.integer(factor(pData(x)[[fac]]))-1)
+                rowpAUCs(x=exprs(x), fac=fac, p=p, flip=flip, caseNames=cn)
+            }else{
+                rowpAUCs(x=x, fac=as.factor(fac), p=p, flip=flip,
+                         caseNames=caseNames)
+            }
+          })
+## ==========================================================================
diff --git a/R/rowttests-methods.R b/R/rowttests-methods.R
new file mode 100644
index 0000000..b5af4a3
--- /dev/null
+++ b/R/rowttests-methods.R
@@ -0,0 +1,215 @@
+##--------------------------------------------------------------------------------------##
+## This file contains methods definitions for rowttests, colttest, rowFtests, colFtests ##
+##--------------------------------------------------------------------------------------##
+
+
+##-----------------------------------------------------------------------
+## The core function for row- and column-wise t-tests - it uses C code
+##------------------------------------------------------------------------
+rowcoltt =  function(x, fac, tstatOnly, which) {
+  if (!missing(tstatOnly) && (!is.logical(tstatOnly) || is.na(tstatOnly)))
+    stop(sQuote("tstatOnly"), " must be TRUE or FALSE.")
+  
+  f = checkfac(fac)
+  if ((f$nrgrp > 2) || (f$nrgrp <= 0))
+    stop("Number of groups is ", f$nrgrp, ", but must be >0 and <=2 for 'rowttests'.")
+
+  if (typeof(x) == "integer")
+      x[] <- as.numeric(x)
+
+  cc = .Call("rowcolttests", x, f$fac, f$nrgrp, which-1L, PACKAGE="genefilter")
+    
+  res = data.frame(statistic = cc$statistic,
+                   dm        = cc$dm,
+                   row.names = dimnames(x)[[which]])
+
+  if (!tstatOnly)
+    res = cbind(res, p.value = 2*pt(abs(res$statistic), cc$df, lower.tail=FALSE))
+
+  attr(res, "df") = cc$df    
+  return(res)
+}
+
+##------------------------------------------------------------
+## The core function for F-tests - it uses R matrix algebra 
+##------------------------------------------------------------
+rowcolFt =  function(x, fac, var.equal, which) {
+  
+  if(!(which %in% c(1L, 2L)))
+    stop(sQuote("which"), " must be 1L or 2L.")
+  
+  if(which==2L)
+    x = t(x)
+
+  if (typeof(x) == "integer")
+      x[] <- as.numeric(x)
+
+  sqr = function(x) x*x
+  
+  stopifnot(length(fac)==ncol(x), is.factor(fac), is.matrix(x))
+  x   <- x[,!is.na(fac), drop=FALSE]
+  fac <- fac[!is.na(fac)]
+
+  ## Number of levels (groups)
+  k <- nlevels(fac)
+
+  ## xm: a nrow(x) x nlevels(fac) matrix with the means of each factor
+  ## level
+  xm <- matrix(
+     sapply(levels(fac), function(fl) rowMeans(x[,which(fac==fl), drop=FALSE])),
+     nrow = nrow(x),
+     ncol = nlevels(fac))
+
+  ## x1: a matrix of group means, with as many rows as x, columns correspond to groups 
+  x1 <- xm[,fac, drop=FALSE]
+
+  ## degree of freedom 1
+  dff    <- k - 1
+
+  if(var.equal){
+    ## x0: a matrix of same size as x with overall means
+    x0 <- matrix(rowMeans(x), ncol=ncol(x), nrow=nrow(x))
+  
+    ## degree of freedom 2
+    dfr    <- ncol(x) - dff - 1
+
+    ## mean sum of squares
+    mssf   <- rowSums(sqr(x1 - x0)) / dff
+    mssr   <- rowSums(sqr( x - x1)) / dfr
+
+    ## F statistic
+    fstat  <- mssf/mssr
+
+  } else{
+
+    ## a nrow(x) x nlevels(fac) matrix with the group size  of each factor
+    ## level
+    ni <- t(matrix(tapply(fac,fac,length),ncol=nrow(x),nrow=k))
+
+    ## wi: a nrow(x) x nlevels(fac) matrix with the variance * group size of each factor
+    ## level
+    sss <- sqr(x-x1)
+    x5 <- matrix(
+       sapply(levels(fac), function(fl) rowSums(sss[,which(fac==fl), drop=FALSE])),
+       nrow = nrow(sss),
+       ncol = nlevels(fac))          
+    wi <- ni*(ni-1) /x5
+
+    ## u : Sum of wi
+    u  <- rowSums(wi)
+
+    ## F statistic
+    MR <- rowSums(sqr((1 - wi/u)) * 1/(ni-1))*1/(sqr(k)-1)
+    fsno <- 1/dff * rowSums(sqr(xm - rowSums(wi*xm)/u) * wi)
+    fsdeno <- 1+ 2* (k-2)*MR
+    fstat <- fsno/fsdeno
+
+    ## degree of freedom 2: Vector with length nrow(x)
+    dfr <- 1/(3 * MR)
+  
+  }
+  
+  res = data.frame(statistic = fstat,
+                   p.value   = pf(fstat, dff, dfr, lower.tail=FALSE),
+                   row.names = rownames(x))
+
+  attr(res, "df") = c(dff=dff, dfr=dfr)
+  return(res)
+}
+
+## ==========================================================================
+## rowttests and colttests methods for 'matrix'
+## ==========================================================================
+setMethod("rowttests", signature(x="matrix", fac="factor"),
+          function(x, fac, tstatOnly=FALSE)
+          rowcoltt(x, fac, tstatOnly, 1L))
+
+setMethod("rowttests", signature(x="matrix", fac="missing"),
+          function(x, fac, tstatOnly=FALSE) 
+          rowcoltt(x, factor(integer(ncol(x))), tstatOnly, 1L))
+
+setMethod("colttests", signature(x="matrix", fac="factor"),
+          function(x, fac, tstatOnly=FALSE)
+          rowcoltt(x, fac, tstatOnly, 2L))
+
+setMethod("colttests", signature(x="matrix", fac="missing"),
+          function(x, fac, tstatOnly=FALSE) 
+          rowcoltt(x, factor(integer(ncol(x))), tstatOnly, 2L))
+
+
+## ==========================================================================
+## rowFtests and colFtests methods for 'matrix'
+## ==========================================================================
+setMethod("rowFtests", signature(x="matrix", fac="factor"),
+          function(x, fac, var.equal=TRUE)
+          rowcolFt(x, fac, var.equal, 1L))
+
+setMethod("colFtests", signature(x="matrix", fac="factor"),
+          function(x, fac, var.equal=TRUE)
+          rowcolFt(x, fac, var.equal, 2L))
+
+
+## ===========================================================================
+## Methods for 'ExpressionSet': only for rowttests and rowFtests
+## -==========================================================================
+setMethod("rowttests", signature(x="ExpressionSet", fac="factor"),
+  function(x, fac, tstatOnly=FALSE)
+    rowcoltt(exprs(x), fac, tstatOnly=tstatOnly, 1L))
+
+setMethod("rowttests", signature(x="ExpressionSet", fac="missing"),
+  function(x, fac, tstatOnly=FALSE) {
+    x = exprs(x)
+    fac = integer(ncol(x))
+    rowcoltt(x, fac, tstatOnly, 1L)
+  })
+
+setMethod("rowttests", signature(x="ExpressionSet", fac="character"),
+  function(x, fac, tstatOnly=FALSE) {
+    if (length(fac) != 1)
+      stop("fac must be length 1 character or a factor")
+    fac = factor(pData(x)[[fac]])
+    rowcoltt(exprs(x), fac, tstatOnly, 1L)
+  })
+
+setMethod("rowFtests", signature(x="ExpressionSet", fac="factor"),
+  function(x, fac, var.equal=TRUE)
+    rowcolFt(exprs(x), fac, var.equal, 1L))
+
+setMethod("rowFtests", signature(x="ExpressionSet", fac="character"),
+ function(x, fac, var.equal=TRUE) {
+   fac = factor(as.integer(factor(pData(x)[[fac]]))-1L)
+   rowcolFt(exprs(x), fac, var.equal, 1L)
+ })
+
+
+
+## ------------------------------------------------------------
+## convert fac from factor or numeric to integer and then
+## make sure it is an integer 
+## ------------------------------------------------------------
+checkfac = function(fac) {
+
+  if(is.numeric(fac)) {
+    nrgrp = as.integer(max(fac, na.rm=TRUE)+1)
+    fac   = as.integer(fac)
+  }
+  ## this must precede the factor test
+  if(is.character(fac))
+    fac = factor(fac)
+
+  if (is.factor(fac)) {
+    nrgrp = nlevels(fac)
+    fac   = as.integer(as.integer(fac)-1)
+  } 
+  if(!is.integer(fac))
+    stop("'fac' must be factor, character, numeric, or integer.")
+  
+  if(any(fac<0, na.rm=TRUE))
+    stop("'fac' must not be negative.")
+    
+  return(list(fac=fac, nrgrp=nrgrp))
+}
+
+
+
+
diff --git a/R/shorth.R b/R/shorth.R
new file mode 100644
index 0000000..a8ba179
--- /dev/null
+++ b/R/shorth.R
@@ -0,0 +1,48 @@
+shorth <- function(x, na.rm=FALSE, tie.action="mean", tie.limit=0.05) {
+  stopifnot(is.numeric(x))
+  if (na.rm) {
+    x <- x[is.finite(x)]
+  } else {
+    if(any(!is.finite(x)))
+      stop("'x' contains NA or NaN, and 'na.rm' is FALSE.")
+  }
+    
+  if(length(x)==0L) {
+    
+    NA_real_
+      
+    } else {
+      
+      sx    <- sort(x)
+      width <- round(0.5*length(x))
+      diffs <- sx[(width+1):length(x)] - sx[1:(length(x)-width)]
+      
+      ## cannot use which.min since we want all minimising points not just one:
+      q  <- which(diffs==min(diffs))
+      
+      if(length(q)>1) {
+        ## deal with ties:
+        maxq = max(q)
+        minq = min(q)
+        ## take the action specified in "tie.action"
+        q <- switch(tie.action,
+                    mean = {
+                      if (maxq-minq <= tie.limit * length(x)) {
+                        mean(q)
+                      } else {
+                        stop(paste("Encountered tie(s), and the difference between minimal and maximal value is larger than 'length(x)*tie.limit'.",
+                                   "This could mean that the distribution does not have a single well-defined mode.",
+                                   paste("q=", minq, "...", maxq, ",  values=", signif(sx[minq],4), "...", signif(sx[minq+width],4), sep=""), sep="\n"))
+                      }},
+                    max  = maxq, ## largest midpoint (maxq)
+                    min  = minq, ## smallest midpoint (minq)
+                    stop(sprintf("Invalid value '%s' for argument 'tie.action'", tie.action))
+                    )
+      } ## if
+      
+      mean(sx[q:(q+width-1)])
+      
+    } ## if
+  
+}
+
diff --git a/R/zzz.R b/R/zzz.R
new file mode 100644
index 0000000..e123dbc
--- /dev/null
+++ b/R/zzz.R
@@ -0,0 +1,9 @@
+.onLoad <- function(lib, pkgname) {
+    if(.Platform$OS.type == "windows" && interactive() && .Platform$GUI ==  "Rgui"){
+      addVigs2WinMenu("genefilter")
+   }
+ }
+
+.onUnload <- function( libpath ) {
+  library.dynam.unload( "genefilter", libpath )
+}
diff --git a/build/vignette.rds b/build/vignette.rds
new file mode 100644
index 0000000..fdaac74
Binary files /dev/null and b/build/vignette.rds differ
diff --git a/data/tdata.R b/data/tdata.R
new file mode 100644
index 0000000..75b6ece
--- /dev/null
+++ b/data/tdata.R
@@ -0,0 +1,1952 @@
+"tdata" <- structure(list(A = c(192.742, 97.137, 45.8192, 22.5445, 96.7875, 
+89.073, 265.964, 110.136, 43.0794, 10.9187, 751.227, 76.9437, 
+105.378, 40.4826, 58.1706, 257.619, 129.056, 61.7251, -40.9349, 
+284.407, 178.745, 79.7368, 9903.19, 61.2671, 120.544, 50.0962, 
+42.5285, 36.8936, 234.698, 26.9561, 58.124, 40.616, 125.063, 
+49.9943, 33.1246, 148.494, 66.6936, 19.1364, 165.75, 179.989, 
+151.72, 553.87, 72.2579, -30.1595, 65.1004, 1781.95, 3311.18, 
+4478.99, 3835.31, 4252.98, 5449.81, 79.7636, 3.75133, 44.3623, 
+197.782, 831.418, 541.391, 117.151, 144.719, 70.46, 55.4337, 
+224.167, 238.342, 130.794, 54.0728, 107.263, 382.255, 36.9832, 
+22.9605, 6.29927, 17.1529, 216.932, 190.178, 113.476, 50.7945, 
+1139.56, -18.287, 17.2761, 17.7039, 15.8655, 123.621, 174.661, 
+25.4169, 17.0339, 102.591, 67.8606, 754.361, 1.86526, 121.892, 
+14.5586, 3175.57, 40.8068, 18.1273, 22.5912, 14.4076, 64.5555, 
+17.8468, 412.283, 8.93417, -28.9985, 28.59, 316.157, 139.423, 
+8.50093, 60.8199, 37.7096, 35.6071, 192.835, 24.9388, 29.4782, 
+268.752, 13.0213, 65.5145, 464.122, 65.3482, 185.137, 165.366, 
+240.969, 51.1941, 6.66395, 48.6114, 36.5343, 412.338, 141.939, 
+36.4318, 52.9437, 61.3229, 65.3667, 68.6627, 10.9786, 23.8657, 
+5.01524, 177.065, 45.8588, 50.9341, 407.17, 16.8144, 24.3676, 
+139.241, 101.986, 126.172, 81.2844, -7.15113, 57.5308, 118.845, 
+3351.76, 286.108, 183.669, -0.944537, 21.8096, 16.7794, 405.217, 
+78.5843, 1705.65, 71.6915, 16.6355, 3211.06, 80.4291, 15.9308, 
+86.4344, 12.4541, 13.0163, 138.419, 16.6741, 20.1171, 323.881, 
+132.963, 3.27231, 113.622, -4.52738, 145.533, 19.0251, 28.0719, 
+128.004, 333.392, 17.6846, 92.238, 141.285, 17.7226, 1937.11, 
+54.0638, 15.8039, 29.8451, 76.3667, 445.892, 143.263, 202.725, 
+24.9869, 963.851, 79.9563, 56.2773, 321.199, 738.774, 100.949, 
+188.097, 18.1364, 355.357, 74.2606, 133.454, 98.7327, 694.948, 
+92.4006, 25.0186, 250.085, 3876.44, 117.049, 122.154, 67.1931, 
+7.30897, 84.6283, 49.592, 335.108, 66.4654, 86.0123, 72.9268, 
+44.994, 9.38836, 444.915, 92.0446, 10.0007, 18.8823, 58.7393, 
+13.3018, 569.842, 37.662, 40.3649, 226.662, 12.82, 391.518, 110.782, 
+7.59043, 194.394, 27.4265, 7.68662, 65.2073, 119.647, 16.0125, 
+1281.78, 226.635, 10.8538, 17.5639, 1335.61, 86.3719, 62.4806, 
+195.822, 244.137, 14.4861, 46.9659, 195.317, 5.81787, 184.517, 
+22.0721, 199.422, 16.2109, 6.64863, 161.7, 44.5963, 505.617, 
+110.631, 185.215, 27.4203, 24.4519, 216.36, 255.058, 309.114, 
+4667.83, 112.576, 91.4096, 633.803, 2329.11, -31.0105, 2809.33, 
+9.45511, 2.93526, 245.995, 132.075, 25.4559, -78.1238, 9.77901, 
+66.6104, 78.5702, 60.3145, 40.4373, 50.5534, 93.9559, 152.835, 
+57.4955, 2847.08, 90.0681, 336.346, 333.8, 117.994, 36.3703, 
+75.0352, 53.314, 286.113, 291.484, 73.877, 3858.49, 11.1541, 
+26.7391, -19.123, 8.3213, -175.867, 316.537, 3205.89, 1633.98, 
+490.371, 69.9426, 24.3604, 148.338, 42.0539, 166.386, 11.0695, 
+466.869, 918.454, 105.831, 6336.55, 94.5106, 124.549, 78.9894, 
+57.1918, -10.0784, 3.87075, 109.668, 77.1675, 457.371, 90.2235, 
+2193.88, 97.9357, 67.4934, 12.5044, 87.9604, 1136.1, 52.8251, 
+205.778, 47.9478, 37.0896, 29.8769, 163.502, 52.9366, -6.26854, 
+24.8778, 2172.91, 2117.27, 34.5438, 3.18616, 181.501, 32.5297, 
+105.013, 292.29, 63.8859, 174.173, 95.0869, 280.535, 109.507, 
+1354.61, 1961.83, 64.2933, 34.5335, 92.1684, 6.89252, 118.755, 
+40.8079, 229.027, 100.052, 26.8675, 48.7903, 145.687, 1698.05, 
+165.572, 3.01315, 14.9219, 115.39, 222.809, 52.0182, 17.2658, 
+33.2661, 61.0926, 13.8854, 638.578, 622.462, 1695.75, 685.856, 
+122.788, 13.867, 234.63, 327.099, 45.4667, 34.1512, 10.0776, 
+-57.7591, 33.2443, 43.9199, 345.91, 157.343, 276.585, 551.108, 
+401.466, 26.783, 344.651, 99.7442, -80.8385, 19.5091, 66.3027, 
+87.1783, 8.25017, 37.6927, 113.722, 78.6986, 24.9035, 6.32616, 
+-36.7863, 30.8709, 48.0258, 347.951, 6.1035, 20.7713, 59.5264, 
+119.503, 27.8618, 35.1162, 92.8325, 190.052, 11.9853, -53.8608, 
+-0.760266, 789.487, 349.556, 252.402, 148.234, 158.495, 7.5498, 
+258.37, 4.04513, 2.94722, 11.3329, 37.8421, 29.3296, 153.122, 
+328.971, 287.74, 59.2783, 52.3302, 70.1602, 285.172, 110.687, 
+442.733, 55.6486, 37.2868, 81.0269, 239.965, 582.627, 858.9, 
+230.119, 58.5767, 13.7181, 1739.95, 72.151, 286.243, 265.477, 
+652.056, 5.14324, 27.5791, 238.494, 310.136, 35.5071, 23.6182, 
+2080.61, 376.363, 545.377, 66.1117, 82.6331, 54.9434, 11.3511, 
+259.183, 153.759, 16.8873, 30.2569, 1505.73, 1937.31, 233.214, 
+3250.14, -22.2448, 269.912, 84.6064, 233.003, 248.216, 150.127, 
+4.59592, 129.867, 19.7505, 24.819, 63.576, 190.533, 26.7016, 
+446.512, 22.4641, 299.434, 253.692), B = c(85.7533, 126.196, 
+8.83135, 3.60093, 30.438, 25.8461, 181.08, 57.2889, 16.8006, 
+16.1789, 515.004, 40.907, 97.4932, 7.45801, 15.7926, 113.69, 
+74.6095, 50.2372, -83.9302, 208.099, 101.3, 55.5632, 8501.62, 
+37.474, 75.9854, 27.9532, 33.7186, 35.1697, 102.467, -2.37297, 
+-1.69785, 34.713, 98.0369, 19.8722, 4.91484, 70.9219, 5.60854, 
+20.8099, 300.024, 790.943, 546.343, 1758.42, 159.484, -64.7658, 
+19.7163, 2370.97, 3270.14, 3937.24, 5529.02, 5758.12, 5870.02, 
+36.0172, 20.7365, 54.8022, 44.7054, 501.091, 377.234, 128.234, 
+181.278, 93.6398, 64.7447, 180.978, 190.311, 67.1193, 30.2595, 
+73.1682, 237.818, 42.2591, 13.4121, 19.1633, 27.1722, 162.563, 
+120.161, 84.9185, 53.818, 5154.31, 3.74538, 36.0095, 15.2357, 
+23.9183, 95.3586, 103.08, 42.3577, 23.4741, 92.3486, 24.4368, 
+777.105, 5.41691, 92.031, 34.3359, 3548.02, 3.2361, 9.65582, 
+9.13811, -1.38469, 56.5676, 1.12837, 440.35, 4.28296, -30.0532, 
+16.6452, 278.807, 169.568, 21.1695, -394.553, 16.4941, 38.4721, 
+78.9517, 3.10118, 30.1089, 167.865, -3.0867, 44.0921, 436.574, 
+44.5892, 163.138, 194.529, 214.829, 55.8029, 11.3476, 14.958, 
+25.3529, 384.259, 72.7142, 12.4748, 27.1124, 66.3107, 66.8159, 
+63.0803, 92.1722, 0.177197, -38.9859, 171.192, 34.0826, 4.07801, 
+373.017, -0.769524, 6.01475, 89.9168, 84.6254, 107.521, 74.2868, 
+-20.7531, 148.301, 94.944, 4323.17, 232.94, 121.714, 69.4382, 
+5.72227, 7.3986, 415.275, 28.8216, 1315.01, 36.1148, 67.0027, 
+2593.65, 24.3428, -17.6152, 50.0729, 9.31312, -23.0799, 86.1644, 
+-8.1025, 19.6846, 235.001, 73.4631, 13.8193, 59.9681, 2.94767, 
+157.69, 47.6266, 61.1661, 104.139, 379.143, 23.7638, 71.4745, 
+87.7626, 30.7267, 1499.43, 39.9567, 7.69656, 2.28445, 59.4088, 
+330.876, 105.898, 176.47, 1.81061, 851.733, 20.8281, 45.8031, 
+649.608, 1163.7, 55.8623, 151.278, -16.7101, 277.792, 42.7732, 
+241.785, 131.357, 616.905, 54.4591, 41.0307, 212.55, 4456.75, 
+212.208, 115.759, 58.1292, -15.082, 90.8461, 20.9174, 277.822, 
+44.4367, 68.6069, 16.3172, 3.4138, -3.38286, 285.917, 126.127, 
+0.609841, 59.5828, 4.21187, 8.49004, 870.198, 13.2164, 14.4078, 
+203.901, 14.9982, 252.349, 74.7691, 10.7374, 170.651, 97.6762, 
+33.0937, 35.1276, 200.758, 24.2109, 808.399, 176.946, 10.668, 
+23.3083, 2208.33, 62.0363, 40.6219, 64.4413, 104.971, 22.7284, 
+600.467, 361.212, -6.01692, 291.5, 21.2316, 473.545, 20.4983, 
+31.2972, 150.28, 111.154, 182.812, 93.91, 372.524, 72.3758, 15.8334, 
+147.966, 267.088, 813.374, 2995.08, 66.3044, 46.9761, 1468.57, 
+2370.87, -59.0063, 3676.6, 148.159, 12.0201, 220.69, 111.018, 
+55.0777, -66.3389, -13.7223, 76.5278, 53.8695, 194.842, 131.637, 
+235.74, 240.715, 247.238, 122.939, 3743.96, 573.17, 387.269, 
+251.052, 107.653, 37.0203, 137.625, 33.853, 238.052, 863.607, 
+35.8266, 3568.89, 1.50669, 27.7993, -5.28788, 11.2962, -125.024, 
+408.582, 3515.46, 2218.3, 511.181, 41.3118, 15.083, 116.584, 
+9.54446, 142.225, -26.1006, 363.157, 728.89, 93.9206, 7294.08, 
+22.3793, 107.922, 31.4733, 101.262, 57.8828, -28.1437, 59.2715, 
+66.1019, 377.694, 78.6573, 3324.68, 50.878, 71.3438, 9.54178, 
+54.2085, 2764.5, 20.1416, 167.67, 10.6369, 22.4401, 48.3359, 
+70.4437, 19.7066, 52.0355, 25.3512, 3017.39, 2812.14, 11.6979, 
+77.0231, 212.566, 16.6308, 82.0771, 185.749, 34.072, 101.539, 
+181.17, 197.009, 75.3342, 2147.25, 1587.88, 151.32, 30.4737, 
+123.478, 2.23759, 69.8942, 26.9286, 79.6353, 117.308, -34.0231, 
+42.9693, 217.778, 1353.85, 116.874, 3.5022, 22.7868, 57.4058, 
+161.722, 29.8741, 9.53801, 33.8521, 24.413, 17.7637, 520.449, 
+591.734, 2062.22, 996.584, 78.1948, 45.329, 167.125, 401.967, 
+34.1303, 21.5371, 2.24541, -26.3753, 32.5026, 29.1886, 206.237, 
+93.309, 200.928, 487.538, 337.674, 30.2136, 278.321, 118.652, 
+-52.243, 17.923, 21.0778, 55.3885, 2.27909, 47.3832, 88.2588, 
+49.7464, 32.1044, -1.05329, -4.33992, 18.2626, 40.7261, 333.625, 
+-7.93034, 19.45, 57.6465, -755.812, 21.0434, 33.7346, 106.43, 
+268.848, 8.83568, -46.6535, -1.72494, 623.697, 231.072, 198.967, 
+469.976, 269.123, 68.4686, 316.445, 7.37585, 33.8574, 8.8682, 
+21.018, 10.5003, 67.5913, 1110.82, 295.222, 83.4115, 11.1847, 
+126.866, 373.091, 71.2689, 713.406, 58.4652, 22.5675, 232.293, 
+236.371, 469.914, 762.529, 103.91, 60.7067, 5.59537, 3355.81, 
+84.9986, 230.098, 272.078, 563.61, 24.53, 13.1461, 221.654, 274.996, 
+5.44171, 24.4863, 2227.03, 392.032, 508.608, 93.93, 31.5536, 
+31.0355, 3.83873, 230.849, 242.947, 13.9151, 3.29854, 1556.68, 
+1911.55, 146.58, 4013.99, -13.4229, 211.98, 72.7237, 186.692, 
+165.056, 214.073, 9.80107, 84.4112, 89.002, 26.9743, 11.6784, 
+169.962, 33.1578, 271.494, 23.4589, 233.138, 183.306), C = c(176.757, 
+77.9216, 33.0632, 14.6883, 46.1271, 57.2033, 164.926, 67.398, 
+37.6002, 10.1495, 622.901, 62.0314, 74.0299, 19.4069, 25.1962, 
+187.796, 82.8271, 61.671, -28.705, 239.039, 118.699, 68.5976, 
+9453, 44.7525, 126.374, 29.261, 35.842, 36.5703, 97.901, 34.4333, 
+52.6747, 82.4409, 77.1769, 32.2058, 24.6518, 118.632, 60.3028, 
+10.7195, 152.424, 150.249, 173.624, 599.857, 42.4559, -28.2104, 
+39.1968, 1693, 2670.94, 3822.94, 2961.39, 3739.82, 4788.63, 82.2737, 
+-0.597615, 44.8314, 206.137, 620.729, 436.198, 84.4842, 191.682, 
+64.3478, 79.7282, 237.773, 207.319, 97.155, 38.0971, 74.1949, 
+388.945, 23.294, 16.9304, 3.03659, -0.338279, 166.482, 169.273, 
+177.832, 58.2412, 600.494, -3.03599, 0.533814, 10.2753, 22.7978, 
+94.4468, 177.465, 28.9386, 18.9332, 120.461, 84.3285, 1208.68, 
+11.7631, 201.403, 16.3046, 1820.51, 18.7009, 8.06063, 17.7927, 
+4.91404, 64.3351, 9.33222, 495.373, 11.3434, -26.9727, 32.8212, 
+309.36, 132.574, 4.76155, 85.7358, 41.2689, 63.5624, 96.1371, 
+13.489, 40.0346, 288.847, 32.9084, 53.8278, 371.229, 68.3952, 
+128.63, 266.452, 269.956, 47.743, -0.199725, 67.7454, 30.8355, 
+394.639, 99.8759, 32.5865, 49.5398, 56.054, 78.8531, 85.9725, 
+-3.55993, 26.8936, 0.485286, 277.25, 60.7702, 36.151, 466.838, 
+-4.87448, 9.19057, 137.726, 117.944, 122.385, 91.1349, -9.44844, 
+90.8404, 78.8022, 2793.21, 217.035, 142.901, 58.8769, -25.6195, 
+16.2116, 472.011, 76.1839, 975.155, 25.4608, 23.3196, 3219.65, 
+98.2355, 11.5571, 62.0855, -3.89868, 0.364566, 133.15, 14.9364, 
+30.4366, 247.264, 230.803, 0.868223, 114.364, -1.38195, 202.254, 
+24.8141, 56.6022, 142.538, 404.582, 26.6696, 110.596, 159.432, 
+20.0713, 1981.21, 79.788, 20.2375, 32.2108, 78.4334, 534.38, 
+194.198, 268.142, 19.7106, 1151.71, 33.9701, 40.1148, 189.034, 
+458.814, 111.326, 243.659, 11.1631, 410.494, 64.8875, 86.9771, 
+150.6, 897.232, 70.4278, 41.771, 266.278, 3561.69, 96.4136, 139.54, 
+65.321, 1.92815, 70.2624, 23.7333, 334.227, 37.4708, 55.9757, 
+42.6704, 24.337, 56.2867, 462.89, 176.691, 6.97726, 12.3479, 
+61.623, -40.8948, 496.399, 12.4289, 16.7948, 234.34, 18.1656, 
+744.438, 52.0471, 26.1707, 277.678, 59.6709, 8.88736, 67.9387, 
+166.966, 38.5175, 2748.11, 285.982, 11.8812, 17.6829, 1051.91, 
+156.014, 48.2021, 159.216, 139.037, 18.6021, 45.0407, 180.731, 
+2.32048, 184.486, 16.5329, 105.691, 41.7953, 0.693056, 116.963, 
+26.7144, 244.615, 117.343, 108.422, 59.9884, 23.0708, 201.693, 
+373.406, 331.275, 2239.38, 114.994, 116.796, 628.728, 1887.55, 
+-81.7433, 2448.39, 8.64014, 5.43453, 255.595, 117.117, 76.3595, 
+-37.4766, 6.22211, 136.229, 89.6268, 50.2193, 77.6374, 95.2023, 
+98.8803, 175.198, 125.214, 2868.78, 173.548, 471.518, 404.532, 
+181.375, 39.4546, 103.158, 105.342, 387.073, 537.699, 75.7463, 
+2560.07, -0.373076, 12.8639, -12.5198, 15.1326, -117.8, 395.382, 
+3143.06, 1271.65, 721.257, 61.8619, 23.3659, 172.881, 28.6697, 
+171.244, 14.1655, 375.339, 840.046, 93.8486, 6579.89, 40.5256, 
+138.575, 62.4509, 109.496, 24.4152, 24.7544, 105.943, 71.9599, 
+331.429, 105.756, 1786.61, 128.158, 84.3728, 20.6126, 157.824, 
+1300.7, 48.2448, 229.14, 61.0324, 21.6207, 32.5197, 173.512, 
+33.0107, -3.57515, 38.8318, 2115.7, 2353.56, 37.2077, 26.4637, 
+204.545, 45.8613, 170.981, 324.006, 46.7089, 243.086, 84.3667, 
+312.187, 83.842, 7748.04, 1548.52, 131.897, 47.1247, 131.118, 
+4.11246, 124.225, 34.5025, 197.734, 91.6667, 22.7796, 84.4513, 
+143.789, 905.632, 179.091, 1.12619, 33.9309, 69.3337, 190.008, 
+51.8768, 21.6014, 26.3087, 55.8036, 2.06138, 629.873, 494.789, 
+1648.93, 627.546, 104.333, 9.70183, 196.457, 264.936, 30.9323, 
+23.3243, 2.87676, -56.3115, 40.8574, 29.4056, 243.143, 155.89, 
+368.955, 729.211, 331.715, 28.1446, 513.724, 123.675, -68.25, 
+15.495, 86.2276, 76.1181, 5.3182, 33.6867, 134.632, 48.2266, 
+24.8465, 0.541914, -19.0799, 12.4705, 64.7863, 362.379, 8.82454, 
+12.3041, 73.1326, 147.117, 40.8124, 50.4434, 76.3825, 264.597, 
+12.1591, -75.3722, 4.81662, 650.118, 239.454, 215.675, 206.716, 
+129.04, 1.6552, 240.097, 10.8357, 9.03269, 15.9011, 26.9514, 
+10.7637, 106.479, 301.017, 362.135, 72.0019, 55.6966, 174.68, 
+332.694, 388.184, 337.534, 18.5135, 12.4759, 118.672, 261.799, 
+207.092, 600.212, 192.576, 47.1807, 4.08804, 2498.19, 63.1878, 
+312.842, 326.4, 455.249, 1.25862, 24.361, 278.501, 324.997, 10.9836, 
+10.5946, 1666.93, 553.31, 634.472, 64.7392, 62.0543, 37.4184, 
+17.2002, 260.407, 185.728, 16.1287, 21.148, 1761.11, 1776.92, 
+257.1, 3288.88, -8.50769, 338.949, 66.6674, 336.641, 298.4, 195.258, 
+0.368562, 116.449, 16.639, 39.5593, 55.6773, 156.71, 31.7113, 
+304.809, 39.417, 355.204, 291.385), D = c(135.575, 93.3713, 28.7072, 
+12.3397, 70.9319, 69.9766, 161.469, 77.2207, 46.5272, 9.73639, 
+669.859, 54.4218, 54.5277, 20.6246, 46.5057, 210.58, 101.534, 
+93.2235, -27.9979, 236.428, 131.834, 55.6881, 8595.65, 43.902, 
+90.4021, 38.6436, 43.8173, 37.0274, 146.239, 17.5947, 55.7056, 
+42.4596, 107.861, 37.0137, 30.3256, 118.691, 63.5276, 13.9764, 
+118.693, 82.6372, 135.163, 426.569, 3.26054, -37.3464, 24.3987, 
+931.981, 1916, 2995.59, 1712.31, 2266.59, 3491.7, 51.4973, -8.47943, 
+31.2879, 116.343, 668.082, 560.846, 101.776, 202.534, 63.019, 
+102.178, 216.3, 217.761, 109.506, 35.9229, 103.339, 336.965, 
+31.0905, -15.2399, -0.903413, -14.1061, 248.735, 173.702, 117.493, 
+59.7341, 658.421, -5.98093, 11.4078, 12.9648, 24.8195, 124.794, 
+174.559, 19.3623, 26.6189, 113.723, 84.2596, 730.314, 8.62522, 
+134.993, 18.4485, 2612.13, 28.5711, 5.85333, 19.1999, 11.1325, 
+56.7737, -1.59376, 501.236, 13.8976, -23.0042, 37.1873, 403.88, 
+109.777, 10.3207, 67.3778, 47.4344, 55.8759, 108.988, 13.9802, 
+43.1862, 208.604, 2.65486, 48.6217, 465.519, 60.0952, 129.701, 
+250.405, 265.694, 36.3271, 17.8139, 60.2125, 28.2217, 362.904, 
+114.494, 16.9474, 45.4437, 52.1385, 40.8464, 81.6387, 0.849691, 
+21.6048, -2.29043, 190.222, 66.5821, 46.4369, 467.278, -0.835582, 
+18.1039, 115.949, 98.4812, 128.012, 67.5637, 11.2539, 77.5852, 
+91.8056, 3072.51, 192.841, 161.071, 40.22, 31.2705, -61.0733, 
+436.333, 60.0639, 1420.69, 41.971, 16.3495, 2453.11, 104.167, 
+13.7932, 89.1047, 4.4386, 8.19584, 89.7832, 14.4443, 54.3745, 
+249.8, 187.791, 6.62558, 127.032, -5.58777, 191.617, 17.9258, 
+78.5784, 148.488, 364.183, 46.72, 97.8402, 130.051, 11.396, 1414.58, 
+117.664, 26.8048, 35.6676, 51.7222, 382.114, 196.659, 264.509, 
+14.1542, 1326.21, 64.8629, 39.6481, 175.793, 529.609, 80.6403, 
+118.342, 12.7879, 358.9, 58.4443, 123.854, 126.945, 763.094, 
+63.7269, 27.4686, 229.632, 3045.6, 94.6744, 108.665, 65.6258, 
+-2.53157, 80.7287, 42.6169, 346.969, 37.3218, 57.9184, 48.6221, 
+32.3597, 17.1126, 475.902, 139.969, 2.52464, 13.3328, 50.5703, 
+8.63196, 724.818, 13.4701, 25.8875, 175.004, 26.7092, 628.343, 
+74.8407, 9.15695, 270.383, 43.9764, 10.0378, 66.9586, 159.203, 
+42.1448, 26.7318, 223.828, 3.47616, 15.4544, 1094.93, 112.442, 
+34.9869, 136.226, 173.703, 18.477, 40.0883, 153.399, 7.51711, 
+160.627, 11.9868, 215.151, 54.3479, 3.20111, 134.432, 44.7578, 
+371.959, 115.912, 58.0414, 89.2656, 25.785, 199.259, 238.99, 
+303.492, 3536.17, 129.548, 139.689, 2010.77, 2790.52, -77.6557, 
+3973.05, 7.47499, 1.14975, 254.188, 81.2887, 71.8499, -57.1317, 
+5.93088, 172.465, 79.6828, 29.3946, 50.5614, 73.798, 78.9586, 
+147.887, 106.963, 2915.08, 138.89, 385.115, 360.427, 115.041, 
+41.4827, 76.5293, 60.0774, 341.52, 761.418, 75.7623, 3682.01, 
+7.51078, 12.0506, -7.89719, 15.0758, 7.52292, 408.186, 4604.16, 
+2217.51, 505.422, 54.4029, 23.8248, 200.161, 26.5075, 116.292, 
+8.75973, 523.481, 968.806, 100.517, 4694.22, 64.1784, 119.122, 
+140.46, 63.7561, -22.7521, 12.7108, 116.718, 79.158, 322.951, 
+94.8393, 3026.42, 111.845, 74.4425, 44.2425, 97.9837, 2370.01, 
+29.0707, 180.18, 39.32, 24.889, 38.6347, 225.425, 31.989, 6.76259, 
+27.4242, 3134.73, 2830.51, 43.1838, 47.3681, 153.038, 19.7044, 
+224.179, 304.823, 82.7017, 226.486, 59.1124, 248.867, 88.2029, 
+1392.41, 1592.51, 72.3257, 43.4622, 128.944, 1.62062, 95.1037, 
+27.9533, 196.074, 86.6898, 20.6985, 86.8609, 104.507, 1146.21, 
+188.642, 0.59902, 41.9507, 92.7837, 224.49, 40.3968, 14.2285, 
+34.5061, 57.1294, 5.34327, 506.241, 522.548, 1160.22, 666.347, 
+97.9268, 17.7801, 218.052, 297.688, 32.3167, 19.5057, 26.6114, 
+-37.5517, 43.6972, 24.0573, 288.353, 185.134, 254.767, 677.218, 
+346.054, 22.2505, 390.636, 124.853, -65.7515, 21.0519, 80.5353, 
+73.7944, 7.61247, 29.269, 119.968, 17.3605, 20.3198, 10.4502, 
+-25.2877, 22.1264, 72.1742, 369.995, -5.68748, 11.8066, 50.6633, 
+173.014, -16.4234, 51.4102, 99.1137, 242.912, 9.02829, -77.6078, 
+7.24242, 528.138, 304.759, 189.418, 159.408, 179.094, 21.2023, 
+215.018, 6.69187, 0.00887041, 21.1965, 22.7721, 16.2251, 96.8354, 
+365.602, 347.427, -0.262678, 59.5886, 79.8423, 278.584, 145.429, 
+323.227, 54.4142, 10.4668, 76.9657, 284.822, 68.987, 825.444, 
+189.224, 40.9088, 1.28765, 2874.21, 69.2813, 288.84, 286.696, 
+481.875, -0.170312, 22.9568, 311.733, 331.046, 7.13579, 18.7409, 
+2532.58, 528.613, 548.603, 31.1731, 80.8461, 33.7246, 10.1153, 
+268.561, 155.212, 5.48352, 16.9418, 361.75, 179.567, 217.952, 
+4233.25, -13.5292, 212.173, 60.0119, 338.307, 315.376, 177.603, 
+1.57145, 166.478, 29.04, 46.9514, 42.201, 211.624, 36.6217, 340.978, 
+25.7452, 314.818, 270.719), E = c(64.4939, 24.3986, 5.94492, 
+36.8663, 56.1744, 49.5822, 236.976, 41.3488, 22.2475, 16.9028, 
+414.165, 29.0704, 54.9849, 25.0496, 15.3157, 137.39, 83.4986, 
+38.113, -29.9097, 152.327, 109.355, 56.396, 9198.53, 40.5637, 
+99.6214, 34.4854, 21.1038, 24.0568, 127.068, 30.9068, 36.449, 
+50.3563, 72.3561, 38.7689, 23.3383, 82.8794, 33.5234, 10.7876, 
+95.3272, 163.14, 193.159, 859.045, 11.4879, -45.8195, 38.9076, 
+2813.41, 3973.08, 4775.69, 3090.42, 4237.75, 4789.47, 76.4602, 
+5.07097, 27.6003, 41.1004, 571.461, 390.73, 96.9881, 190.287, 
+55.4916, 59.3796, 167.976, 186.738, 136.675, 30.0487, 43.4217, 
+218.95, 24.8622, 10.0734, 1.39476, 23.0263, 183.237, 102.385, 
+88.0268, 75.8551, 3378.38, 3.59555, 65.0242, 12.96, 99.2189, 
+89.2497, 121.01, 22.2028, 26.8139, 90.0344, 74.5531, 679.41, 
+13.4006, 117.134, 13.4128, 3201.35, 23.3641, -5.30554, 20.1253, 
+9.54839, 38.7718, -4.62199, 348.54, 13.8821, -18.3141, 17.2074, 
+306.792, 104.859, 12.6733, 94.0531, 21.6537, 43.6782, 89.4138, 
+13.6566, 38.0548, 189.276, 28.5149, 31.4913, 361.772, 62.0669, 
+152.595, 177.347, 153.814, 91.3033, 15.3481, 24.1763, 8.74242, 
+240.273, 138.468, 23.0748, 35.8972, 66.074, 44.1937, 52.9221, 
+25.4535, 11.5091, -23.6341, 138.393, 25.068, 22.5468, 407.637, 
+4.04739, 20.0476, 77.704, 82.5094, 63.1586, 81.2566, -14.8375, 
+83.8227, 92.7443, 3811.76, 193.545, 134.644, -17.3857, 19.9229, 
+7.74658, 340.509, 73.6392, 1432.34, 18.8084, 8.87588, 2627.62, 
+35.1561, 5.30396, 70.8928, -13.8029, 11.239, 114.716, 5.44362, 
+21.3368, 204.602, 136.36, -2.31789, 85.5356, -0.247811, 173.264, 
+12.6704, 90.7857, 104.594, 247.158, 4.83192, 69.3472, 89.6663, 
+20.5333, 1435.34, 31.4634, 47.8388, 21.6173, 36.6126, 304.094, 
+90.4853, 176.797, 5.51239, 1034.81, 42.2959, 31.9282, 561.815, 
+1445.61, 83.6597, 137.314, 20.7974, 284.287, 58.4877, 96.2139, 
+114.396, 572.889, 50.0257, 21.7261, 215.397, 4848.85, 138.355, 
+95.7016, 41.1985, -2.8474, 63.9182, 17.0448, 325.229, 66.8436, 
+43.8797, 22.1161, 26.9722, 17.6747, 416.37, 132.339, 1.41274, 
+8.88926, 27.3809, 6.57349, 1139.67, 7.90949, 16.9425, 161.962, 
+13.7585, 621.043, 94.3556, 8.18545, 198.797, 207.15, 13.595, 
+59.9965, 156.247, 37.4272, 1797.91, 173.597, -7.73911, 9.15676, 
+1813.15, 55.28, 44.1372, 139.674, 139.307, 5.67999, 12.0538, 
+199.397, 6.77999, 120.684, 14.8007, 385.285, -3.4299, 2.18153, 
+91.8316, 48.117, 367.658, 114.124, 65.8494, 65.9354, 7.48233, 
+143.672, 199.44, 657.109, 4029.17, 59.3436, 49.4573, 1927.59, 
+2961.98, -33.9927, 3411.82, 60.5111, 0.298467, 181.269, 74.6144, 
+37.7439, -110.18, 19.0457, 29.6359, 60.9489, 28.0187, 26.8489, 
+33.3419, 85.0067, 133.816, 137.412, 3241.26, 98.0283, 395.614, 
+184.099, 94.8942, 42.2762, 101.342, 40.6483, 253.774, 923.643, 
+25.4809, 3804.5, 17.1477, 16.7315, -17.8845, 7.19612, -99.2543, 
+328.887, 4042.05, 1991.19, 456.9, 35.7412, 22.631, 114.018, 19.7603, 
+118.914, 4.47381, 312.442, 141.333, 73.7581, 6317.23, 44.7439, 
+90.1649, 47.5125, 41.0167, -5.88861, -1.31689, 50.2078, 52.9975, 
+306.946, 55.2381, 2807.46, 62.2553, 56.1606, 18.2972, 71.7201, 
+2288.21, 16.0303, 192.889, 24.1359, 11.582, 35.1956, 138.472, 
+19.3633, 31.5201, 22.3016, 3295.13, 3040.62, 40.9435, 198.743, 
+166.185, 27.0079, 111.59, 289.5, 51.6072, 128.174, 116.62, 195.124, 
+94.2059, 1940.92, 1827.06, 58.5186, 45.1064, 124.442, 118.75, 
+94.8991, 1.10459, 101.25, 72.7004, 8.5148, 48.5702, 238.499, 
+1447.28, 122.661, 5.3293, 28.0415, 86.0212, 128.135, 76.4239, 
+12.8664, 30.3877, 19.3263, -8.55452, 403.789, 426.469, 2773.18, 
+1844.36, 82.3998, 13.0372, 153.673, 352.845, 23.6871, 15.78, 
+55.5372, -18.7618, 23.9722, 41.5831, 271.406, 120.728, 224.949, 
+541.299, 233.333, 22.2221, 254.824, 155.811, -35.171, 6.93843, 
+43.0696, 91.5986, 1.78595, 36.7053, 81.0342, 52.6775, 32.0319, 
+-14.4679, -24.2608, 21.3777, 62.3007, 286.02, 11.041, 8.48455, 
+68.3051, 128.355, 36.9841, 152.66, 37.0811, 168.305, -7.80055, 
+-37.1137, 9.36955, 753.432, 304.638, 180.115, 366.813, 162.324, 
+51.4895, 425.48, 11.9353, 37.1344, 11.3044, 15.0707, 2.81377, 
+87.062, 890.038, 275.697, 82.7545, 48.8611, 134.64, 442.328, 
+92.7822, 297.06, -4.19166, 23.5474, 210.476, 284.862, 326.488, 
+643.018, 149.103, 57.9264, -4.35968, 2422.79, 90.8871, 214.643, 
+214.658, 673.626, -14.3901, 23.2702, 253.467, 314.393, 14.1398, 
+21.0437, 2730.59, 458.75, 440.822, 101.206, 71.8985, 27.3093, 
+2.20914, 193.891, 125.925, 20.2388, 16.0322, 1773.4, 1622.36, 
+167.252, 4208.54, -1.83895, 194.467, 52.4202, 155.889, 170.929, 
+146.268, -3.25423, 92.3306, 28.2821, 36.1026, 52.9031, 105.939, 
+26.8284, 356.127, 14.4032, 238.684, 212.025), F = c(76.3569, 
+85.5088, 28.2925, 11.2568, 42.6756, 26.1262, 156.803, 37.978, 
+61.6401, 5.33328, 654.078, 19.5271, 58.0877, 12.4804, 16.6833, 
+104.159, 73.1986, 51.0869, -26.9004, 159.505, 98.1799, 31.3003, 
+8729.83, 28.5819, 59.8854, 15.9339, 26.0026, 19.8649, 65.0798, 
+19.4564, 27.137, 34.748, 104.56, 19.4119, 20.5827, 69.0769, 38.0418, 
+3.04198, 81.5155, 147.757, 163.458, 552.006, 13.402, -30.6321, 
+22.4197, 2773.8, 3533.69, 4276.28, 4859.32, 5339.43, 6045.84, 
+61.8061, 13.5139, 64.2732, 66.8357, 534.92, 557.232, 97.7246, 
+183.791, 74.0598, 72.8653, 158.024, 209.394, 66.7261, 42.101, 
+45.9945, 234.313, 12.8276, 12.8547, 13.4486, 17.9294, 129.778, 
+93.4386, 90.2193, 65.7247, 265.693, 2.95618, 1.60701, -0.761071, 
+25.1805, 113.248, 128.501, 13.2872, 33.0942, 143.403, 62.9061, 
+472.386, 9.46665, 146.648, 20.1751, 2055.84, 10.4128, 1.51498, 
+7.61478, 10.1273, 50.1046, 17.1919, 416.904, 16.3986, 316.922, 
+31.7997, 271.918, 140.767, 3.43293, 93.2234, 30.2287, 60.9735, 
+81.2301, 13.1852, 15.6828, 244.004, 8.03442, 41.195, 450.588, 
+101.569, 122.576, 203.771, 165.58, 47.3593, -0.578794, 40.8826, 
+19.258, 317.049, 95.6767, 35.6291, 37.5118, 9.52143, 26.7085, 
+57.821, 7.38804, 21.5466, -4.09123, 174.045, 26.0275, 28.2087, 
+372.743, 7.89114, 9.26315, 77.7341, 92.1451, 40.0276, 59.0001, 
+11.3105, 109.624, 71.8631, 2826.91, 183.907, 115.486, 30.823, 
+25.6218, 4.40317, 456.183, 42.8331, 1406.38, 9.25876, 21.9462, 
+3057.25, 43.3653, 13.7308, 45.042, -5.66411, 1.81244, 92.4059, 
+3.38841, 27.4057, 195.913, 170.641, 13.7318, 77.4835, 11.8705, 
+170.034, 27.2993, 48.4951, 112.256, 288.233, 15.8018, 90.4763, 
+135.063, 17.4997, 1447.35, 20.3943, 9.1535, 11.2232, 52.4492, 
+263.404, 88.8359, 240.531, 13.914, 952.742, 25.8131, 33.9627, 
+399.248, 981.156, 99.5194, 113.287, -3.55475, 321.253, 64.8132, 
+153.21, 108.544, 689.428, 40.1967, 24.1371, 219.8, 6103.53, 183.204, 
+117.629, 66.3195, 1.21957, 50.7251, 13.9721, 215.827, 33.5278, 
+29.0743, 26.98, 3.84226, 15.2119, 416.473, 94.0782, 5.65606, 
+6.8239, 29.7649, 33.117, 922.994, 2.95855, 25.7804, 182.436, 
+14.506, 558.625, 50.9544, 7.1015, 232.798, 176.539, 13.849, 55.0411, 
+112.844, 38.1649, 2629.76, 208.982, 8.91111, 3.69219, 2237.49, 
+87.4336, 29.7085, 92.6406, 108.641, 12.5881, 24.5561, 277.109, 
+0.0555992, 168.556, 21.9422, 242.008, 13.2175, -5.18207, 67.707, 
+18.8392, 200.762, 93.2498, 131.197, 38.8349, 11.7789, 150.893, 
+281.69, 697.327, 2363.54, 98.4533, 49.2495, 1184.74, 1743.97, 
+-146.388, 2625.96, -0.550366, -20.5783, 166.122, 111.555, 47.8556, 
+-13.3038, 10.5148, 96.0369, 50.6197, 17.8413, 29.8171, 29.9881, 
+68.2329, 338.401, 242.223, 3103.45, 51.3296, 407.96, 247.109, 
+131.532, 38.6406, 100.263, 14.9409, 363.97, 1696.09, 55.9993, 
+3141.21, 10.7468, 9.4833, -10.1759, 4.94772, -94.8137, 363.273, 
+3357.76, 1370.01, 1055.43, 37.2194, 11.6967, 151.487, 45.4293, 
+122.312, 9.85712, 312.931, 619.899, 86.0735, 6098.96, 35.2556, 
+118.982, 42.6033, 50.3781, 8.79439, 10.0094, 77.1799, 41.375, 
+356.719, 79.1635, 2399.43, 93.6127, 87.3683, 8.51886, 80.539, 
+1489.71, 23.1329, 196.416, 32.6198, 28.1255, 27.9306, 120.298, 
+36.3136, -6.53911, 11.5249, 1818.98, 2629.42, 20.5239, 25.569, 
+176.01, 16.4979, 106.83, 255.7, 47.4432, 202.329, 148.584, 166.122, 
+72.5939, 1147.63, 1571.36, 64.2836, 40.9947, 149.732, 6.98837, 
+76.7431, 32.6061, 241.995, 193.953, 71.849, 43.091, 231.441, 
+1173.24, 148.46, 6.25035, 27.2836, 61.9131, 116.848, 61.847, 
+26.8595, 6.40947, 30.8911, 0.516717, 420.763, 460.661, 1361.44, 
+591.884, 53.3154, 11.9007, 168.517, 250.081, 17.9015, 16.7667, 
+7.98321, -32.7506, 44.1567, 33.2017, 203.785, 118.136, 30.1383, 
+623.624, 321.933, 15.0102, 304.391, 109.031, -35.2096, 7.28756, 
+68.1562, 76.94, 3.84083, -8.66032, 74.518, 45.4732, 5.2473, 0.674253, 
+-38.8464, 58.6034, 54.2982, 400.585, 1.74185, 11.5801, 59.9533, 
+165.597, 41.3708, 49.7561, 53.7959, 173.169, 1.11088, -44.2055, 
+0.345534, 788.229, 233.738, 193.153, 503.509, 170.926, 47.5674, 
+250.997, 5.58086, 23.2777, 19.559, 32.0773, 10.4892, 84.8054, 
+591.492, 310.91, 89.6526, 62.3684, 388.848, 401.377, 87.3499, 
+492.338, 28.0653, 9.77436, 165.732, 180.625, 486.538, 543.039, 
+110.879, 53.3282, -2.68911, 2656.67, 48.7383, 212.146, 226.983, 
+507.041, -4.7378, -7.00055, 303.127, 344.683, 12.0315, 20.7854, 
+2086.7, 136.541, 442.067, 55.9435, 39.8863, 38.2014, 6.7952, 
+184.694, 172.747, 11.6976, -5.41524, 1350.98, 1425.73, 166.823, 
+3207.93, -5.10412, 250.141, 35.7243, 188.316, 202.637, 156.022, 
+-13.1372, 78.0865, 51.5613, 33.0572, 43.5617, 171.992, 38.991, 
+279.015, 27.166, 205.697, 225.357), G = c(160.505, 98.9086, 30.9694, 
+23.0034, 86.5156, 75.0083, 211.257, 110.551, 33.6623, 25.1182, 
+704.781, 56.3164, 96.632, 21.9102, 93.1759, 296.287, 110.631, 
+69.0242, -45.6312, 316.931, 177.533, 84.8437, 10085.3, 49.2893, 
+129.419, 55.8445, 47.7015, 57.4157, 262.579, 18.5628, 59.6477, 
+26.4046, 103.898, 42.146, 42.6331, 147.797, 60.9828, 9.54646, 
+152.298, 169.078, 145.287, 499.943, 20.5481, -56.7485, 67.8308, 
+1331.06, 3001.52, 3922.8, 4656.49, 5809.61, 5387.85, 84.3291, 
+0.756365, 54.4841, 73.8793, 622.534, 510.803, 84.813, 146.505, 
+51.5387, 80.7284, 194.901, 226.182, 56.4972, 40.503, 95.5123, 
+367.258, 68.4181, 10.4643, 5.74156, 35.7209, 270.832, 183.729, 
+117.556, 93.8117, 2347.97, -6.84587, -3.51601, 16.7883, -6.77262, 
+143.695, 173.604, 25.7165, 22.5593, 95.8189, 100.242, 875.514, 
+5.64484, 159.059, 12.8777, 1445.57, 56.5075, 6.67706, 20.3672, 
+16.6175, 71.0378, 0.121618, 770.457, 16.0536, -21.241, 35.6843, 
+289, 130.207, 23.7289, 76.6311, 28.5373, 41.6551, 103.677, 23.7724, 
+24.5001, 227.616, -17.4642, 88.1088, 390.704, 46.2814, 241.579, 
+239.095, 246.333, 68.2692, 3.72669, 43.3918, 34.893, 430.311, 
+139.544, 18.7085, 39.5034, 65.418, 60.8044, 87.8751, 20.2779, 
+30.6158, -1.06324, 181.367, 59.5764, 46.5235, 526.11, 11.1662, 
+24.8809, 125.538, 107.588, 102.268, 71.5763, 19.1748, 97.0634, 
+86.1694, 2280.98, 185.979, 143.129, 59.7806, 20.6691, 4.16593, 
+458.62, 80.0684, 1405.23, 114.141, 15.0017, 2784.51, 67.3431, 
+12.9932, 82.6335, 2.46988, 8.19852, 126.301, 58.2465, 21.3715, 
+342.757, 92.0834, -0.662, 132.709, -6.37538, 173.21, 7.82848, 
+145.062, 126.06, 389.761, 28.5087, 95.2023, 151.083, 18.2265, 
+1746.7, 81.1804, 13.7397, 33.0161, 80.331, 500.006, 168.432, 
+199.011, 22.4592, 1266.08, 96.4681, 52.4657, 165.172, 439.903, 
+58.831, 232.393, 20.3798, 390.69, 76.8212, 102.604, 115.513, 
+694.082, 95.4191, 31.7582, 292.824, 4843.85, 243.369, 150.37, 
+73.6126, 13.5536, 84.8325, 44.2015, 397.304, 52.6378, 56.2434, 
+58.5563, 48.2016, 22.27, 533.109, 180.547, 10.7022, 15.3744, 
+66.0203, 2.8568, 380.877, 23.7808, 23.4922, 192.561, 18.2562, 
+395.242, 160.002, 25.6545, 277.682, 44.8341, 3.6194, 64.0872, 
+145.975, 51.5657, 143.639, 241.318, 16.6696, 22.2736, 979.66, 
+101.48, 14.9272, 194.998, 272.543, 30.1638, 38.2265, 156.142, 
+4.26759, 162.979, 25.2755, 123.551, 23.4759, 2.36219, 141.662, 
+36.5043, 675.211, 135.162, 74.976, 206.357, 20.2907, 205.251, 
+318.483, 363.072, 1549.66, 74.9918, 77.6235, 730.908, 2267.07, 
+-15.9843, 2228.87, -1.32209, 16.2259, 287.157, 113.905, 28.5838, 
+-71.7309, 6.32725, 59.1934, 103.09, 124.573, 168.993, 274.755, 
+452.09, 306.868, 62.5394, 2406.87, 759.884, 520.693, 322.543, 
+99.4452, 69.2543, 82.2784, 47.2046, 302.587, 425.728, 70.1185, 
+2643.65, 25.8529, 15.5019, -27.9583, 21.1836, -159.404, 411.162, 
+1610.64, 847.52, 619.837, 55.6259, 11.2342, 129.321, 29.6711, 
+128.191, 2.12969, 458.098, 967.869, 139.49, 6744.25, 61.7619, 
+125.268, 63.4657, 70.7754, -29.0252, -4.19204, 91.809, 69.6631, 
+308.223, 148.843, 1253.53, 95.4669, 58.6777, 7.81241, 103.607, 
+1040.22, 28.6589, 235.102, 44.9815, 24.0025, 19.831, 212.84, 
+31.8595, -26.5714, 32.8036, 1424.39, 1609, 42.2412, 3.4899, 146.294, 
+31.1852, 70.3539, 367.704, 74.8138, 210.733, 73.2453, 290.952, 
+154.544, 1375.25, 1880.28, 115.808, 67.2951, 125.921, 2.02108, 
+142.316, 36.4292, 130.832, 87.7579, 13.7819, 62.8137, 131.189, 
+1762.44, 234.36, 2.26835, 24.7566, 130.982, 267.213, 50.1711, 
+11.7085, 45.9508, 47.0628, -5.0788, 642.114, 690.187, 1158.76, 
+224.69, 129.032, 10.1764, 219.981, 320.364, 48.4923, 22.6838, 
+4.00794, -51.6805, 40.6299, 62.9865, 405.183, 213.955, 349.216, 
+787.593, 375.517, 52.7782, 576.754, 133.512, -81.2397, 30.8676, 
+93.9739, 116.764, 0.861936, 27.6728, 110.052, 89.8018, -26.8523, 
+-29.9146, -33.5474, 49.7079, 33.9368, 323.446, -2.84178, 19.3021, 
+63.4884, 134.071, 91.5641, 27.7786, 94.1995, 219.683, 4.70264, 
+-76.1152, -7.59186, 770.503, 487.319, 190.619, 146.871, 193.463, 
+1.49736, 433.626, 8.95326, 8.46145, 32.2166, 30.7369, 82.9398, 
+163.432, 487.778, 308.937, 30.117, 41.7749, 39.3079, 288.488, 
+121.753, 478.74, 36.5597, 17.859, 50.2198, 371.859, 670.302, 
+2002.02, 224.547, 64.1557, 0.410534, 1522.33, 91.8752, 293.092, 
+308.702, 576.066, 6.09243, 32.27, 284.832, 318.128, -0.548151, 
+16.6889, 722.22, 571.163, 667.587, 45.1672, 90.5216, 47.5207, 
+17.3392, 314.547, 112.627, 11.9066, 15.2477, 1232.75, 2182.13, 
+212.534, 2586.28, -28.1626, 273.352, 88.6858, 235.716, 288.56, 
+147.061, -52.4786, 182.97, 36.2152, 33.1716, 58.5177, 181.279, 
+70.0673, 393.73, 35.3598, 400.955, 267.019), H = c(65.9631, 81.6932, 
+14.7923, 16.2134, 30.7927, 42.3352, 235.994, 47.769, 31.4423, 
+38.7576, 472.087, 36.2044, 52.731, 23.772, -2.286, 110.536, 116.742, 
+51.7352, -62.9474, 152.188, 124.795, 33.4283, 5398.15, 7.59488, 
+52.935, 20.0904, 23.8035, 18.3142, 67.9807, 5.85058, 26.2214, 
+35.91, 61.4678, 26.795, 20.733, 53.9483, 40.4661, 5.0816, 122.23, 
+255.646, 144.067, 701.339, -18.0681, -50.5899, 46.573, 3409.56, 
+3670.05, 4113.84, 4652.41, 5529.77, 4934.23, 72.5007, 21.6755, 
+49.6503, 123.648, 645.022, 405.539, 174.681, 138.473, 76.3049, 
+41.9885, 175.705, 186.137, 61.5467, 32.3343, 28.5536, 190.158, 
+19.6626, 1.0001, 19.8489, -3.43857, 126.72, 113.821, 124.49, 
+48.9977, 1474.59, 6.59068, 26.293, 15.1744, 31.0988, 164.839, 
+105.427, 15.3515, 7.64309, 75.7023, 58.9412, 426.069, 22.7863, 
+93.8675, 36.6998, 3752.44, 15.5375, -37.2626, 40.972, 2.83778, 
+29.8097, 7.85899, 383.393, 8.59187, -14.6747, 22.0106, 314.445, 
+91.1368, 3.31941, 55.9907, 13.6873, 85.1964, 75.6375, 24.9673, 
+-19.4126, 154.493, 9.51653, 7.00295, 172.512, 54.844, 206.315, 
+114.929, 161.489, 18.9867, 17.967, 20.58, 16.5985, 317.839, 68.4194, 
+0.632673, 24.8422, 42.741, 55.0761, 29.1132, -9.59971, 1.92886, 
+24.2057, 212.31, 23.1776, 46.685, 327.569, -19.7231, 16.127, 
+102.909, 89.4731, 88.002, 55.5039, 3.78602, 98.7201, 59.1011, 
+3677.21, 168.304, 97.5727, 62.7741, 6.98695, 7.7722, 287.765, 
+31.1771, 1034.85, 41.1973, 14.484, 1973.97, 26.3003, 13.0387, 
+70.2444, -23.7586, 3.61405, 144.866, 12.9588, 12.1978, 228.561, 
+69.1006, -12.9076, 33.1189, -12.0223, 107.954, 20.2041, 56.6382, 
+72.1951, 231.902, 4.51244, 59.7258, 97.1518, 14.8023, 1446.33, 
+31.1922, 17.7331, 23.9397, 34.4429, 275.279, 89.5355, 150.161, 
+12.1368, 733.126, 33.8044, 32.9493, 428.544, 908.692, 55.2216, 
+122.623, 12.5489, 234.033, 12.3606, 79.2471, 132.363, 477.632, 
+48.276, 18.9685, 170.293, 3218.18, 133.185, 71.059, 42.2979, 
+17.1591, 62.4136, 20.5905, 328.759, 23.5485, 28.9632, 32.4677, 
+15.6095, 29.6611, 263.733, 83.1204, 10.8203, 0.0645667, 20.8901, 
+17.402, 2317.54, -1.71971, 15.5579, 175.414, 17.9223, 132.269, 
+49.3328, 20.0075, 161.866, 96.6339, -1.22723, 28.5114, 69.8331, 
+19.9071, 3594.62, 184.264, 36.2862, -0.250289, 2657.7, 66.4338, 
+45.9629, 158.683, 84.2689, 11.0174, 12.8382, 461.884, 1.2479, 
+186.49, 40.9668, 410.214, 35.1459, 7.58523, 86.1551, 74.4591, 
+147.043, 50.2503, 155.398, 38.0677, 17.9086, 81.876, 262.617, 
+923.903, 3372.24, 65.0195, 56.1913, 1989.38, 3297.89, -48.9684, 
+3520.01, 21.7884, 29.6134, 186.365, 93.1961, 103.971, -22.6964, 
+8.73567, 93.5217, 99.9293, 319.164, 444.212, 623.513, 437.966, 
+126.152, 79.5352, 4437.69, 981.041, 287.177, 166.311, 91.5453, 
+43.8078, 137.337, 17.6704, 163.841, 1149.64, 21.6281, 4237.01, 
+-4.72068, 6.06603, -8.07375, 31.8066, -59.8348, 267.843, 4094.25, 
+2536.1, 392.48, 30.4019, 16.2788, 103.038, 23.8032, 63.9377, 
+-3.16035, 280.371, 679.892, 60.1188, 5272.74, 36.681, 77.0613, 
+9.46983, 82.3953, 23.5921, 7.82025, 53.0366, 38.2291, 162.251, 
+71.3313, 3289.3, 71.1382, 36.5156, 10.9756, 96.3876, 2250.24, 
+23.9772, 155.927, 11.0189, 32.6098, 26.072, 63.7697, 10.0424, 
+54.173, 28.7016, 3204.18, 2521.5, 14.6506, 45.914, 140.744, 55.0265, 
+55.2523, 173.877, 40.5893, 88.8999, 244.048, 208.946, 84.1878, 
+1234.61, 1959.86, 100.845, 34.196, 121.971, 6.00279, 65.4532, 
+25.6252, 205.105, 145.486, 14.5797, 28.9883, 418.138, 1054.41, 
+192.451, -6.77577, 3.52808, 43.4975, 133.57, 29.8818, 5.54331, 
+28.0327, 17.1614, 4.50518, 438.525, 568.957, 1341.85, 823.083, 
+11.0206, 5.28213, 145.935, 238.488, 20.9897, 17.3526, 5.4934, 
+-24.8509, 27.9785, -11.0401, 170.731, 60.0793, 147.971, 354.996, 
+333.375, 37.7786, 352.022, 115.454, -30.8254, 9.93972, 47.3987, 
+68.3317, 67.7091, 49.2164, 77.5302, 36.9154, 8.39283, 4.92543, 
+-20.5218, -0.730059, 47.7373, 518.214, 9.22062, -24.8561, 49.1153, 
+105.805, 29.2637, 15.3461, 45.0949, 179.074, 12.3872, -16.1917, 
+9.87644, 785.672, 164.981, 181.252, 397.135, 215.004, 56.6237, 
+304.372, 25.614, 65.028, 8.81296, 18.3069, 9.54185, 25.4821, 
+1084.56, 225.453, 44.6071, 38.2034, 47.3505, 405.11, 80.4995, 
+317.942, 19.5663, 18.4398, 160.898, 180.688, 313.737, 1445.36, 
+99.1103, 48.6681, 12.3674, 2653.13, 83.7136, 229.497, 249.714, 
+488.489, 54.2498, 23.6874, 174.373, 258.626, 72.8444, 5.42297, 
+3475.67, 259.205, 396.013, 56.4187, 31.3486, 48.0814, 13.669, 
+168.408, 159.795, 29.286, 0.992278, 1970.63, 2206.93, 93.7185, 
+4695.35, -8.87077, 220.34, 81.2755, 132.113, 159.9, 87.984, -9.8868, 
+88.2923, 38.6535, 7.80274, 8.33834, 164.635, 37.4181, 173.935, 
+21.2248, 218.935, 213.479), I = c(56.9039, 97.8015, 14.2399, 
+12.0375, 19.7183, 41.1207, 175.64, 24.7875, 23.1008, 31.4041, 
+456.496, 34.4118, 35.4588, 24.184, 9.00485, 123.767, 149.329, 
+48.4943, -31.4359, 182.803, 86.0768, 42.3172, 7851.25, 23.629, 
+64.1861, 24.7383, 11.3737, 13.9659, 67.9566, 26.2278, 8.82339, 
+25.1295, 95.496, 20.6417, 25.9931, 55.5277, 39.5032, 6.61344, 
+91.9547, 135.592, 138.774, 662.183, -71.7969, -43.3654, 53.0483, 
+2500.59, 3411.11, 3853.04, 4628.45, 5465.07, 5404.54, 62.1373, 
+48.0582, 49.8266, 46.3265, 539.881, 420.27, 121.429, 101.841, 
+67.6596, 49.3447, 155.066, 240.654, 30.8823, 25.8423, 35.7027, 
+208.684, 14.2983, 2.92394, 15.392, 7.00862, 159.539, 77.6879, 
+71.3888, 44.6516, 966.339, 18.009, 14.3594, 16.2639, 32.865, 
+135.098, 124.688, 10.4324, -158.624, 77.4182, 52.9351, 541.812, 
+9.68571, 110.694, 21.3595, 3766.64, 11.7948, -41.5181, 32.1378, 
+18.3991, 44.214, 25.6868, 332.747, 20.8813, -22.3464, 41.9897, 
+372.205, 89.3285, 0.688826, 47.3014, 7.46991, 87.8979, 69.1955, 
+24.0044, -5.65372, 178.113, -27.5173, 16.9593, 308.891, 51.437, 
+180.81, 116.305, 257.957, 28.8561, 41.9913, 9.78746, 32.055, 
+337.631, 78.1148, 14.6921, 15.7892, 72.4446, 46.0098, 38.0461, 
+-7.25167, -77.7694, -6.12358, 151.401, 50.853, 31.6659, 375.203, 
+-15.4885, 23.6577, 82.6901, 79.2893, 77.364, 64.7703, -5.01044, 
+70.8695, 109.516, 3949.6, 143.33, 95.621, 43.3468, 17.4263, 0.0576889, 
+316.743, 36.0296, 1039.75, 20.8679, -7.13015, 2136.31, 32.4043, 
+35.4223, 57.7617, -19.3941, 15.0063, 137.011, 15.0828, 10.3074, 
+209.233, 26.6425, 75.8138, 42.3457, -12.372, 129.54, -0.808758, 
+115.298, 111.984, 277.088, 48.9072, 60.702, 89.4102, 11.8831, 
+1280.76, 7.54955, 21.8121, 26.8602, 27.1097, 276.223, 69.8056, 
+141.762, 9.92208, 471.624, 18.7722, 34.121, 330.872, 803.91, 
+89.2639, 202.322, 17.1598, 204.002, 19.8715, 69.9369, 139.112, 
+475.68, 38.5653, 10.3207, 179.287, 5019.1, 131.735, 96.5819, 
+52.7207, 118.578, 66.3749, 11.2237, 262.136, 37.3264, 37.2226, 
+44.4505, 9.80769, 28.258, 311.98, 145.188, -13.876, -6.60292, 
+27.446, 52.3413, 1437.92, 14.9031, 6.43931, 191.186, 62.2038, 
+533.959, 52.2601, -0.812122, 163.045, 97.5818, 4.27843, 49.925, 
+117.116, 26.2354, 107.634, 183.655, 44.0061, 10.6966, 1861.3, 
+68.6117, 55.3026, 120.201, 143.756, 24.2935, 7.63267, 273.163, 
+6.46505, 130.595, 24.3482, 570.118, 10.9965, 18.2516, 73.701, 
+42.386, 281.665, 51.0993, 156.168, 71.8904, 15.0406, 96.8189, 
+267.787, 1033.72, 4213.76, 63.4817, 29.8674, 2468.85, 3093.27, 
+-23.3657, 4172.56, 54.6128, 25.3713, 141.131, 50.7424, 64.7935, 
+39.3548, 9.35458, 97.9677, 77.4194, 36.3783, 56.15, 80.5102, 
+160.375, 422.177, 186.838, 4189.58, 261.971, 290.421, 145.819, 
+110.678, 30.1821, 62.6842, 32.8513, 212.074, 1073.22, 14.7815, 
+4803.12, -52.8976, 9.0613, -7.8137, 12.2626, -79.6776, 256.768, 
+4118.03, 2597.5, 487.991, 32.4547, 22.1637, 87.9791, 31.6146, 
+66.199, 23.917, 219.436, 676.787, 66.6259, 6602.19, 28.4735, 
+96.0434, 31.4449, 51.5631, 62.1528, 14.7575, 38.9174, 50.5804, 
+226.292, 1.33535, 3972.17, 79.3392, 82.5123, -8.05703, 57.3154, 
+2779.82, 50.7459, 362.999, 31.716, 45.9685, 32.3122, 83.0068, 
+17.4939, 25.959, 15.3953, 3793.5, 2909.96, 28.6528, 32.7872, 
+125.396, 45.0034, 59.3125, 207.221, 67.8755, 95.7511, 134.838, 
+221.671, 92.718, 953.289, 1358.65, 115.183, 42.0618, 260.924, 
+-5.67053, 106.906, 15.4698, 86.5805, 138.179, 6.36567, 42.2539, 
+263.136, 1555.94, 152.362, -0.750177, -10.2169, 39.3872, 10.9171, 
+38.3977, 24.2579, 37.0798, 22.001, -68.9469, 364.56, 513.066, 
+1020.6, 725.306, 74.2402, 4.32573, 152.556, 149.95, 30.4155, 
+9.87658, -2.83936, -14.2585, 37.5048, -4.54525, 231.427, 40.9725, 
+179.04, 472.655, 298.223, 30.6501, 226.595, 217.446, -11.2347, 
+7.99247, 44.5376, 34.1872, 56.2715, 65.826, 68.4123, 33.5924, 
+27.0132, -0.932949, -26.6856, 22.9653, 54.7115, 385.224, 52.8945, 
+4.19935, 39.7645, 126.784, 10.7498, 25.48, 30.5649, 230.8, -49.7404, 
+-19.0299, 0.534617, 761.77, 199.883, 145.558, 381.822, 330.34, 
+130.641, 331.091, 19.2022, 61.6367, 3.28127, 21.4743, 21.9916, 
+58.4991, 676.788, 206.801, 256.74, 53.8124, 250.424, 275.746, 
+49.6752, 682.774, 5.10634, 24.2536, 265.575, 259.757, 114.583, 
+789.964, 113.886, -120.217, -17.5734, 3283.41, 77.2334, 190.75, 
+246.745, 438.071, 17.5467, -6.3988, 190.05, 250.068, 65.1947, 
+22.333, 2626.26, 342.48, 354.569, 97.9919, 39.7226, -4.73579, 
+71.337, 140.925, 253.267, 39.1377, -0.0626833, 2094.61, 2349.06, 
+100.454, 5027.34, -5.0921, 197.648, 33.0178, 154.763, 215.446, 
+74.4776, -30.5011, 71.1762, 78.434, 9.63535, 38.429, 95.5045, 
+35.9276, 350.806, 41.0651, 155.007, 147.564), J = c(135.608, 
+90.4838, 34.4874, 4.54978, 46.352, 91.5307, 229.671, 66.7302, 
+39.7419, 0.398779, 601.335, 54.0765, 60.2642, 29.7032, 13.1253, 
+165.21, 113.737, 66.3324, -26.3253, 275.02, 143.596, 124.882, 
+9906.75, 57.0429, 101.061, 38.8725, 40.5822, 37.3897, 85.4896, 
+-16.7811, 58.4851, 49.3878, 74.32, 31.5766, 36.5884, 127.344, 
+29.8857, 16.9064, 129.385, 134.197, 161.823, 603.143, 14.8066, 
+-24.1965, 49.6252, 1397.65, 2582.35, 4196.47, 1871.55, 2697.63, 
+3957.01, 52.7505, -1.9, 33.6619, 105.523, 538.821, 404.586, 82.7721, 
+231.526, 65.5417, 103.837, 254.894, 167.249, 63.5263, 33.6277, 
+82.7237, 447.998, 22.9679, 17.0239, 6.46696, 14.6832, 173.033, 
+173.092, 236.388, 95.0014, 1603.25, -4.79112, 14.3931, 12.9168, 
+45.525, 123.521, 160.284, 63.7235, 52.2413, 115.725, 76.4369, 
+647.946, 10.8287, 196.504, 30.8472, 2082.26, 24.9831, 7.45908, 
+29.2904, 3.96332, 63.3964, 5.05391, 523.434, 3.81431, -26.9582, 
+25.5166, 272.893, 104.55, -3.29841, 29.0413, 34.7569, 123.341, 
+136.982, 21.1208, 33.4306, 252.045, 28.2319, 46.8118, 460.704, 
+36.2471, 140.332, 322.058, 301.488, 28.6611, 17.8804, 69.2656, 
+30.5353, 428.04, 89.2726, 21.6357, 40.5838, 64.8148, 81.0943, 
+89.0303, 9.78984, 31.5737, -64.844, 181.883, 69.0185, 36.0617, 
+396.731, -5.39451, 18.3907, 135.384, 99.2002, 102.87, 97.414, 
+815.247, 102.809, 87.5921, 3294.23, 293.865, 170.835, 57.4489, 
+14.6789, 20.4225, 467.575, 65.7655, 1022.23, 36.5604, 17.9342, 
+2621.21, 69.9044, 5.62125, 61.0467, 7.16121, 8.74683, 159.503, 
+-6.5198, 30.0345, 215.707, 242.766, 9.23312, 122.68, -3.09805, 
+230.551, 25.0568, 73.4859, 148.278, 309.373, 29.2142, 133.58, 
+161.551, 25.4871, 1284.19, 110.777, 27.8657, 33.4392, 99.1692, 
+382.291, 180.04, 290.715, 26.878, 1354.88, 49.6606, 32.0053, 
+100.544, 275.601, 139.466, 145.483, 18.9868, 350.785, 62.5827, 
+142.035, 166.257, 824.404, 54.5118, 41.2395, 214.626, 2876.39, 
+117.19, 145.883, 77.1433, 21.0514, 88.9109, 35.9333, 342.005, 
+31.9545, 92.5985, 53.7139, 21.4681, 27.0079, 421.99, 191.869, 
+10.0729, 24.6545, 73.4274, -5.67084, 508.396, 16.2005, 20.4873, 
+199.64, 20.8818, 602.088, 53.0939, 11.985, 283.946, 33.3808, 
+7.65265, 79.7055, 179.645, 71.8716, 2280.1, 271.502, 18.3756, 
+16.292, 899.497, 106.102, 36.3051, 172.514, 84.6076, 14.9555, 
+42.3853, 76.7314, 9.74661, 177.697, 28.1345, 79.7277, 46.0504, 
+3.37234, 173.442, 37.7323, 281.782, 192.507, 65.114, 54.3543, 
+28.8901, 207.512, 302.66, 312.493, 2511.98, 115.631, 84.6329, 
+767.382, 1931.97, -74.91, 2442.8, 6.76813, 9.87214, 280.934, 
+164.196, 45.6826, -55.5401, 11.0881, 126.062, 188.277, 17.0563, 
+95.9991, 148.692, 109.747, 149.315, 464.839, 2018.08, 295.362, 
+520.54, 361.875, 118.235, 39.8868, 76.292, 52.8225, 393.946, 
+411.312, 82.4469, 3684.05, 5.70422, 15.3688, -18.2261, 20.1009, 
+-139.096, 322.853, 3536.29, 1415.81, 782.34, 58.8639, 19.9128, 
+172.436, 37.7876, 145.228, 8.84162, 527.972, 978.775, 115.247, 
+3620.29, 39.7757, 117.731, 73.8482, 82.0633, -8.08212, 8.88042, 
+114.975, 74.6192, 412.158, 116.883, 1723.88, 140.51, 55.4878, 
+29.5934, 126.615, 937.356, 25.1989, 80.04, 8.7691, 21.9003, 76.7322, 
+310.711, 35.1739, -11.3853, 31.0779, 2667.19, 2861.65, 55.9846, 
+24.2809, 201.009, 37.3568, 245.946, 321.117, 55.7212, 248.928, 
+83.1845, 301.538, 65.4351, 1978.58, 1469.72, 128.82, 51.2861, 
+129.685, -17.8222, 135.186, 16.9915, 148.667, 68.2773, 35.807, 
+130.481, 63.6107, 1220.17, 162.351, -0.850396, 29.6177, 65.2407, 
+199.876, 45.451, 17.4884, 1687.26, 65.1685, -0.458492, 640.976, 
+443.544, 1000.16, 530.158, 92.305, 16.7319, 211.431, 421.328, 
+42.7661, 23.1612, 19.5893, -41.9418, 67.1385, 24.0513, 278.235, 
+207.151, 354.466, 796.341, 370.781, 12.3542, 340.021, 101.469, 
+-77.2604, 20.2691, 90.9995, 88.3706, 11.782, 31.0455, 105.789, 
+87.4514, 20.9132, 2.51492, -21.3631, 18.128, 97.4119, 289.648, 
+-0.886138, 6.81447, 81.1169, 197.282, 25.0956, 42.3875, 108.956, 
+231.877, 11.0389, -81.2323, 7.01839, 732.505, 264.916, 224.387, 
+218.727, 161.252, 9.47757, 354.758, 11.3622, 18.4517, 28.7067, 
+31.1141, 27.7379, 123.108, 383.613, 297.234, 11.0615, 90.0501, 
+89.7434, 345.844, 129.75, 365.013, 29.9642, 33.6507, 64.2794, 
+272.773, 265.781, 752.182, 223.423, 50.9474, -4.21796, 1864.68, 
+43.8291, 270.01, 318.279, 587.201, -5.85108, 23.5828, 287.82, 
+330.953, -2.55689, 16.6618, 1450.23, 567.114, 589.9, 78.5015, 
+39.0382, 42.769, 29.0629, 276.211, 135.465, 3.88573, 12.61, 912.208, 
+663.228, 288.022, 3034.4, 189.179, 286.524, 62.3556, 379.114, 
+292.434, 197.347, -4.49651, 120.196, 27.3089, 59.2932, 68.8523, 
+178.683, 37.8029, 285.409, 25.2501, 320.904, 258.658), K = c(63.4432, 
+70.5733, 20.3521, 8.51782, 39.1326, 39.9136, 222.287, 62.9876, 
+35.1225, 2.98167, 674.334, 48.572, 90.2266, 19.6438, 7.90277, 
+172.95, 74.9809, 65.8276, -18.7649, 217.385, 104.273, 41.7587, 
+9269.15, 46.7404, 59.8996, 17.0458, 41.1433, 19.2095, 113.046, 
+9.25781, 31.0843, 23.1894, 80.0615, 22.9088, 19.8219, 64.5628, 
+1.59616, -3.92957, 106.196, 198.033, 242.284, 780.726, 21.2847, 
+-37.9727, 33.1548, 3225.72, 3930.01, 4756.24, 5051.09, 5411.19, 
+5341.82, 48.9417, 18.8431, 77.9987, 61.1681, 579.578, 398.83, 
+87.6531, 141.597, 54.4746, 44.0052, 148.141, 201.392, 88.0201, 
+15.68, 32.9481, 203.989, 10.3677, 11.4256, 19.3874, 37.8795, 
+170.047, 90.0128, 109.125, 42.046, 389.255, 6.18134, 51.0467, 
+22.6883, 74.2571, 144.772, 122.08, 3.81317, 26.7613, 64.7226, 
+72.9707, 642.128, 1.42032, 107.479, 27.3876, 4332.08, 12.988, 
+-17.4797, 27.6168, 25.2248, 35.1496, 2.71006, 412.996, -3.03517, 
+-23.2741, 13.488, 429.321, 119.51, -0.0278592, 63.9798, 32.4618, 
+46.5545, 89.1795, 57.5241, 14.5249, 209.735, -1.74408, 29.3106, 
+369.08, 43.4709, 173.913, 138.194, 119.037, -29.4263, 6.58678, 
+50.6164, 25.5873, 368.14, 110.281, 14.0098, 35.9248, 55.6823, 
+27.6514, 33.9682, -6.56723, 7.08044, 1.08545, 141.452, 32.0375, 
+-66.6585, 422.12, -1.94732, 14.131, 99.5792, 82.1444, 106.177, 
+92.9003, -10.7343, 53.8349, 94.3465, 4913.77, 163.125, 121.302, 
+38.5655, 4.60806, 22.7875, 474.352, 57.8392, 1343.88, 37.8733, 
+11.6468, 2134.67, 20.7209, -0.262148, 60.1439, 9.54504, 11.0515, 
+85.3045, 17.2096, -10.0328, 249.915, 80.3918, 12.3823, 79.3767, 
+-24.3948, 154.531, 65.6515, 45.5399, 120.194, 286.588, 20.0277, 
+84.3456, 114.626, -3.70138, 1408.67, 55.6233, 86.996, 44.146, 
+56.8192, 330.901, 94.1995, 198.394, 20.956, 1004.99, 34.7985, 
+43.6125, 458.303, 1105.91, 85.4095, 239.99, 14.5133, 367.98, 
+70.3372, 159.58, 113.518, 627.214, 48.9686, 18.9257, 215.514, 
+5072.36, 198.417, 108.445, 43.7502, 15.3726, 60.6967, 28.7406, 
+372.747, 26.8717, 36.0099, 28.4521, 16.6598, 16.615, 395.562, 
+89.2151, -3.48287, 0.949098, 24.0036, 17.1753, 2020.4, 9.37298, 
+22.2364, 194.071, 17.2649, 733.02, 63.9442, 12.6841, 161.425, 
+97.0986, 8.80042, 58.5091, 110.127, 30.2948, 792.965, 185.47, 
+25.4438, 15.206, 1653.84, 96.7924, 46.6804, 129.393, 139.963, 
+3.9302, 23.1836, 349.028, -13.9703, 205.086, 23.3787, 565.436, 
+11.5014, 25.2942, 115.304, 30.4287, 467.942, 78.5613, 332.408, 
+68.0818, 26.654, 139.279, 305.494, 968.042, 4295.6, 66.1099, 
+47.9075, 1671.49, 3009.75, -51.6177, 4419.01, 1.49445, 33.3544, 
+208.223, 80.8896, 109.391, -47.5517, -1.54634, 112.731, 55.4344, 
+121.317, 126.149, 186.27, 234.836, 431.412, 199.881, 4633.97, 
+550.201, 313.787, 260.752, 97.9721, 26.1838, 57.8575, 41.7102, 
+212.398, 1386.77, 42.3915, 4815.65, 7.77927, 16.2139, -14.3346, 
+7.23423, -36.5622, 382.237, 5040.27, 2787.18, 663.805, 47.069, 
+13.1205, 120.841, 25.3661, 123.813, -13.3061, 296.745, 768.182, 
+62.1101, 7337.71, 51.5785, 93.0793, 59.6659, 55.9502, 6.17613, 
+15.2514, 61.4079, 64.7212, 282.774, 87.2862, 4089.22, 49.6829, 
+57.329, 10.3485, 66.0395, 2900.05, 26.7714, 179.807, 16.8715, 
+21.8325, 41.8975, 93.0038, 17.5775, 4.26559, 9.86239, 4223.25, 
+2841.06, 20.8292, 31.5969, 124.771, 13.3185, 101.18, 220.587, 
+24.4661, 114.014, 217.8, 222.152, 97.8749, 1328.36, 1628.74, 
+119.543, 55.8618, 198.105, 17.7912, 131.838, 12.0612, 89.1887, 
+160.229, 16.6904, 55.4143, 297.18, 1501.55, 177.512, -3.47425, 
+7.49265, 73.3793, 130.814, 49.1007, 20.585, 22.3491, 28.9578, 
+-14.2241, 477.958, 695.053, 1797.77, 1188.65, 75.4384, 5.40401, 
+148.423, 168.659, 21.3487, 23.8646, 13.9465, -31.1664, 10.517, 
+42.0685, 185.579, 127.054, 255.91, 405.051, 452.185, 17.8215, 
+418.522, 183.725, 20.8731, 20.8792, 31.9397, 62.6096, 5.9791, 
+17.6778, 64.7069, 30.6733, 17.734, -0.770045, -12.5623, 5.15007, 
+40.9506, 408.107, 2.22234, -2.07164, 58.2916, 129.924, 57.7661, 
+16.038, 58.9447, 213.212, 26.9509, -26.1956, -3.61176, 648.933, 
+272.632, 131.979, 386.255, 313.417, 87.9249, 374.494, 22.2172, 
+53.833, 46.8675, 49.705, -13.3931, 60.8839, 829.741, 263.664, 
+171.084, 32.7409, 171.323, 253.907, 105.42, 553.365, 12.8651, 
+27.5378, 522.891, 439.887, 489.785, 806.483, 135.509, 57.6252, 
+4.23123, 3305.96, 62.7559, 223.958, 300.78, 586.625, 60.3832, 
+16.7481, 203.739, 329.75, 29.9522, 2.0116, 2821.25, 456.575, 
+442.349, 88.1746, 33.6031, 6.54673, 30.7566, 197.82, 212.203, 
+24.5808, 22.5957, 2147.63, 2914.48, 175.206, 6133.12, -12.2493, 
+264.909, 81.9187, 120.393, 197.285, 152.217, -14.6336, 90.9128, 
+37.7668, 16.6599, 31.4279, 138.896, 22.406, 316.208, 22.2439, 
+244.162, 216.155), L = c(78.2126, 94.5418, 14.1554, 27.2852, 
+41.7698, 49.8397, 181.522, 46.2777, 28.1342, 17.7506, 540.255, 
+42.9071, 72.4584, 20.6693, 24.6885, 124.837, 108.469, 45.7015, 
+-34.298, 162.256, 120.737, 49.9029, 7969.59, 30.7302, 77.3764, 
+36.5985, 29.1573, 30.6495, 108.717, 24.0504, 28.6438, 29.9055, 
+94.9414, 27.9779, 16.9136, 82.0327, 52.7458, 10.6833, 104.433, 
+141.173, 155.572, 489.626, -23.2247, -47.1546, 36.6282, 3832.06, 
+4173.52, 4636.95, 4251.54, 5318.93, 4684.27, 74.8463, 10.7062, 
+57.8296, 49.8605, 480.33, 427.257, 86.2199, 130.797, 67.4093, 
+32.5288, 163.479, 189.271, 59.1629, 33.477, 31.8509, 226.835, 
+20.3279, 7.70438, 17.391, -17.6818, 178.158, 126.103, 106.483, 
+65.3268, 192.701, 5.72163, 7.87614, 17.3802, 7.25462, 107.479, 
+130.882, 19.0447, 22.8006, 95.6079, 64.857, 540.998, 2.98843, 
+104.51, 13.8843, 3127.05, 15.1634, -20.1506, 31.8186, 9.41495, 
+62.762, 2.31336, 318.532, 15.8975, -31.2221, 28.2393, 358.525, 
+113.643, 2.6089, 79.5849, 27.9021, 72.6205, 118.595, 19.8483, 
+11.0152, 192.243, 44.7104, 40.9957, 309.898, 68.6476, 141.44, 
+175.615, 212.777, 30.6944, 10.4933, 17.5478, 17.2951, 284.513, 
+115.904, 7.71463, 22.3834, 63.3352, 51.9875, 41.5452, 5.70349, 
+17.5473, 3.36623, 196.457, 32.0315, 40.8864, 390.245, -6.20708, 
+18.8825, 107.995, 89.682, 83.529, 86.4903, -14.662, 80.7351, 
+77.1165, 4714.97, 174.416, 125.587, 34.9933, 15.3988, 7.72275, 
+373.108, 58.9034, 1091.26, 22.5644, 10.6076, 2825.84, 31.0684, 
+3.06087, 66.2265, -12.3439, 18.2999, 156.12, 3.64407, 8.4741, 
+202.573, 99.9544, -3.61491, 66.551, -4.67678, 143.992, 7.87179, 
+102.047, 112.608, 232.685, 16.5717, 65.0425, 101.624, 15.5074, 
+1336.5, 28.023, 19.2818, 21.8167, 54.3966, 319.706, 103.576, 
+203.31, 3.55299, 1068.35, 28.3274, 26.3981, 252.545, 703.073, 
+54.1925, 217.043, 6.1789, 257.203, 51.0011, 122.56, 104.892, 
+669.295, 55.4482, 14.6155, 192.87, 3837.67, 164.49, 98.1155, 
+44.7301, -3.83686, 65.8807, 15.7527, 224.901, 35.5609, 42.3085, 
+38.2248, 23.7824, 36.5926, 329.908, 151.346, 2.20718, -6.77795, 
+32.9619, 9.10169, 1484.18, -1.97644, 9.40026, 184.919, 18.7039, 
+675.331, 80.7041, 7.85682, 157.12, 292.043, 5.51988, 54.3092, 
+113.512, 22.944, 0.00333823, 203.611, 18.8989, 15.0135, 1072.25, 
+84.0077, 45.5236, 166.489, 143.034, 16.4508, 24.3721, 270.51, 
+0.128169, 231.787, 15.2198, 491.515, 56.7006, 2.14923, 76.0331, 
+25.3416, 315.647, 60.7932, 93.3669, 61.774, 24.7379, 142.502, 
+273.436, 559.009, 4565.57, 91.3635, 51.3326, 1216.42, 2264.58, 
+-10.6544, 3693.04, 2.36806, 7.91398, 182.291, 68.3882, 99.9411, 
+-29.8436, 13.0513, 111.624, 60.5107, 56.3676, 43.5945, 57.6264, 
+92.3869, 222.841, 117.365, 4733.16, 154.346, 378.059, 194.359, 
+111.34, 23.7334, 109.848, 32.1758, 206.46, 1041.33, 5.56239, 
+4024.79, 10.4667, 14.2839, -17.2184, 20.4523, -79.7605, 264.947, 
+3918.19, 2872.76, 628.093, 39.0135, 18.5584, 137.049, 25.2468, 
+99.8514, 6.99163, 309.396, 812.051, 55.7119, 4544.12, 43.3877, 
+91.4044, 34.6002, 32.6657, 24.6652, 10.2426, 54.852, 57.2348, 
+303.057, 87.6017, 3190.4, 67.4407, 62.8154, 6.78031, 73.504, 
+2679.17, 14.6392, 132.44, 29.5628, 33.7716, 29.6722, 115.932, 
+23.4293, -5.8544, 14.3031, 3444.45, 2869.71, 28.9977, 4.27229, 
+186.639, 28.0031, 89.4065, 246.739, 48.2378, 103.241, 161.446, 
+270.958, 125.482, 1006.52, 1669.62, 164.343, 60.0043, 163.457, 
+3.32663, 74.8823, 21.1182, 150.393, 153.827, 23.2867, 39.983, 
+295.462, 1489.4, 198.153, 8.37534, 9.11512, 77.9832, 116.607, 
+81.8224, 30.7223, 19.276, 26.9488, 2.9106, 411.878, 445.727, 
+874.957, 500.034, 69.2402, 32.9342, 150.361, 151.8, 31.3103, 
+16.5552, -3.76102, -45.0008, 54.7287, 41.5445, 218.859, 119.3, 
+216.473, 601.634, 417.205, 16.8544, 385.101, 92.1054, -34.8347, 
+7.67655, 20.2027, 62.5156, 19.8893, 36.8451, 84.4214, 43.7161, 
+20.6758, 14.1665, -17.9138, 3.66986, 51.094, 386.478, 2.78177, 
+-23.3501, 85.6016, 106.723, 24.712, 19.2536, 63.4195, 141.174, 
+4.08547, -40.6516, 5.0975, 852.823, 297.981, 185.162, 353.931, 
+197.236, 51.9685, 254.8, 21.2191, 23.4201, 19.4266, 15.4119, 
+6.83701, 57.5619, 788.663, 192.798, 92.6476, 58.0558, 103.424, 
+402.939, 78.4368, 482.728, 12.8727, 20.3747, 304.571, 280.536, 
+868.772, 681.686, 154.107, 56.8466, 4.34006, 3009.56, 78.9415, 
+224.968, 260.592, 495.764, 27.1459, 25.2768, 271.342, 280.424, 
+67.1491, 11.4204, 2824.45, 379.401, 432.295, 86.7501, 51.2107, 
+13.8727, 12.0495, 162.998, 144.218, 29.2461, 10.0415, 1747.69, 
+2279.5, 194.048, 4077.38, 10.459, 267.847, 63.0694, 173.069, 
+268.178, 108.644, -11.9445, 71.3147, 72.9171, 42.753, 46.8353, 
+106.018, 39.0425, 297.051, 19.9168, 239.654, 175.866), M = c(83.0943, 
+75.3455, 20.6251, 10.1616, 80.2197, 63.4794, 177.979, 61.8372, 
+20.6908, 13.764, 364.233, 34.743, 46.9686, 51.7133, 30.1908, 
+133.826, 141.43, 74.9533, -37.9804, 199.741, 101.196, 45.6627, 
+8569.94, 21.5053, 71.6353, 45.2345, 16.2124, 29.3611, 155.95, 
+17.4717, 6.67245, 25.5961, 84.4995, 34.4475, 27.0618, 87.2791, 
+53.0348, 22.1029, 83.485, 145.652, 78.7713, 552.023, -7.45341, 
+-38.1208, 52.3868, 951.709, 2054.2, 3593.47, 2363.09, 3394.98, 
+5280.83, 73.6465, -3.59805, 11.6322, 39.7948, 474.48, 446.417, 
+83.9094, 82.0596, 4.65439, 25.0958, 132.912, 160.376, 46.9679, 
+21.0982, 39.5596, 172.825, 57.0022, 15.1321, 6.89282, 10.249, 
+231.956, 84.717, 162.506, 105.706, 368.552, 20.8338, 3.34395, 
+22.629, 16.5794, 112.52, 120.17, 25.3857, 18.5757, 76.1544, 56.769, 
+710.362, 25.2881, 104.82, 17.9295, 2166.34, 33.6051, -68.8391, 
+27.5807, 6.22118, 87.7027, 11.1385, 226.395, 15.0665, -8.00193, 
+38.6553, 297.233, 97.0745, 14.7636, 36.9007, 27.4486, 93.4518, 
+133.967, 1.93178, -31.4089, 125.988, 27.2904, 34.3379, 306.955, 
+76.0012, 117.52, 127.058, 162.262, 26.3359, 9.83787, 9.8701, 
+2.59895, 221.225, 120.925, 13.4816, 16.825, 55.9125, 50.2382, 
+20.5871, -8.9378, -0.825097, 4.93097, 87.2036, 38.8415, 63.1551, 
+342.044, 1.55868, 43.3275, 59.2687, 76.2816, 54.1066, 35.1053, 
+-18.1485, 87.1477, 69.0928, 3061.22, 142.504, 61.3115, 19.8458, 
+16.7309, 26.7999, 291.012, 68.0085, 1341.42, -5.03949, 11.985, 
+2462.38, 33.7193, 31.9753, 87.5545, -0.64562, 23.9027, 118.133, 
+4.938, 16.1042, 202.256, 54.5443, -18.7757, 42.8026, -23.1493, 
+109.216, 20.9903, 168.211, 96.529, 255.983, 24.6469, 57.3531, 
+60.9461, 16.7617, 1194.77, 65.8861, 41.8083, 35.2495, 39.6414, 
+315.246, 91.0557, 99.0671, -13.6988, 735.746, 41.1719, 47.3791, 
+177.377, 614.182, 59.8693, 30.885, 22.5553, 243.968, 35.9511, 
+63.6658, 99.4039, 522.82, 60.6395, -1.66086, 159.967, 4483.8, 
+129.281, 39.2241, 32.5089, 10.4541, 33.5574, 26.8906, 213.557, 
+39.2447, 45.558, 42.9064, 41.2092, 25.2691, 416.211, 131.378, 
+14.8044, -12.8104, 41.5559, 25.2181, 910.831, 43.8009, 26.3252, 
+154.752, 12.9101, 687.584, 88.6125, -0.336495, 198.312, 94.2741, 
+17.5389, 51.9669, 88.3272, 36.4551, 461.577, 165.445, 36.2047, 
+24.8808, 1081.74, 36.55, 23.7109, 159.069, 233.972, 12.9205, 
+28.5951, 108.56, -6.12013, 191.418, 12.2177, 231.754, 37.0556, 
+6.70182, 87.9948, 36.1115, 612.477, 84.2877, 40.2468, 80.9183, 
+20.9539, 127.597, 149.293, 690.077, 3202.51, 68.2316, 36.8647, 
+2056.22, 2154.64, -9.95432, 3391.38, 25.0875, 8.04776, 165.387, 
+38.9222, 34.9766, -69.0935, 15.7108, 63.4733, 94.4522, 24.1385, 
+45.2206, 61.5433, 70.8851, 185.287, 135.227, 2325.45, 147.141, 
+439.105, 249.862, 60.6961, 28.8159, 67.1284, 0.982107, 222.603, 
+862.449, 30.9948, 3355.67, 2.58366, 11.8532, -18.402, 13.2898, 
+-102.745, 346.194, 3064.76, 1603.25, 369.522, 18.631, 32.082, 
+88.5522, 17.4802, 80.5616, 4.62538, 260.651, 728.888, 81.0913, 
+4699.84, 99.8263, 83.0734, 37.3094, -12.5336, 61.8152, 15.6515, 
+60.4089, 63.2578, 340.254, 69.8406, 2758.39, 46.0112, 48.4845, 
+3.00775, 29.5308, 2099.51, -6.78946, 174.172, 9.25558, 45.1605, 
+26.3615, 156.608, 31.6536, 24.1051, 6.58549, 2570.12, 2601.37, 
+27.6198, 9.27717, 127.368, 55.0356, 62.7111, 242.408, 37.2933, 
+89.3639, 80.0193, 181.817, 116.242, 902.432, 1249.58, 80.8068, 
+52.1335, 136.944, 9.19369, 71.6054, 18.0322, 88.5453, 98.5185, 
+20.4774, 55.4713, 149.533, 1363.19, 149.736, -1.52306, 4.68956, 
+110.182, 101.287, 41.1006, 12.8158, 48.2847, 38.6703, 6.17504, 
+315.271, 417.669, 917.604, 526.949, 86.7901, 5.49079, 143.844, 
+167.758, 47.3894, 21.3244, 2.5463, -7.53348, 26.1854, 49.2212, 
+385.217, 96.6181, 210.713, 551.058, 243.31, 15.2205, 219.578, 
+72.9952, -46.7619, 7.65478, 47.2021, 53.3323, 134.446, 30.1702, 
+60.0559, 72.6591, 27.7802, 11.7253, -21.2467, 19.6256, 43.3206, 
+260.447, 22.5582, -12.5203, 83.1298, 100.778, 73.4488, 19.4349, 
+60.313, 83.9283, 12.583, -42.8756, 6.82419, 793.746, 326.453, 
+137.1, 256.042, 131.438, 29.7611, 318.512, 13.3918, 13.7316, 
+27.2708, 54.9233, 18.3137, 110.58, 875.888, 253.193, 40.8993, 
+44.3985, 70.4717, 352.11, 80.2816, 311.052, -21.727, 20.0393, 
+70.7562, 179.195, 217.285, 569.148, 198.792, 62.9297, -7.06251, 
+2414.78, 116.931, 194.218, 159.881, 385.724, 23.8568, 14.4838, 
+245.611, 197.367, 99.2812, 2.62564, 1601.98, 300.787, 375.428, 
+117.816, 70.1534, 25.8099, 25.0521, 242.021, 143.848, 24.7516, 
+9.49541, 1610.07, 1234.16, 100.479, 4545.04, -15.8535, 132.319, 
+54.0656, 168.764, 231.665, 73.7824, -13.5897, 134.05, 52.493, 
+13.629, 32.2955, 71.1854, 58.7573, 389.896, 17.564, 159.716, 
+143.938), N = c(89.3372, 68.5827, 15.9231, 20.2488, 36.4903, 
+24.7007, 105.778, 54.7061, 27.6193, 12.9047, 620.004, 28.1586, 
+49.6642, 16.4545, 27.6512, 125.316, 83.1231, 62.1944, -43.3921, 
+179.797, 108.527, 61.2552, 8328.77, 27.2929, 61.2444, 24.9717, 
+23.3693, 24.7045, 80.3862, 13.1025, 14.058, 25.7586, 95.8448, 
+17.5522, 11.7202, 46.8633, 19.37, -3.87819, 97.6268, 126.247, 
+151.156, 593.651, 12.4314, -33.8106, 22.1085, 4461.43, 5802.7, 
+6060.91, 4086.23, 5676.56, 5252.6, 113.113, 122.966, 423.178, 
+48.5391, 711.508, 541.712, 110.042, 165.886, 76.3206, 39.4698, 
+183.316, 179.084, 70.8899, 29.984, 36.0984, 212.015, 10.657, 
+12.9578, 12.4452, 9.72711, 135.855, 112.589, 100.713, 43.1201, 
+65.7495, -4.33284, -0.353979, 9.78135, 2.40246, 113.384, 108.119, 
+15.8645, 16.1352, 77.5753, 28.2062, 550.153, 11.4208, 108.602, 
+12.7647, 4361.74, 18.7189, -6.71526, 13.7928, 2.6998, 42.8679, 
+3.04152, 577.023, 6.81695, -33.8613, 28.6891, 323.837, 144.178, 
+-0.204522, 54.4277, 12.9936, 46.847, 61.8186, 15.4617, 19.7307, 
+233.956, 13.7186, 19.5749, 359.412, 52.5534, 197.571, 141.737, 
+142.417, 17.3591, -1.58291, 20.88, 16.6252, 239.4, 110.505, 13.056, 
+4.91238, 48.4446, 26.072, 40.4425, -0.057119, 4.31744, 3.55702, 
+211.343, 35.0582, 32.3002, 432.547, -19.1825, 9.51985, 84.1913, 
+94.2885, 123.165, 79.0483, -11.4864, 78.9365, 82.8418, 2930.72, 
+155.284, 107.217, 39.1289, 26.7801, 9.41311, 385.342, 40.9863, 
+1405.31, 20.5272, 16.6352, 1806.13, 36.4705, 2.26179, 45.9531, 
+-1.86616, 9.38855, 164.578, -0.27847, 13.6962, 218.181, 120.039, 
+11.5751, 51.5134, -6.85612, 190.775, 8.15471, 62.5651, 82.6708, 
+298.427, 18.8969, 55.542, 93.0269, 21.6652, 1345.85, 44.3509, 
+14.3534, 17.6052, 25.6272, 334.12, 100.373, 178.179, 55.6927, 
+688.725, 42.0559, 18.2529, 223.116, 530.782, 67.9175, 99.6496, 
+5.35416, 256.393, 35.4812, 111.821, 92.1831, 531.768, 45.3206, 
+19.816, 142.631, 4859.73, 249.207, 103.439, 47.2751, 9.05566, 
+52.3237, 10.8053, 261.957, 38.8147, 29.6072, 39.9453, 18.349, 
+23.3791, 413.473, 113.186, 2.09751, 7.43113, 11.7495, 12.2955, 
+1782.61, 19.2064, 14.4603, 209.874, 6.45993, 1194.03, 77.9975, 
+19.6906, 186.337, 60.5553, 5.50611, 32.9364, 92.4704, 15.2531, 
+7.7857, 188.105, 11.737, 7.2607, 3617.54, 71.8314, 31.2533, 111.588, 
+121.778, 15.4925, 10.2916, 373.124, -5.67633, 263.947, 28.3399, 
+511.64, 28.4413, 0.574707, 68.9702, 20.9132, 272.211, 63.9764, 
+48.3643, 30.8804, 21.9132, 122.642, 233.14, 1010.75, 5954.55, 
+69.8307, 43.5644, 685.638, 2882.43, -83.7943, 3310.72, -0.662038, 
+15.7596, 188.547, 61.6832, 52.9313, -30.2268, 8.68393, 73.6295, 
+83.5782, 122.053, 276.064, 478.966, 220.497, 100.523, 203.143, 
+4325.4, 1204.45, 317.819, 165.436, 105.013, 17.2486, 89.6286, 
+19.6521, 165.066, 1597.74, 32.3071, 3807.53, 8.59767, 23.1666, 
+-12.7933, 8.29188, -76.8493, 250.028, 4850.56, 2571.96, 649.683, 
+35.8371, 13.2905, 109.861, 18.661, 88.348, -7.57178, 285.068, 
+774.966, 66.5567, 4813.55, 32.302, 83.0898, 20.6217, 46.1896, 
+-8.74484, 19.2316, 50.1061, 53.0092, 336.649, 52.5886, 4113.01, 
+66.7013, 69.1918, 13.2679, 81.2299, 2784.21, 57.2455, 493.228, 
+51.2349, 22.1017, 24.0103, 74.66, 7.29694, -6.52568, 14.8964, 
+3829.49, 2508.11, 27.265, 13.3097, 191.151, 52.0473, 59.4327, 
+508.603, 18.7608, 138.484, 142.005, 208.164, 87.9654, 956.885, 
+1678.65, 126.171, 33.5949, 209.168, 3.14731, 86.6463, 12.9521, 
+188.472, 247.983, 14.3525, 45.611, 325.842, 1110.41, 250.488, 
+0.118744, 15.712, 57.1836, 148.356, 22.0745, 10.0903, 29.8132, 
+22.3227, -6.73099, 452.967, 642.795, 3101.61, 1906.24, 83.7163, 
+6.33219, 144.829, 172.174, 16.5198, 6.6039, 11.7319, -15.1945, 
+-8.16856, 69.3211, 183.732, 118.473, 164.074, 496.539, 546.727, 
+15.4349, 460.542, 112.704, -24.5723, 14.6984, 58.4225, 65.6001, 
+3.60186, 25.3583, 71.0586, 36.3139, 10.6933, -5.65051, -18.0382, 
+0.915797, 15.0201, 694.094, 1.26846, 8.0124, 55.5302, 97.4134, 
+31.2342, 17.4901, 57.458, 106.358, 9.61853, -12.591, 0.139887, 
+592.938, 241.521, 190.222, 796.422, 507.855, 172.553, 334.769, 
+14.3157, 50.7952, 8.26035, 20.5055, 19.4919, 78.6369, 1046.35, 
+367.375, 15.7459, 42.2202, 392.361, 626.004, 94.4381, 293.149, 
+13.0971, 18.8269, 187.413, 229.444, 475.299, 808.413, 110.807, 
+57.2558, 1.20242, 3338.31, 58.0464, 235.895, 268.525, 585.18, 
+0.460327, 25.8225, 365.538, 328.021, 11.4567, 22.2974, 4049.75, 
+363.501, 443.315, 88.0459, 37.9932, 28.3565, 22.1575, 191.576, 
+148.362, 10.7204, 9.84052, 881.215, 756.276, 123.841, 3855.89, 
+-7.62355, 227.628, 44.8431, 134.087, 223.436, 95.7585, 9.15849, 
+75.5934, 34.1658, 19.5753, 35.3076, 69.8382, 26.808, 216.754, 
+1469.03, 190.992, 182.317), O = c(91.0615, 87.405, 20.1579, 15.7849, 
+36.4021, 47.4641, 223.689, 62.0684, 40.6454, 13.3902, 569.133, 
+48.5457, 65.2693, 17.8828, 17.8083, 132.419, 54.7312, 84.2989, 
+-30.5948, 195.324, 109.446, 52.2385, 8663.51, 42.2334, 88.0712, 
+24.4171, 35.6076, 39.693, 100.474, 21.742, 30.3021, 43.7021, 
+116.99, 23.6911, 27.313, 84.3709, 49.9739, 13.2802, 217.396, 
+367.256, 332.381, 930.928, 5.36648, -52.6525, 23.6439, 1362.9, 
+1763.15, 2298.72, 3454.28, 3828.45, 3727.14, 62.2097, 13.5778, 
+56.544, 53.5262, 481.904, 402.718, 99.6078, 162.308, 69.0339, 
+61.0306, 155.209, 206.509, 59.7551, 33.1553, 52.3652, 278.303, 
+16.0722, 11.0232, 12.9863, 24.7943, 150.402, 139.517, 94.6878, 
+45.6489, 1290.84, 3.43024, 12.9193, 7.68004, 33.7241, 119.821, 
+173.552, 34.6971, 31.6987, 131.983, 85.5727, 621.437, 3.78157, 
+162.985, 18.0843, 1465.47, 17.9788, -9.77655, 19.0585, 4.2578, 
+48.7836, 6.20112, 465.464, 11.8042, -17.8159, 36.906, 344.095, 
+117.624, -60.686, 70.5839, 24.5116, 57.8507, 106.437, 23.974, 
+29.632, 199.984, 23.5255, 18.0818, 465.204, 47.253, 110.568, 
+210.712, 189.16, 25.4456, 14.1781, 33.2616, 29.6363, 312.489, 
+112.39, 19.7958, 31.6101, 23.2446, 67.7264, 63.1741, -1.28236, 
+15.6809, -22.4669, 164.455, 35.2809, -16.8447, 308.41, 15.6924, 
+13.6633, 108.893, 89.4569, 97.3631, 80.1768, 353.866, 114.01, 
+75.672, 1931.77, 216.261, 154.741, 24.8446, 11.0583, 10.2016, 
+437.672, 44.1626, 1150.15, 33.3331, 25.9648, 2849.15, 56.2084, 
+21.5655, 61.6313, 0.5633, 6.6802, 142.206, -1.52441, 14.2807, 
+227.428, 154.188, 2.73304, 135.888, -6.55262, 146.762, 13.6927, 
+59.0275, 149.335, 322.438, 18.4279, 131.005, 124.646, 12.9452, 
+1413.51, 63.8342, 15.1334, 24.8349, 53.312, 329.991, 112.056, 
+260.494, 15.5461, 1383.65, 37.1371, 26.8427, 243.959, 606.582, 
+98.9069, 61.6406, 16.9089, 340.449, 49.6253, 149.616, 120.192, 
+667.523, 49.9381, 24.8398, 225.262, 3546.96, 136.091, 121.874, 
+51.4883, 8.84598, 69.2017, 20.1963, 285.056, 41.1304, 47.4723, 
+45.6532, 21.6557, 34.7265, 446.774, 84.824, 11.7275, -7.08199, 
+48.6305, 28.8085, 1075.68, 12.0825, 25.3304, 192.562, 26.608, 
+392.937, 66.2018, 6.86363, 251.672, 91.9728, 22.2643, 74.2767, 
+126.254, 37.9815, 209.963, 191.709, 12.6392, 6.46965, 1395.67, 
+95.0177, 42.7501, 125.366, 101.043, 24.6033, 34.9832, 459.64, 
+-2.3563, 194.104, 32.6242, 208.027, 104.251, -0.780733, 105.502, 
+37.781, 291.185, 1161.23, 235.632, 46.5727, 27.6308, 159.657, 
+300.935, 557.992, 2116.27, 1054.46, 73.9035, 1217.01, 1460.15, 
+-88.8, 1992.36, 6.53622, 5.29332, 225.701, 125.598, 116.968, 
+-27.5739, 9.55741, 179.675, 89.3978, 88.787, 315.728, 345.216, 
+335.878, 168.616, 439.822, 3306.11, 1049.26, 547.481, 286.447, 
+99.1406, 38.4488, 114.556, 45.9393, 273.941, 1111.15, 39.4502, 
+2902.01, 6.15638, 23.0667, -14.1021, 9.35298, -116.857, 452.608, 
+3544.92, 927.414, 756.701, 41.3498, 23.6982, 211.032, 35.4816, 
+123.105, 23.9056, 353.035, 743.73, 79.2366, 5514.38, 42.0635, 
+127.181, 44.6466, 43.0307, -0.20449, 19.4447, 66.9031, 55.2938, 
+399.75, 81.2312, 2672.37, 64.994, 67.4257, 10.9589, 71.4969, 
+2093.8, 14.6523, 28.02, 34.3509, 21.8848, 29.0589, 128.662, 20.666, 
+-1.34474, 21.2585, 1646.82, 2867.21, 37.065, 42.8606, 207.514, 
+26.1821, 153.811, 274.655, 45.6786, 170.145, 173.887, 234.359, 
+60.399, 1349.8, 1600.49, 78.0854, 43.6012, 203.56, 6.03428, 131.07, 
+26.5348, 97.5548, 161.412, 16.7075, 71.5095, 280.713, 1207.67, 
+155.317, 6.33112, 30.6113, 62.8205, 164.324, 47.1694, 16.4894, 
+24.9893, 38.3245, 1.62452, 499.28, 442.922, 1074.38, 605.84, 
+60.6398, 16.3385, 188.24, 272.834, 30.0742, 22.7793, 6.38199, 
+-41.293, 37.8102, 33.2661, 223.882, 126.257, 295.781, 524.562, 
+420.12, 16.3514, 287.683, 95.448, -39.3764, 15.5204, 65.131, 
+69.1624, 7.15867, 23.082, 106.437, 53.8414, 13.3305, -0.569408, 
+-24.9162, 30.1215, 80.6879, 429.743, 7.23502, 6.9824, 55.0579, 
+178.074, 15.6577, 58.2782, 66.9708, 163.589, 9.62151, -61.7727, 
+1.91402, 805.173, 262.389, 80.9406, 322.827, 125.727, 18.9264, 
+204.438, 38.7136, 40.4771, 13.2167, 31.9875, 5.56237, 82.045, 
+542.137, 304.213, 40.4456, 57.2924, 116.115, 283.383, 88.494, 
+402.55, 16.2518, 16.7579, 245.128, 287.116, 367.802, 1390.38, 
+175.099, 55.0086, -3.22419, 2509.98, 49.9448, 240.87, 250.352, 
+577.222, 17.2906, 10.8333, 290.135, 354.61, 3.13894, 47.0525, 
+2374.41, 394.607, 452.372, 57.5241, 42.6069, 40.0522, 20.0476, 
+202.874, 146.704, 18.5251, 8.70428, 747.181, 746.294, 210.542, 
+2534.57, -4.78982, 265.571, 47.9046, 255.362, 222.945, 202.534, 
+-1.89679, 75.6935, 108.222, 31.3858, 47.6782, 134.868, 18.6868, 
+315.229, 23.4902, 256.412, 183.381), P = c(95.9377, 84.4581, 
+27.8139, 14.3276, 35.3054, 47.3578, 183.585, 40.6705, 35.5333, 
+-6.86196, 520.495, 36.3279, 80.8682, 16.4829, 12.1731, 101.991, 
+83.9226, 48.5502, -37.918, 182.143, 109.243, 72.062, 9703.19, 
+33.9123, 59.607, 11.2079, 28.1836, 29.3086, 87.4065, 12.4074, 
+33.7019, 34.2866, 60.5425, 28.0745, 8.17936, 56.7914, 43.755, 
+1.30735, 380.761, 949.318, 873.601, 2133.17, 8.94132, -49.4911, 
+13.8909, 3635.18, 4155.44, 5029.35, 5097.63, 5885.63, 5158.47, 
+76.3571, 40.6937, 129.156, 44.6594, 532.827, 407.366, 150.024, 
+166.733, 79.4228, 52.9089, 146.577, 212.089, 58.6137, 25.1409, 
+57.365, 218.192, 22.9141, 9.60791, 16.0146, 16.0711, 193.675, 
+131.629, 90.5224, 78.5255, 2666.04, 1.83676, 107.723, 8.9607, 
+166.211, 87.4163, 137.844, 58.0048, 18.4808, 84.3373, 69.2211, 
+501.736, -0.0219398, 110.627, 27.8748, 3428.02, 18.2661, -0.552943, 
+9.04877, -7.55392, 34.7136, -22.0775, 438.31, 8.01353, -10.6556, 
+11.7081, 286.784, 142.977, -1.75306, 92.0008, 17.9923, 43.3699, 
+69.9862, 7.03824, 15.2385, 266.447, 13.9918, 44.109, 343.971, 
+106.388, 193.132, 259.72, 146.305, 27.5627, 11.8241, 28.1245, 
+10.5465, 298.405, 72.1411, 8.54124, 19.1003, 28.5318, 19.2189, 
+50.9797, -6.94101, 12.6264, -19.0878, 132.13, 32.4503, 34.6964, 
+356.571, -4.75583, 15.0408, 90.0344, 83.563, 72.9321, 89.6479, 
+-9.24438, 112.635, 89.945, 4708.72, 307.156, 106.495, 35.6991, 
+21.3087, 11.8785, 403.283, 45.9825, 1190.18, 17.3389, 12.962, 
+2253.57, 26.0812, -9.33715, 45.8318, 4.25198, -0.235197, 95.423, 
+12.242, 21.7191, 207.132, 110.167, 18.8907, 62.423, -2.17878, 
+188.407, 4.73582, 57.3755, 91.7946, 346.722, 5.35646, 88.8214, 
+112.848, 12.5417, 1366.66, 55.1934, 13.0844, 33.9986, 60.4339, 
+318.644, 107.152, 207.756, 10.0655, 908.623, 24.9347, 30.1607, 
+784.132, 1581.78, 61.0361, 208.332, 9.41051, 272.553, 35.7506, 
+287.011, 130.155, 675.119, 37.0291, 27.0153, 197.177, 4754.66, 
+130.537, 106.092, 67.2723, 6.46507, 102.061, 32.6796, 343.667, 
+49.9468, 37.6753, 17.743, 23.795, 28.4899, 391.945, 100.785, 
+-5.28743, 24.6998, 36.4727, 5.44548, 1542.53, 15.6564, 1.72514, 
+175.246, 16.8081, 592.958, 58.0536, 16.8238, 196.898, 173.092, 
+19.4727, 32.409, 157.622, 40.8702, 1926.03, 209.951, 19.1415, 
+-1.09743, 1946.8, 90.6256, 54.4008, 133.856, 87.6597, -6.63018, 
+31.2292, 373.655, 4.77085, 326.268, 36.6104, 415.757, -10.3339, 
+5.03371, 145.241, 98.7188, 232.926, 65.1305, 305.526, 39.0101, 
+16.5698, 133.832, 318.781, 1051.04, 3344.31, 57.0384, 52.8896, 
+2427.39, 3146.21, -33.1885, 3671.85, 53.1269, 0.677284, 226.086, 
+112, 58.5344, -26.5842, 14.5561, 69.9531, 57.5755, 159.83, 196.863, 
+377.648, 271.063, 130.595, 473.57, 4174.7, 926.876, 384.274, 
+269.828, 174.097, 8.58941, 98.2331, 31.5614, 230.974, 1317.19, 
+34.6345, 4225.96, -7.23611, 32.0804, -8.18457, -19.4876, -79.0781, 
+318.325, 3938.1, 2173.5, 627.963, 36.4799, 30.1577, 104.443, 
+20.5033, 100.631, 11.327, 310.695, 737.578, 93.6738, 6463.77, 
+28.3647, 78.8394, 40.2777, 41.681, -9.14832, -1.23541, 59.2399, 
+39.7863, 330.049, 51.3537, 2981.12, 48.1936, 44.3643, 2.1581, 
+71.4727, 2383.25, 25.6787, 195.431, 18.1804, 18.4473, 13.8278, 
+89.4967, 13.0111, -36.4418, 14.1874, 2983.45, 3025.66, 27.0738, 
+100.308, 166.18, 19.0582, 73.1515, 268.685, 35.5036, 137.303, 
+194.318, 233.562, 76.5329, 1958.33, 1834.38, 83.1306, 43.8636, 
+188.715, 4.5986, 86.2513, 14.9692, 37.6332, 80.6467, 8.96311, 
+46.4031, 361.995, 1489.12, 152.357, -11.4613, 42.1186, 60.9955, 
+145.517, 49.2345, 22.0977, 26.0827, 29.9162, -4.43161, 498.882, 
+516.328, 1400.31, 753.996, 67.8413, 11.8069, 128.401, 314.835, 
+15.3117, 14.2839, 5.99399, -27.0365, 25.2353, 26.3329, 205.1, 
+108.31, 208.561, 440.486, 485.368, 24.4458, 332.205, 108.732, 
+-33.8566, 3.19337, 64.9522, 71.5209, 4.01805, 36.4773, 88.9457, 
+39.8483, 21.7754, 1.84143, -20.8023, 9.08591, 48.9682, 312.86, 
+2.54359, 10.9099, 39.17, 141.846, 40.0549, 26.9255, 54.3649, 
+213.655, 14.2068, -21.6539, -3.26063, 610.592, 240.758, 181.643, 
+705.632, 323.292, 112.908, 669.242, 21.5416, 77.7138, 9.21672, 
+28.6409, 8.29647, 52.3091, 1202, 299.665, 181.463, 49.5697, 118.863, 
+366.126, 99.5636, 271.68, 22.9561, 21.5974, 330.821, 275.754, 
+551.549, 755.334, 142.136, 45.7811, -6.41456, 3184.69, -7.71132, 
+269.67, 334.009, 579.92, -11.1694, 37.5901, 224.289, 312.906, 
+23.2579, 14.2944, 2260.91, 453.288, 511.297, 63.2891, 35.8314, 
+36.5171, 21.961, 165.049, 126.496, 17.4001, -4.83672, 2869.42, 
+3314.75, 216.978, 4321.76, -3.40488, 302.999, 55.3171, 215.658, 
+234.406, 229.894, 2.80647, 51.6358, 46.0148, 30.7832, 36.3961, 
+104.452, 28.7967, 270.453, 10.2954, 299.513, 298.381), Q = c(179.845, 
+87.6806, 32.7911, 15.9488, 58.6239, 58.1331, 192.221, 53.2711, 
+57.5078, 21.5091, 401.43, 57.8427, 53.4837, 6.53565, 26.9214, 
+204.75, 103.289, 74.191, -30.488, 144.421, 107.088, 36.6448, 
+6945.46, 26.3551, 72.2323, 34.9787, 31.9271, 39.3662, 88.351, 
+20.2063, 47.751, 39.3882, 93.421, 38.4229, 24.4473, 97.0614, 
+48.2842, 20.4114, 149.48, 91.9974, 99.0099, 489.616, -47.5854, 
+-50.1208, 40.9994, 2056.61, 3297.7, 5375.36, 1481.99, 2634.74, 
+5005.51, 58.5187, -2.27154, 49.6001, 104.546, 589.112, 435.819, 
+197.43, 162.421, 88.937, 59.6806, 220.031, 148.895, 145.55, 38.3616, 
+130.29, 441.142, 22.7215, 5.45075, 0.541475, -2.7933, 143.731, 
+151.581, 122.392, 64.1095, 241.961, 9.33198, 2.84321, -0.0813966, 
+13.0512, 137.274, 152.312, 17.9966, 24.0255, 56.6119, 19.8654, 
+602.892, 18.9863, 128.256, 5.18994, 3225.78, 20.0576, -22.8684, 
+24.0201, 23.255, 52.3609, 9.78681, 378.532, 7.86409, -10.9199, 
+39.3368, 509.703, 98.3465, 4.3278, 30.9841, 15.7241, 72.934, 
+131.086, 17.678, -8.3158, 206.659, 15.5542, 30.9563, 526.82, 
+40.1954, 157.392, 186.118, 463.845, 25.6804, 18.7586, 30.2144, 
+26.5379, 426.224, 72.4541, 27.7973, 43.7178, 38.8451, 29.4314, 
+65.894, -1.37091, 17.5584, -18.2047, 175.757, 43.0175, 59.291, 
+360.72, 2.91078, 8.54141, 144.081, 107.063, 115.136, 118.639, 
+14.3273, 78.5512, 77.0416, 3784.57, 205.474, 129.544, 46.1631, 
+-6.58117, 6.7294, 407.759, 50.2326, 732.503, 31.4596, 22.3868, 
+1987.59, 135.708, -2.7049, 85.6406, -1.73791, -0.253871, 128.843, 
+-3.70685, 48.5898, 210.508, 211.484, -16.6187, 69.303, -20.0826, 
+159.374, 28.6098, 45.1189, 138.511, 418.071, 24.5252, 58.6564, 
+113.994, 9.71542, 1149.7, 62.2579, 28.4784, 50.1206, 53.1632, 
+382.944, 205.593, 292.019, 4.40127, 972.107, 11.6381, 33.2306, 
+137.403, 382.1, 107.61, 274.315, 3.02641, 402.868, 51.989, 161.62, 
+144.589, 700.349, 72.0878, 12.6023, 195.966, 4706.92, 92.8416, 
+92.2657, 41.3558, 7.73853, 70.9883, 18.9096, 306.337, 35.7701, 
+77.9582, 44.4995, 22.9144, 39.9449, 370.19, 129.158, 18.4312, 
+-3.72863, 33.1532, 16.5481, 750.471, 15.7297, 17.9517, 227.91, 
+29.0455, 1137.05, -10.154, 17.0133, 205.213, 27.6867, 9.59297, 
+64.6394, 171.64, 20.2732, 551.24, 215.793, 22.2288, 13.2424, 
+2093.72, 118.054, 55.8656, 181.877, 114.434, 25.1648, 37.2732, 
+199.615, -2.11748, 194.627, 20.2581, 225.932, 125.897, 14.3432, 
+97.1932, 17.4086, 236.933, 73.5888, 59.5797, 55.2935, 22.0871, 
+195.733, 225.552, 383.538, 4529.62, 88.9723, 147.116, 818.793, 
+2845.39, -117.257, 3771.48, 9.29057, 40.9826, 197.999, 138.397, 
+98.8488, -66.7108, 18.8726, 147.691, 59.8272, 155.593, 127.694, 
+169.62, 116.026, 124.979, 123.351, 4635.37, 489.761, 411.588, 
+329.29, 94.3519, 36.1513, 92.763, 33.1402, 247.683, 589.211, 
+17.2803, 5472.93, -0.0945169, 20.9166, -16.4756, 4.16099, -103.032, 
+310.225, 5160.17, 2308.51, 711.944, 67.0825, 26.3465, 252.606, 
+30.0716, 81.0213, 10.7387, 415.856, 831.018, 77.574, 5768.87, 
+38.7843, 188.789, 57.3272, 19.5062, 4.65378, 21.8456, 59.9341, 
+55.3942, 286.712, 145.81, 3762.74, 125.689, 65.3176, 63.5216, 
+114.212, 2204.63, 105.805, 734.733, 21.1044, 31.2069, 24.5646, 
+141.729, 14.2803, -0.0164678, 7.31915, 3652.55, 3571.21, 18.3819, 
+23.5022, 126.492, 57.9871, 378.767, 275.041, 86.5916, 194.384, 
+84.5018, 268.68, 66.6054, 1165.89, 1102.24, 131.127, 39.04, 127.934, 
+6.77768, 93.8452, 36.2621, 244.989, 113.863, 19.5587, 83.6092, 
+90.1186, 1144.37, 222.243, -0.112485, 3.04715, 39.3341, 174.551, 
+9.39525, 8.86476, 34.0683, 38.2249, 21.4314, 534.847, 423.109, 
+1412.79, 1009.59, 69.7896, 5.09325, 184.737, 197.544, 19.5185, 
+1.42929, 0.732096, -25.099, 48.13, 22.9186, 194.558, 133.921, 
+302.006, 589.515, 316.913, 6.54445, 244.15, 140.078, -54.1407, 
+5.48896, 54.3901, 49.1413, 32.6048, 35.0332, 115.283, 45.2265, 
+21.2021, 2.61183, -23.157, 23.1803, 60.5066, 644.764, 7.54052, 
+-10.2434, 80.3851, 120.091, 28.2656, 38.8046, 69.4305, 211.22, 
+16.6813, -51.1497, 15.4236, 773.751, 236.359, 220.25, 444.252, 
+197.603, 22.1516, 163.368, 4.38515, 32.3105, 21.5567, 34.8164, 
+7.38586, 83.7836, 690.248, 289.526, 55.7817, 58.9882, 376.087, 
+409.305, 135.194, 479.253, -7.37725, 0.122464, 93.6764, 187.529, 
+100.787, 663.026, 156.812, 46.7963, -3.89443, 4278.74, 53.7028, 
+236.132, 274.988, 476.378, -19.3199, 32.5085, 185.91, 297.545, 
+21.7566, -28.1106, 3377.88, 361.914, 433.109, 63.4572, 54.1816, 
+33.141, 18.6417, 195.832, 131.329, 26.9925, 15.6661, 2709.4, 
+1378.63, 237.151, 4236.67, -12.2979, 277.669, 60.6225, 364.282, 
+250.075, 168.212, -24.2041, 93.1122, 16.1807, 38.0609, 49.8754, 
+118.717, 32.9751, 239.852, 20.653, 237.043, 310.96), R = c(152.467, 
+108.032, 33.5292, 14.6753, 114.062, 104.122, 305.567, 107.237, 
+41.1337, 3.10536, 757.495, 83.1914, 108.545, 42.4696, 40.3873, 
+265.771, 140.76, 74.7106, -54.5634, 316.037, 188.792, 94.3601, 
+9186.23, 70.3766, 131.602, 56.8246, 40.0859, 48.3323, 187.831, 
+40.0367, 63.2577, 23.5424, 133.267, 40.1676, 26.7121, 157.43, 
+93.5228, 27.2889, 195.412, 267.395, 209.605, 582.488, 25.0043, 
+-29.4005, 41.4228, 1071.56, 2141.77, 2913.78, 4131.25, 4546.89, 
+3987.55, 60.5533, 8.11091, 70.4294, 91.2818, 621.923, 558.21, 
+86.4503, 157.802, 72.6112, 46.4297, 176.787, 196.865, 92.815, 
+50.2916, 85.7762, 331.161, 48.8162, 20.6512, 10.9181, -0.905975, 
+233.632, 204.266, 172.993, 103.938, 1614.46, 20.4997, 12.0684, 
+15.2499, 37.1182, 133.572, 145.011, 29.0069, 20.7526, 72.8516, 
+102.421, 734.952, 10.8608, 148.424, 14.2887, 1699.09, 40.0938, 
+4.5551, 22.2042, 20.2862, 66.5785, 8.12938, 438.409, 9.16017, 
+-26.0217, 40.6845, 334.96, 166.697, 11.0599, 85.3465, 65.1488, 
+70.9823, 226.982, 18.595, 30.777, 213.079, 17.112, 47.8895, 488.479, 
+80.2266, 206.459, 170.515, 305.913, 59.6001, 12.9898, 66.436, 
+38.64, 452.142, 147.568, 31.2212, 39.9977, 86.5661, 37.2774, 
+76.2522, -5.98051, 26.4634, -30.1757, 144.372, 65.8211, 61.777, 
+448.511, 17.0231, 39.0015, 141.992, 107.897, 105.584, 80.5216, 
+203.611, 79.6198, 110.707, 2188.94, 418.162, 185.003, 40.7064, 
+16.2165, 13.4062, 427.505, 93.5351, 1818.93, 62.4827, 16.2637, 
+2446.46, 70.9351, 19.1831, 99.676, 2.48638, 27.4741, 141.248, 
+27.3096, 25.9065, 252.931, 113.078, 6.87179, 116.856, -18.8597, 
+147.415, 36.6545, 109.731, 120.15, 318.348, 22.4257, 107.673, 
+135.75, 42.688, 1507.05, 64.8156, 12.377, 38.9106, 72.865, 483.677, 
+150.884, 183.042, 30.0473, 1264.23, 67.7055, 43.9821, 83.8563, 
+235.309, 83.3796, 153.38, 21.2252, 339.996, 64.6378, 173.331, 
+98.6056, 743.576, 87.6906, 50.6009, 267.82, 3831.35, 133.764, 
+103.796, 65.1927, 4.23406, 102.03, 38.5771, 412.567, 80.7445, 
+84.7391, 66.967, 51.0009, 26.7375, 480.525, 124.697, 10.7221, 
+27.7304, 59.3173, 69.1332, 415.189, 34.8442, 30.0275, 196.203, 
+8.14025, 170.304, 111.209, 9.7514, 266.524, 49.1039, 18.0585, 
+63.3793, 193.721, 30.783, 120.978, 227.752, 11.044, 14.0334, 
+1425.13, 63.0943, 42.0432, 197.522, 223.889, 22.6631, 51.5177, 
+250.103, -4.79409, 200.241, 16.6868, 102.159, 22.8715, 4.64345, 
+209.266, 49.3408, 468.176, 106.673, 172.501, 43.7646, 34.6348, 
+216.858, 260.969, 302.636, 1863.93, 111.276, 81.7995, 685.466, 
+1808.08, -10.9104, 2189.63, 17.3143, -0.330623, 290.932, 141.705, 
+11.9967, -93.7383, 17.2784, 47.8672, 113.007, 68.5187, 60.3833, 
+107.685, 111.365, 95.6294, 16.0335, 2125.74, 189.074, 403.838, 
+266.738, 106.865, 34.9085, 106.845, 66.5682, 325.85, 296.042, 
+63.2891, 2926.16, 14.8828, 25.1732, -18.4655, 14.9405, -182.623, 
+345.625, 2151.06, 622.274, 515.647, 40.7728, 28.5061, 117.372, 
+35.1721, 121.707, 12.6398, 452.022, 1037.91, 99.5648, 6397.87, 
+83.2929, 112.015, 70.6735, 42.6805, 75.0421, 24.7328, 117.228, 
+67.4218, 359.033, 98.0862, 2005.45, 57.4873, 57.8876, 7.38197, 
+77.2251, 677.15, 30.288, 81.2351, 32.8085, 35.7945, 29.5189, 
+151.22, 48.3396, 7.56941, 33.6318, 1287.71, 1373.77, 45.7599, 
+31.5629, 109.559, 54.1209, 111.934, 339.228, 72.705, 131.702, 
+71.9102, 263.616, 120.872, 1364.11, 2092.8, 87.4137, 56.3817, 
+95.6377, -4.18302, 130.424, 45.2359, 187.043, 65.6953, 18.7438, 
+55.2051, 105.641, 1499.26, 167.485, 2.11053, 21.5399, 117.773, 
+217.44, 51.3506, 18.8601, 40.4956, 53.5845, 5.83571, 660.491, 
+664.955, 1574.65, 478.21, 129.376, 15.2661, 260.743, -8466.18, 
+49.5091, 33.2026, 9.27869, -61.5478, 66.153, 40.8323, 360.081, 
+178.816, 218.49, 485.663, 352.142, 25.7411, 348.956, 149.195, 
+-85.781, 22.1877, 74.7517, 88.4789, 2.98481, 41.6607, 87.5974, 
+80.5128, 40.4506, 2.68361, -41.1939, 30.8733, 64.0993, 310.536, 
+16.2474, 16.2138, 48.1475, 178.396, 26.3308, 32.5856, 77.08, 
+161.854, 39.5347, -79.1266, 7.97024, 791.045, 366.511, 245.5, 
+77.9898, 164.441, -4.43778, 290.684, 3.41354, -0.254222, 34.5304, 
+48.6374, 14.6504, 4470.95, 319.764, 203.609, 28.2099, 53.0766, 
+55.7597, 257.995, 149.451, 354.238, 69.3679, 29.4672, 93.0593, 
+319.169, 169.189, 983.872, 237.993, 57.6727, -2.76582, 1531.69, 
+33.0223, 262.881, 253.669, 772.192, -2.05733, 30.0128, 262.16, 
+321.552, 6.10686, 18.6129, 889.943, 504.265, 567.512, 93.0405, 
+88.32, 58.962, 30.366, 271.145, 149.116, 27.7497, 28.916, 1564.67, 
+1988.77, 229.076, 4052.49, -20.0849, 304.424, 94.6692, 234.158, 
+280.213, 163.26, -0.523823, 95.161, -5.09898, 35.5848, 51.4191, 
+218.051, 43.3184, 501.531, 27.493, 287.333, 262.567), S = c(180.834, 
+134.263, 19.8172, -7.91911, 93.4402, 115.831, 300.689, 119.666, 
+79.9829, 5.95347, 595.908, 66.6783, 136.044, 41.4669, 17.6882, 
+317.314, 177.441, 112.964, -49.0879, 269.485, 240.35, 71.4727, 
+9889.05, 72.777, 136.208, 46.6026, 49.1144, 56.4269, 247.966, 
+30.2897, 15.9976, 43.3184, 98.5873, 52.8215, 29.895, 104.566, 
+51.2824, 14.161, 105.061, 121.308, 98.4066, 449.081, 90.946, 
+-3.12303, 52.178, 787.855, 2671.19, 4881.61, 1094.09, 1992.91, 
+4568.23, 43.1294, -2.45485, 35.8078, 194.779, 1149.07, 472.645, 
+153.465, 155.811, 78.5674, 67.3687, 196.392, 224.741, 103.921, 
+37.9265, 121.149, 330.471, 44.5184, -25.7326, -5.03244, 12.0736, 
+249.667, 152.511, 106.064, 91.2649, 163.929, -15.2783, 22.2097, 
+32.284, 19.4569, 90.3666, 154.363, -2.0974, 28.5418, 56.7267, 
+66.856, 807.89, 16.8584, 107.983, 20.4714, 3460.35, 47.6155, 
+-5.06083, 36.6995, 25.7782, 67.9857, -7.1937, 510.066, 8.34297, 
+-22.6467, 17.5439, 409.735, 115.789, -2.30007, 27.6526, 31.344, 
+46.8879, 149.112, 20.8777, 57.4851, 259.185, 1.47103, 50.97, 
+345.388, 42.0308, 240.033, 129.362, 257.606, 31.0306, 4.59672, 
+45.0933, 33.1438, 436.701, 175.625, 33.768, 39.8363, 80.3382, 
+29.0026, 49.2988, 5.05956, 23.5987, -10.8797, 176.337, 54.4923, 
+58.8794, 439.405, -3.61493, 38.4084, 128.262, 92.448, 157.364, 
+96.7016, -26.1654, 90.6717, 132.453, 3486.82, 246.219, 187.849, 
+15.8017, 16.9958, 3.98389, 506.407, 76.9606, 1854.34, 61.4706, 
+7.87159, 2154.92, 63.9216, 21.003, 126.628, 15.2875, 14.8456, 
+155.615, 12.7579, 33.5934, 316.255, 98.0338, -0.155925, 114.746, 
+-1.48718, 154.094, 17.3349, 147.235, 156.007, 418.399, 21.6388, 
+108.515, 142.459, 24.9952, 1218.14, 11.8222, 7.9083, 37.2163, 
+85.4512, 491.36, 183.883, 208.501, 50.3986, 1077.88, 124.843, 
+50.9061, 135.342, 408.804, 99.3985, 192.397, 22.2958, 286.63, 
+70.1096, 55.9491, 137.51, 721.507, 98.5957, 19.5054, 251.092, 
+4551.91, 122.042, 152.411, 60.2571, 27.1888, 100.811, 39.2265, 
+467.092, 64.3961, 76.1911, 83.2083, 46.4905, 18.0486, 489.009, 
+74.2649, 4.50381, 29.8879, 49.1869, 0.631129, 1000.79, 11.3707, 
+18.8654, 238.469, 23.2369, 718.064, 89.7505, 9.75831, 170.33, 
+28.7157, 8.9678, 112.746, 78.4019, 25.9762, 169.867, 206.853, 
+23.486, 6.17877, 1152.77, 192.186, 58.7668, 225.352, 306.653, 
+30.2744, 32.5775, 69.0377, 8.76418, 167.482, 12.9271, 212.637, 
+-13.1019, -10.4586, 155.464, 56.8248, 599.134, 92.2997, 51.1154, 
+33.7343, 23.6795, 203.75, 179.768, 436.384, 4338.32, 118.207, 
+111.672, 1810.67, 3395.32, -38.9316, 4429.26, -5.22744, 14.8681, 
+271.399, 145.53, 35.5675, -92.9327, 27.1228, 101.219, 70.1528, 
+144.957, 104.611, 156.323, 158.986, 185.459, 73.1768, 3557.53, 
+318.342, 360.28, 392.819, 134.733, 37.7964, 67.7007, 49.1147, 
+243.646, 643.462, 36.4443, 3379.99, 6.81798, 23.0309, -17.2907, 
+19.7955, -93.9038, 331.732, 4460.44, 2559.39, 403.001, 19.597, 
+18.4828, 201.77, 39.4426, 128.766, 9.73723, 568.667, 964.267, 
+91.0142, 5593.77, 80.4497, 91.9147, 96.3875, 77.823, -10.0185, 
+-0.552131, 104.977, 67.3361, 298.984, 103.676, 3175.74, 76.1713, 
+42.9305, 23.5164, 80.5255, 2942.06, 46.0359, 211.746, 24.4057, 
+36.5004, 28.4086, 189.812, 24.9993, 2.04241, 8.26861, 3992.39, 
+2822.58, 6.13577, -24.8298, 114.667, 45.6519, 113.635, 345.131, 
+41.3414, 204.028, 46.206, 286.119, 137.48, 874.469, 1530.73, 
+144.398, 50.0945, 106.27, 18.9696, 185.828, 42.4012, 109.506, 
+106.629, 0.265347, 114.964, 79.697, 1196.91, 181.206, -5.2015, 
+34.0159, 105.566, 275.02, 36.3232, -2.9961, 44.4439, 52.9923, 
+14.0299, 662.469, 689.304, 1951.98, 1049.51, 110.576, 6.38378, 
+257.273, 272.63, 46.4421, 8.63581, -10.7732, -50.931, 62.8756, 
+35.9405, 363.809, 210.738, 326.868, 518.104, 360.48, 17.5659, 
+389.966, 147.554, -85.8457, -4.62999, 67.4847, 72.5869, 17.7463, 
+72.1119, 106.536, 52.8706, 30.1552, 1.41616, -38.1398, 42.2391, 
+48.2987, 245.317, -2.8878, -8.54974, 67.0057, 85.5775, 68.6865, 
+58.0009, -100.96, 153.806, 8.89852, -52.7776, 13.7009, 741.804, 
+342.906, 213.806, 246.234, 249.977, 6.98249, 313.301, 4.85294, 
+-6.65, 11.7382, 44.1473, 26.9037, 150.331, 373.791, 225.069, 
+-13.2615, 71.2087, 77.8136, 316.181, 121.96, 535.475, 4.9466, 
+23.6025, 102.613, 253.591, 38.0866, 1595.16, 184.578, 67.1935, 
+-1.492, 2918.08, 45.1199, 272.804, 333.432, 845.986, 4.28768, 
+32.6207, 233.91, 363.863, 21.951, 11.784, 1891.02, 329.09, 486.907, 
+64.4783, 66.7354, 46.4086, 33.8196, 233.154, 136.06, 47.6797, 
+6.52799, 340.142, 141.886, 266.149, 5408.5, -0.330254, 249.207, 
+91.4136, 217.254, 223.499, 125.535, -26.3701, 124.581, 23.0902, 
+27.3877, 63.5235, 91.5899, 30.2485, 414.683, 32.0805, 292.537, 
+337.14), T = c(85.4146, 91.4031, 20.419, 12.8875, 22.5168, 58.1224, 
+146.081, 24.0654, 23.4953, 5.66012, 381.23, 24.8852, 43.8619, 
+21.6548, 38.31, 88.0773, 75.8888, 63.2349, -22.5916, 148.114, 
+94.9754, 24.3627, 8872.19, 16.6944, 25.9624, 14.2291, 26.7874, 
+18.7009, 67.1026, 22.4741, 9.27033, 47.5063, 63.1381, 15.6287, 
+16.4874, 48.3661, 29.3514, 5.19944, 80.6699, 130.446, 92.6789, 
+991.455, -47.5568, -27.8809, 34.8781, 1764.84, 3354.22, 5156.98, 
+2924.77, 4220.09, 5945.49, 54.869, -14.7753, 17.6952, 106.033, 
+752.364, 315.533, 201.13, 132.043, 53.3268, 38.1879, 153.224, 
+164.918, 84.4463, 21.762, 54.4231, 199.737, 8.43104, -21.5154, 
+24.0447, 16.0306, 175.385, 123.68, 85.9635, 69.9593, 838.797, 
+42.3079, 9.28645, 7.80179, 41.7727, 147.448, 124.652, 14.7371, 
+31.7192, 37.8179, 42.2796, 488.885, -46.2152, 132.058, 5.27287, 
+4440.33, -0.0718337, -57.624, 4.71695, 5.46426, 39.1079, 12.6737, 
+321.994, 9.97344, -17.4564, 26.4203, 428.175, 105.465, 2.87448, 
+38.7378, 9.81193, 62.2688, 78.2701, 21.3358, -49.4748, 144.854, 
+23.4393, 19.4808, 341.139, 32.9906, 129.144, 185.672, 168.829, 
+6.00401, 33.8803, 9.36118, 14.9659, 247.173, 82.8192, 13.4658, 
+22.9884, 47.6126, 45.9863, 14.9616, -17.078, 13.3633, -10.6613, 
+149.949, 16.9201, 32.2351, 303.763, 17.3263, 12.6098, 90.374, 
+67.1811, 96.5753, 30.4414, 5.25392, 97.9433, 84.0109, 4791.92, 
+158.83, 70.5196, 25.2591, 10.6006, 4.74133, 328.929, 29.5291, 
+1108.02, 25.4939, 9.86538, 1881.79, 38.0273, 18.6363, 47.8304, 
+-10.7556, 19.3657, 156.49, -4.6479, 24.3279, 177.577, 99.0255, 
+-20.2743, 18.2502, -21.5958, 204.768, 13.9135, 30.9209, 41.149, 
+384.304, 4.3501, 56.0264, 84.2963, 5.9091, 1111.55, 18.1803, 
+35.6877, 36.4223, 28.7847, 336.821, 113.682, 153.298, -12.3375, 
+703.197, 6.54321, 3.4003, 365.171, 948.665, 57.6749, 140.807, 
+-47.5884, 230.304, 35.2882, 92.0679, 119.55, 594.026, 47.8285, 
+1.59722, 141.695, 4590.73, 91.6325, 73.205, -7.3732, 4.2271, 
+54.6507, 13.1526, 354.281, 25.637, 31.0081, 29.8338, 2.26946, 
+26.7666, 362.02, 115.711, 11.7932, -32.3943, 32.0935, 29.629, 
+2198.45, 10.5357, 2.06974, 160.126, 17.9661, 557.344, 30.7372, 
+5.81217, 173.58, 28.031, 113.638, 44.2328, 119.839, 13.3271, 
+3588.49, 180.036, 12.2911, 6.12067, 2513.45, 130.452, 43.649, 
+164.033, 86.9239, -4.89138, 2.61077, 318.083, -9.8494, 226.599, 
+27.9181, 709.636, 58.3088, 8.21628, 53.439, 27.9726, 152.485, 
+56.2261, 35.4081, 49.3529, 23.6595, 101.075, 201.208, 1349.67, 
+4097.11, 57.5865, 46.8813, 2496.72, 4302.08, -14.5668, 4226.52, 
+7.23516, -10.6584, 199.645, 25.6556, 88.8947, -27.3404, 7.1847, 
+123.708, 54.1917, 95.0836, 53.2071, 87.2175, 65.777, 141.115, 
+127.916, 4586.4, 188.076, 373.932, 177.252, 58.2959, 22.0144, 
+78.9151, 8.43176, 264.651, 1104.78, 17.8202, 4534.5, 3.39535, 
+11.9647, -7.74796, -0.772443, -26.6313, 295.923, 4712.16, 3425.1, 
+614.955, 22.927, 10.8969, 148.503, 14.3999, 80.8697, 12.8348, 
+329.268, 673.343, 56.6204, 5771.56, 24.6675, 110.65, 35.7516, 
+41.8782, 44.7822, 19.8892, 41.73, 19.3424, 298.774, 37.7131, 
+3728.22, 36.5436, 48.8184, 28.1586, 54.0515, 3337.96, 20.775, 
+279.927, 18.8433, 32.674, 14.6679, 29.86, 12.9458, 19.2027, -2.83335, 
+3800.89, 3485.23, 20.018, 6.81922, 171.361, 23.6272, 82.1207, 
+183.374, 27.095, 260.132, 108.528, 184.085, 61.5014, 1167.08, 
+1433.71, 135.186, 31.2864, 434.736, 17.5452, 91.0749, 21.8009, 
+99.108, 210.107, 20.1143, 54.7748, 175.689, 1361.39, 270.05, 
+1.2547, -11.7241, 29.3876, 138.432, 10.7093, 10.0032, 10.2681, 
+18.3958, 7.03457, 512.672, 440.222, 1362.39, 910.424, 44.8842, 
+3.24524, 103.19, 183.772, 15.0041, 5.54029, -8.76264, -22.0844, 
+38.0021, -25.9207, 264.602, 55.2672, 206.417, 594.362, 448.783, 
+20.5519, 336.445, 171.817, -39.842, 8.79081, 50.1709, 58.1773, 
+46.4573, 46.5964, 43.8317, 37.5065, -2.50102, 9.116, -12.1285, 
+-5.29367, 36.3098, 370.765, 6.12811, -26.2998, 59.922, 99.4379, 
+23.3231, 38.6395, 41.8341, 163.323, 2.35223, -33.2088, -0.318706, 
+700.347, 149.244, 149.939, 444.315, 197.612, 65.3287, 672.978, 
+20.2036, 60.3929, 2.13584, 16.3533, 25.6992, 33.6586, 1906.36, 
+228.049, 17.1178, 48.7949, 146.708, 209.255, 89.5143, 329.467, 
+-84.1617, 9.28273, 73.3277, 150.263, 402.813, 724.912, 93.5619, 
+26.9338, -3.23502, 4343.81, 84.6119, 176.598, 273.432, 468.032, 
+20.1705, 20.3546, 250.216, 300.855, 31.8932, -0.101973, 2796.81, 
+353.51, 464.394, 110.78, 19.739, 21.7774, -1.61634, 189.76, 178.32, 
+10.1773, 29.4681, 2330.43, 1832.11, 163.47, 4295.36, 1.24901, 
+169.036, 51.2922, 162.709, 210.078, 101.101, -44.4698, 60.07, 
+31.3394, 30.0544, 26.2902, 162.19, 23.6549, 193.004, 15.0567, 
+284.328, 304.22), U = c(157.989, -8.68811, 26.872, 11.9186, 48.6462, 
+73.4221, 142.913, 98.8425, 51.5609, 52.9338, 501.744, 61.9548, 
+49.8289, 34.6108, 18.0297, 156.179, 87.3699, 37.4892, -21.2394, 
+193.205, 104.147, 48.4806, 9682.71, 36.3847, 76.8974, 24.4563, 
+50.9666, 51.7285, 73.0255, 24.2106, 81.0265, 47.44, 82.9362, 
+22.7492, 30.1752, 86.5914, 36.8239, 14.7646, 162.673, 253.176, 
+234.595, 516.142, 3.69034, -48.9365, 65.8244, 1617.96, 2640.46, 
+3657.65, 3819.17, 4090.65, 4454.83, 74.8586, 30.8665, 115.707, 
+89.1666, 506.21, 387.529, 136.212, 126.173, 62.8923, 40.0836, 
+202.828, 177.232, 78.8619, 45.8239, 79.8199, 403.987, 19.3334, 
+-4.33529, 11.4801, 9.01189, 195.923, 148.046, 137.08, 88.7213, 
+1731.1, 5.7097, 65.7457, 11.6924, 164.186, 62.7575, 170.711, 
+27.103, 19.0265, 77.2922, 43.5574, 689.458, 17.2022, 158.953, 
+19.0796, 1570.76, 11.1243, -47.8425, 10.6524, -0.824531, 67.9613, 
+18.0697, 456.784, 4.19371, -26.2001, 62.0666, 313.22, 106.68, 
+5.68857, 98.9954, 27.1199, 81.5302, 135.078, 13.4029, 2.27847, 
+222.449, 27.6569, 36.3149, 319.741, -3.24216, 86.4926, 279.68, 
+302.545, 0.710896, 9.79766, 35.8284, 20.4802, 428.874, 93.8246, 
+8.23201, 37.7287, 72.151, 65.6202, 47.0053, 0.315092, 21.1461, 
+-8.71233, 164.907, 41.8224, 39.359, 424.272, 3.92809, 14.0193, 
+129.938, 118.107, 110.441, 57.8896, 903.554, 84.1557, 90.7458, 
+2653.41, 355.276, -1816.64, 7.02804, 8.16405, 9.63254, 371.113, 
+68.6348, 875.156, 22.8315, 12.7834, 2908.65, 73.0268, 19.0389, 
+97.903, -18.5831, 30.1621, 141.008, 15.9366, 20.1853, 627.3, 
+247.215, -17.4408, 89.5689, -11.199, 164.223, 25.376, 43.2611, 
+165.297, 467.893, 13.1353, 98.6927, 140.993, 11.9114, 1813.87, 
+67.8542, 25.6188, 22.4116, 82.7, 460.699, 124.313, 238.174, 8.88709, 
+1043.82, 25.7917, 39.0679, 109.691, 209.892, 103.859, 245.403, 
+10.1044, 311.758, 35.0417, 156.112, 129.443, 773.753, 54.0158, 
+19.2496, 195.573, 3191.4, 60.8176, 85.4708, 78.6881, 8.26688, 
+106.968, 22.7105, 343.198, 33.6467, 58.9204, 30.6993, 21.9813, 
+34.1661, 397.846, 172.861, 18.11, -14.0195, 49.0661, 19.4589, 
+485.993, -5.94627, 19.3554, 203.228, 15.4995, 182.748, 33.6588, 
+12.4801, 250.566, 89.4413, 1.24338, 62.8193, 135.39, 26.084, 
+66.58, 304.39, 15.5656, 0.0976848, 2026.74, 93.9433, 50.5064, 
+136.347, 107.083, 0.193948, 56.348, 559.336, -1.34568, 131.805, 
+28.0195, 78.0697, 40.3857, 4.25619, 106.778, 46.9773, 146.015, 
+120.829, 175.308, 45.3821, 24.7305, 164.084, 298.482, 265.155, 
+1623.42, 120.842, 74.8246, 873.725, 1696.78, -58.2311, 2161.09, 
+154.495, 21.3336, 230.491, 137.396, 34.7623, -58.6789, 11.4523, 
+69.9525, 116.551, 48.5494, 151.926, 187.422, 154.078, 123.855, 
+95.9424, 2044.5, 491.992, 529.63, 340.004, 120.157, -10.32, 69.8532, 
+34.5671, 327.885, 636.459, 80.0114, 3073.94, -1.47433, 16.6172, 
+-27.206, 24.0632, -93.0832, 310.202, 2273.54, 1030.79, 692.127, 
+50.6523, 0.0949905, 163.055, 35.4072, 126.346, -0.203757, 441.602, 
+770.905, 125.032, 5956.98, 36.5848, 162.222, 51.3298, 20.8305, 
+15.5991, 25.9609, 58.655, 52.9268, 333.587, 96.7429, 1602.47, 
+97.4173, 86.7895, 21.8971, 89.7959, 1174.03, 25.7309, 35.7276, 
+57.156, 44.3944, 28.3338, 128.169, 32.7755, 138.659, 15.3786, 
+1535.37, 3200.62, 62.304, 183.76, 149.049, 8.71382, 196.735, 
+309.498, 178.323, 237.073, 96.5753, 272.477, 80.7959, 1641.59, 
+1393.03, 88.4958, 49.7455, 107.804, 1.72709, 216.482, 37.8761, 
+263.464, 95.4082, 18.0926, 73.9372, 119.028, 1342.88, 259.724, 
+1.22813, 23.9773, 57.3953, 183.088, 45.7202, 18.3849, 26.61, 
+55.6054, -0.706882, 556.393, 421.879, 1167.84, 517.988, 59.9694, 
+3.20685, 206.993, 312.68, 22.9889, 18.4686, 4.63857, -30.2465, 
+89.4418, -33.5483, 234.894, 140.073, 299.794, 647.004, 226.003, 
+15.86, 335.638, 67.1859, -51.8662, 31.7451, 83.9066, 41.8285, 
+42.0325, 32.7291, 119.85, 39.4677, 30.8266, 5.43731, -28.7512, 
+-1.65284, 78.5071, 261.552, 8.97927, -51.5476, 51.7288, 150.168, 
+14.6407, 45.8702, 87.2712, 130.708, 6.04671, -55.0078, 3.91318, 
+826.722, 190.35, 215.967, 315.772, 185.466, 37.9453, 186.14, 
+14.3975, 23.4929, 25.426, 17.2156, 6.52523, 68.4645, 390.197, 
+373.666, 48.2707, 70.0616, 151.743, 201.533, 140.316, 349.969, 
+-33.2442, 15.2186, 98.48, 276.547, 25.9707, 517.012, 214.317, 
+33.5505, -2.96451, 2726.88, 90.5135, 245.165, 318.465, 467.27, 
+13.3121, 23.4317, 308.334, 305.01, 47.6936, 5.27658, 1097, 378.496, 
+613.637, 52.5746, 39.5571, 49.8384, -12.1801, 195.255, 178.577, 
+11.7318, 12.5255, 1648.03, 1427.1, 243.458, 2091.88, -6.21422, 
+272.611, 59.9022, 424.443, 250.476, 211.563, -42.4763, 97.4135, 
+21.3433, 34.6708, 59.0011, 191.443, 28.995, 282.507, 21.9004, 
+223.679, 247.843), V = c(146.8, 85.0212, 31.1488, 12.8324, 90.2215, 
+64.6066, 187.132, 92.0846, 48.1247, 15.7267, 659.613, 58.0325, 
+88.3787, 36.9725, 28.012, 249.872, 130.509, 69.9946, -38.734, 
+294.238, 168.992, 79.3437, 10396.1, 58.1014, 104.428, 59.6125, 
+27.7013, 60.7026, 189.186, 37.1239, 87.2832, 32.3454, 129.234, 
+49.4815, 39.3013, 144.819, 89.547, 19.1634, 192.314, 233.304, 
+232.416, 691.134, 15.2424, -29.8916, 37.2982, 1198.8, 2378.58, 
+2860.87, 3879.76, 4507.62, 4098.65, 54.4923, 16.7083, 98.5723, 
+84.3737, 596.467, 434.575, 73.1467, 163.036, 53.4802, 58.4489, 
+204.88, 196.61, 89.4526, 47.7735, 90.0391, 348.738, 51.0633, 
+11.8902, 2.31597, 9.60877, 242.327, 149.534, 153.576, 132.633, 
+3006.34, 2.60968, 109.943, 25.9401, 70.5182, 118.336, 173.694, 
+17.664, 5.00616, 93.2511, 73.8148, 848.672, 14.9824, 104.303, 
+18.5045, 2350.16, 52.1706, 4.98633, 24.2924, 15.9269, 63.3791, 
+4.59506, 336.982, 17.333, -22.031, 35.598, 288.123, 154.099, 
+6.85971, 196.454, 46.4389, 45.5724, 129.7, 16.933, 31.0391, 193.007, 
+11.3017, 68.8202, 365.599, 81.2111, 171.59, 180.212, 300.681, 
+32.2205, 8.08239, 55.0635, 43.0479, 415.1, 140.86, 27.6083, 50.3935, 
+108.081, 46.7669, 93.0661, 4.387, 32.655, -36.8072, 128.504, 
+67.4608, 49.1855, 430.627, 7.29553, 30.7981, 115.461, 99.4041, 
+120.119, 79.4284, -8.70355, 129.377, 111.452, 2636.2, 283.657, 
+152.508, 10.2713, 21.833, 12.0283, 384.157, 111.401, 1552.5, 
+70.0416, 9.38613, 3105.92, 69.0755, 14.0697, 72.8632, 1.86091, 
+12.6286, 165.686, 23.575, 29.6849, 291.643, 136.994, 12.2572, 
+116.667, -9.89752, 162.058, 14.9847, 135.385, 134.205, 282.957, 
+31.3019, 79.3672, 129.701, 25.2638, 2063.8, 85.4085, 22.2778, 
+35.5618, 68.1409, 477.608, 159.587, 177.912, 12.3833, 1504.4, 
+89.2294, 36.7813, 100.322, 178.409, 74.2343, 145.029, 22.5529, 
+338.865, 70.4458, 143.998, 137.354, 718.835, 92.2865, 44.6636, 
+294.612, 3153.36, 107.572, 127.595, 66.1574, 20.5912, 123.183, 
+38.7749, 538.56, 54.1507, 73.0012, 55.4213, 58.4307, 28.2636, 
+558.944, 130.972, 9.68121, 34.9358, 75.5451, 10.1148, 242.757, 
+25.2692, 31.3001, 186.852, 23.7675, 243.991, 124.371, 12.6768, 
+219.736, 74.2949, 15.8069, 64.9143, 141.896, 46.0688, 18.6799, 
+228.678, 17.3736, 14.7902, 904.369, 30.203, 39.7144, 200.381, 
+242.083, 29.385, 39.6679, 217.316, 0.453118, 146.591, 27.3242, 
+99.2733, -6.54072, 6.56623, 172.795, 67.0636, 498.539, 140.281, 
+126.26, 77.8774, 31.0841, 234.303, 259.19, 271.516, 3717.97, 
+94.2988, 71.7809, 694.162, 1565.52, -7.65442, 2008.76, 56.0799, 
+14.7563, 254.124, 152.548, 3.96758, -112.889, 23.7309, 43.959, 
+115.697, 21.7522, 84.5736, 143.954, 144.098, 98.6888, 48.2402, 
+1436.37, 341.351, 401.483, 309.221, 93.2162, 48.3087, 76.9098, 
+46.6884, 273.507, 266.358, 67.4139, 2866.11, 20.2726, 16.3465, 
+-29.4872, 11.5116, -204.174, 332.45, 1994.19, 1184.78, 392.023, 
+44.7525, 36.1219, 110.905, 39.2748, 117.471, 22.0005, 513.787, 
+927.413, 125.58, 6498.24, 84.7558, 104.13, 57.8553, 58.1969, 
+-28.5082, 6.40566, 107.818, 92.3361, 404.992, 83.7837, 1459.51, 
+76.4665, 66.6122, 7.24202, 113.211, 954.436, 22.4689, 32.1727, 
+48.0985, 27.3616, 36.9859, 179.13, 47.7911, 188.365, 28.236, 
+1653.81, 1759.21, 48.8833, 146.243, 159.633, 35.2368, 116.22, 
+359.115, 77.2792, 145.838, 81.4343, 290.231, 152.031, 1603.45, 
+1937.63, 75.9467, 61.9098, 80.9726, -7.0814, 134.276, 49.8239, 
+185.681, 94.0413, 17.4167, 59.2552, 106.439, 1243.49, 162.989, 
+9.0091, 38.2842, 146.055, 211.768, 48.178, 23.925, 73.9306, 64.0879, 
+45.589, 662.33, 516.529, 687.539, 140.826, 134.102, 11.9479, 
+255.559, 640.483, 50.5054, 26.5233, 13.8135, -62.5521, 50.5043, 
+56.0148, 340.46, 193.713, 234.002, 565.911, 286.525, 28.1796, 
+349.433, 101.645, -92.2694, 10.4707, 75.8019, 98.9545, 2.58892, 
+45.9471, 159.292, 98.5365, 29.5933, 5.29836, -33.1193, 22.5066, 
+63.4782, 291.064, 17.8339, 13.534, 89.7338, 138.021, 53.3355, 
+47.8456, 114.431, 128.613, 13.7885, -87.8064, 3.74718, 738.26, 
+314.237, 239.549, 134.137, 186.247, 3.33742, 190.915, 8.25899, 
+-1.16246, 27.3675, 39.4051, 25.0474, 148.14, 212.304, 266.504, 
+11.992, 54.1384, 35.5603, 284.945, 148.733, 329.237, 36.8865, 
+18.7155, 77.6382, 324.99, 42.4623, 979.981, 210.802, 68.029, 
+-0.70452, 929.993, 122.7, 286.294, 204.529, 657.229, 4.27519, 
+29.4157, 249.475, 231.63, 10.1838, 15.7454, 1418.74, 554.93, 
+590.865, 83.5738, 96.2179, 65.2052, 28.1082, 274.239, 144.532, 
+18.8459, 15.9159, 568.05, 826.803, 177.082, 2839.7, -25.3921, 
+214.296, 88.9582, 262.805, 197.053, 159.425, -1.24586, 152.398, 
+20.8587, 32.8964, 87.765, 159.64, 58.8501, 504.189, 31.6534, 
+273.78, 202.284), W = c(93.8829, 79.2998, 22.342, 11.139, 42.0053, 
+40.3068, 170.583, 53.3866, 31.8358, 15.2116, 590.156, 28.7707, 
+91.5539, 16.9959, 24.8743, 141.803, 91.7096, 42.8123, -44.2136, 
+197.745, 109.586, 42.6647, 8365.8, 40.3792, 68.447, 22.6792, 
+30.9739, 43.9691, 104.818, 23.3193, 30.0672, 36.1116, 96.675, 
+24.9362, 18.2112, 79.414, 73.7415, 11.4693, 125.129, 234.052, 
+180.548, 780.294, 20.5804, -27.1269, 27.4847, 2573.87, 3477.17, 
+4471.09, 4331.77, 5276.04, 5664.37, 67.9535, 25.6475, 76.769, 
+68.6645, 569.912, 448.872, 84.3918, 151.687, 70.5891, 46.049, 
+163.378, 205.215, 85.3799, 20.69, 52.4086, 217.039, 28.319, 8.98009, 
+2.49221, 7.2658, 132.225, 113.424, 90.7812, 49.4236, 194.233, 
+-2.22783, 12.3812, 2.20869, 11.5695, 99.7647, 128.898, 19.5615, 
+35.292, 94.5332, 67.4591, 554.534, 7.66178, 125.216, 14.4581, 
+2937.07, 16.2097, -13.3297, 8.89613, 0.268704, 53.3312, -3.18541, 
+400.768, 7.91864, -22.0276, 27.0425, 307.79, 117.905, 1.04752, 
+62.4551, 47.2319, 47.9187, 95.9799, 22.9395, 20.0366, 186.816, 
+31.649, 46.0998, 480.031, 60.3285, 164.009, 200.208, 161.315, 
+56.6931, 9.0717, 23.3418, 29.9439, 311.585, 105.587, 18.0468, 
+27.286, 52.2595, 41.7338, 41.9092, -6.27292, 15.0346, 2.49389, 
+158.706, 47.6087, 63.6269, 371.786, 14.0691, 20.6185, 83.1104, 
+88.1335, 74.1428, 88.3365, -16.7579, 109.776, 78.3542, 3723.43, 
+181.918, 127.877, 39.8845, 36.89, 6.36301, 370.387, 60.0514, 
+1250.16, 45.784, 17.0307, 2659.47, 39.4764, 8.75707, 67.4581, 
+3.32201, 6.27112, 109.75, 0.0379001, 18.788, 219.604, 83.3589, 
+0.223356, 72.8466, -3.92575, 115.845, 15.8586, 100.997, 110.407, 
+293.455, 34.1911, 77.0416, 120.623, 13.4395, 1331.91, 31.2241, 
+8.70833, 25.7259, 59.1483, 305.94, 77.5733, 178.913, 16.5687, 
+1227.09, 25.6378, 25.5943, 424.363, 1060.22, 66.4364, 214.827, 
+10.2609, 326.249, 58.4576, 316.629, 103.313, 630.475, 56.2809, 
+20.6089, 197.695, 4188.16, 130.831, 85.652, 54.0967, -0.698646, 
+50.5705, 16.5062, 228.745, 39.6945, 45.1939, 13.7713, 24.4483, 
+23.2166, 421.695, 141.163, 5.23799, 14.9818, 42.4541, 14.3148, 
+1018.29, 44.1777, 18.0954, 174.692, 1.13532, 177.388, 76.7073, 
+6.18476, 211.823, 91.4271, 3.23425, 43.7706, 118.826, 27.0587, 
+2702.13, 235.38, 10.0865, 5.50446, 2175.88, 51.4997, 50.5894, 
+95.3916, 148.45, 6.40436, 23.5829, 330.852, -0.310719, 207.436, 
+21.3795, 284.009, 36.3695, -7.45753, 108.835, 28.6744, 351.821, 
+81.5486, 162.442, 66.8129, 7.60735, 162.102, 287.533, 631.07, 
+3388.32, 79.7706, 57.3322, 1271.83, 2471.53, -29.1697, 3267.69, 
+5.95262, 32.91, 194.936, 86.4109, 53.1509, -41.465, 15.2884, 
+72.1419, 64.2053, 201.034, 164.92, 232.637, 267.261, 104.615, 
+246.293, 3545.06, 668.983, 390.615, 206.928, 113.631, 17.5142, 
+107.777, 23.6411, 285.105, 894.496, 30.4761, 3370.49, 9.77489, 
+18.472, -14.7844, 16.7371, -113.75, 389.444, 3420.63, 1801.31, 
+572.056, 43.4844, 11.8425, 99.7886, 17.1879, 101.741, 12.4638, 
+282.006, 757.723, 68.368, 7042.88, 49.1817, 100.521, 41.5229, 
+48.4048, 1.87017, 1.50182, 73.7493, 47.2105, 326.063, 51.7689, 
+2653.49, 66.4281, 77.9568, 11.6907, 52.1105, 1675.42, 34.4654, 
+294.214, 24.6104, 17.815, 28.1464, 124.825, 28.0614, 5.60878, 
+17.4288, 2473.69, 2296.06, 14.6744, 4.47085, 168.622, 27.3937, 
+86.2253, 270.465, 40.3882, 117.987, 86.8032, 230.207, 85.7811, 
+1289.93, 1702.7, 145.237, 63.6695, 125.432, 3.0438, 89.7088, 
+21.3173, 132.6, 116.694, 15.4594, 45.2788, 184.129, 1587.01, 
+157.617, -0.493317, 9.90994, 97.5666, 144.692, 34.5865, 7.931, 
+40.2999, 27.9275, -3.58742, 485.435, 437.813, 1452.56, 574.669, 
+86.8385, 23.5322, 171.905, 224.899, 32.7434, 13.9438, 13.343, 
+-40.59, 25.1954, 44.9909, 245.033, 127.305, 177.074, 440.508, 
+290.957, 15.9839, 294.587, 101.032, -35.4977, 6.72849, 46.2628, 
+58.8674, 0.475095, 34.3861, 130.95, 54.8103, 15.4945, -0.39281, 
+-21.281, 6.00761, 72.1088, 250.751, -0.406172, 7.80526, 59.6821, 
+132.221, 36.7295, 23.074, 56.5949, 293.273, 6.76556, -46.7689, 
+3.47536, 748.806, 294.336, 146.912, 271.733, 219.698, 62.569, 
+345.02, 3.13008, 30.308, 6.17931, 18.9706, 13.9386, 89.2086, 
+748.361, 358.791, 109.327, 49.8742, 110.424, 319.118, 98.7191, 
+310.937, 29.6553, 22.2504, 123.248, 201.381, 272.266, 1368.36, 
+143.957, 51.4594, 4.59039, 2751.79, 72.3933, 219.441, 271.931, 
+494.064, 10.4994, 15.2219, 236.647, 314.185, 5.56465, 11.6035, 
+2087.89, 422.794, 390.361, 66.1281, 66.8283, 41.6442, 17.8877, 
+207.359, 185.938, 15.4422, 0.0721809, 2390.02, 2842.8, 188.211, 
+3583.67, -13.5936, 213.801, 72.5324, 184.59, 223.815, 144.363, 
+-0.491996, 95.4303, 53.5745, 23.847, 43.1828, 122.662, 50.3786, 
+318.681, 22.925, 283.962, 180.556), X = c(103.855, 71.6552, 19.0135, 
+7.55564, 57.5738, 41.8209, 133.279, 52.0164, 29.9264, -5.35282, 
+461.23, 48.5346, 40.2298, 8.39896, 17.7428, 117.473, 77.9277, 
+63.8059, -23.6993, 203.531, 106.757, -12.6489, 9345.94, 33.9219, 
+84.325, 26.541, 20.4447, 12.9576, 129.619, 39.302, 32.4333, 36.6902, 
+94.5572, 27.0847, 15.2479, 64.4091, 52.7497, -2.53228, 77.664, 
+85.4302, 81.7355, 981.646, 38.5142, -17.5833, 27.7867, 1552.46, 
+3626.69, 5900.96, 965.54, 2335.83, 5219.36, 56.3916, 11.4089, 
+8.23804, 45.1092, 590.292, 404.212, 158.902, 172.453, 70.8063, 
+75.0311, 132.294, 227.772, 40.4406, 32.6849, 55.5681, 186.463, 
+15.9432, 7.08868, 9.96418, -12.0555, 204.795, 136.208, 67.8371, 
+47.1633, 130.277, -3.05798, 15.524, 0.394058, -0.575181, 116.937, 
+137.411, 15.8249, 27.7821, 56.4698, 72.6469, 793.019, -3.20777, 
+166.785, 20.0154, 3257.57, 27.9982, -0.0363981, 25.4436, 10.4671, 
+38.5609, 3.58018, 404.834, -4.70361, -11.9295, 43.1111, 84.1063, 
+69.6939, 1.9759, 77.2344, 12.9422, 45.3537, 51.7135, 8.80947, 
+7.73061, 130.009, 9.35285, 34.4833, 433.679, 27.4743, 158.522, 
+215.065, 179.114, 26.4954, 9.3366, 23.7929, 13.452, 199.349, 
+105.274, -0.691375, 17.7547, 4.10314, 35.5965, 44.8385, -0.221245, 
+14.5359, -16.4445, 105.255, 38.4129, 66.9824, 382.957, 15.7831, 
+14.7568, 67.7456, 74.4817, 85.8083, 79.3688, -11.9028, 95.3734, 
+88.6175, 3638.23, 179.778, 81.8201, 21.4498, 25.1334, 13.3877, 
+373.739, 41.2316, 1690.04, 42.6084, 26.4521, 2174.18, 35.9456, 
+17.0905, 26.4139, 12.1516, 7.7893, 101.429, 3.61813, 25.9043, 
+165.546, 165.029, 2.21347, 41.351, -15.7535, 196.906, 5.87379, 
+71.1112, 112.901, 307.683, 13.0548, 71.6915, 87.8448, 13.656, 
+1324.22, 68.4614, 13.8467, 15.6624, -2.11244, 297.141, 107.993, 
+217.546, 8.23705, 872.009, 70.5007, 20.4041, 198.528, 839.796, 
+78.6212, 64.8983, 6.00077, 245.485, 54.9742, 172.73, 102.901, 
+624.53, 66.6335, 29.4896, 180.67, 5833.66, 116.569, 74.2093, 
+58.8941, 11.4795, 38.9307, 24.9464, 238.739, 50.3452, 25.8187, 
+30.6562, 27.1836, 24.7247, 461.369, 149.096, 4.03206, 31.8861, 
+58.9681, 4.73846, 1079.05, 10.5102, 10.7358, 171.903, 21.6532, 
+1614.61, 69.1148, -1.06577, 246.209, 60.9519, 8.55947, 53.5345, 
+107.852, 15.5495, 1089.79, 100.743, -9.84966, 8.50146, 2509.63, 
+88.4241, 11.468, 93.436, 136.846, 14.834, 12.8876, 87.0857, -4.64621, 
+227.816, 12.562, 421.94, 16.9143, 2.74598, 63.8839, 17.5857, 
+413.069, 87.988, 46.8763, 79.4983, 23.5537, 156.533, 142.026, 
+625.897, 3069.9, 93.4094, 50.3598, 1902.77, 3014.6, -71.304, 
+3680.73, -1.80914, 19.1538, 190.056, 52.2877, 60.5452, -23.5987, 
+-1.91455, 103.818, 31.699, 134.021, 37.0279, 52.1777, 73.3428, 
+276.737, 287.212, 3643.06, 113.995, 339.686, 198.545, 79.3342, 
+98.5352, 82.1863, 22.447, 239.447, 1430.28, 32.5284, 3884.78, 
+15.1339, 17.3066, -6.03283, 29.8269, -58.3026, 313.006, 4781.54, 
+2323.54, 536.467, 29.7574, 10.0447, 152.661, 18.8966, 109.161, 
+2.93635, 301.283, 646.211, 59.3143, 5632.2, 42.6628, 82.368, 
+50.862, 63.6873, 6.28557, 6.79988, 64.1165, 61.7862, 296.761, 
+68.4204, 3511.48, 62.6788, 66.0424, 16.0121, 83.9819, 2693.64, 
+33.3963, 541.391, 24.8203, 25.8722, 20.7669, 405.887, 16.5432, 
+-11.8931, 9.47242, 3512.12, 3913.11, 28.1157, 0.942018, 198.992, 
+24.5918, 133.321, 320.601, 45.0174, 152.439, 49.5598, 168.985, 
+72.77, 1044.1, 1593.03, 99.944, 41.6344, 239.253, 8.03384, 87.8811, 
+27.0239, 50.1334, 137.746, 18.3693, 123.532, 217.189, 1474.25, 
+160.646, 6.16888, 6.51786, 69.9984, 131.152, 16.941, 3.84455, 
+34.2437, 24.9068, -3.62168, 379.14, 373.372, 1373.67, 1082.74, 
+83.0411, 12.5, 133.863, 195.145, 23.0121, 6.82277, -9.81922, 
+-3.47117, 56.0757, 31.1144, 260.057, 144.496, 207.943, 650.587, 
+296.833, -2.61181, 309.397, 84.0845, -43.7302, 14.4997, 120.602, 
+62.3774, 2.61724, 20.4225, 101.752, 37.9427, 12.9264, 7.63623, 
+-20.0477, 25.8764, 65.8894, 314.29, 7.61551, 10.3069, 53.5564, 
+145.203, 68.0812, 86.306, 55.2896, 122.202, -1.52974, -65.4116, 
+-0.873269, 628.029, 288.948, 178.474, 669.091, 180.865, 48.6863, 
+312.838, 7.52951, 49.6373, 15.7523, 26.4832, 19.6958, 88.0791, 
+1157.78, 369.865, 2.1029, 56.2654, 225.17, 370.433, 102.009, 
+376.608, 26.6551, 15.7319, 40.9501, 158.392, 127.145, 1200.37, 
+146.255, 36.6009, -2.10472, 4898.71, 45.5338, 188.234, 170.369, 
+404.419, 9.80528, 11.8492, 255.268, 323.192, -8.35253, 12.1275, 
+3268.36, 445.377, 382.372, 50.5897, 52.3964, 32.0701, 5.56768, 
+212.712, 106.366, 9.38988, -15.6778, 2116.01, 678.949, 264.591, 
+3558.35, -10.315, 182.813, 51.2728, 221.997, 214.561, 231.79, 
+-3.55962, 98.0544, 21.0206, 52.5622, 46.7389, 144.45, 30.4269, 
+304.96, 14.9017, 230.878, 247.59), Y = c(64.434, 64.2369, 12.1686, 
+19.9849, 44.8216, 46.1087, 187.407, 65.9154, 37.8611, 13.1884, 
+367.433, 31.1489, 36.2151, 41.0271, 34.7923, 126.114, 129.627, 
+50.1246, -38.6532, 181.623, 90.1958, 37.4389, 8252.65, 23.7046, 
+46.6156, 30.6529, 14.6951, 16.9243, 91.4007, 25.4601, 20.7603, 
+30.3978, 59.0705, 24.7106, 16.143, 72.0106, 30.1115, 1.63297, 
+197.797, 499.756, 352.708, 1662.26, 6.94581, -38.1436, 53.7229, 
+2323.13, 3276.53, 3914.43, 3999.14, 4771.61, 4448.73, 81.5114, 
+13.4753, 55.5644, 39.1224, 489.808, 346.004, 118.373, 107.175, 
+76.3004, 30.3936, 143.483, 173.181, 52.6598, 27.0883, 48.0123, 
+209.379, 30.3679, 2.3115, 28.1439, 3.83654, 188.775, 87.3997, 
+136.297, 100.923, 3595.46, 7.79922, 187.656, 16.3697, 141.183, 
+79.4596, 112.344, 20.7649, 16.9782, 84.3264, 44.8918, 629.055, 
+22.3966, 99.9854, 26.0274, 2532.94, 18.3218, -23.3218, 33.7587, 
+11.0642, 56.9848, 14.2393, 293.748, 15.9607, -14.1471, 29.6764, 
+382.133, 128.27, 4.71653, -220.107, 12.1819, 79.097, 205.179, 
+13.0671, 3.55578, 151.32, 16.0169, 30.5214, 198.184, 76.6212, 
+140.886, 113.38, 178.667, 22.2304, 13.2707, 26.3927, 23.7605, 
+264.064, 95.6504, 19.7899, 21.6213, 56.3858, 30.2128, 48.8188, 
+3.19005, 18.608, -20.9676, 151.208, 35.7417, 47.3164, 333.499, 
+8.86286, 55.5017, 94.081, 86.7739, 54.8253, 68.9776, -18.072, 
+129.709, 67.4869, 3659.51, 277.895, 84.8364, 28.3289, 33.0593, 
+-11.8278, 360.766, 57.256, 1069.6, 18.9821, 8.01176, 2442.02, 
+38.3782, 12.7976, 77.7258, -3.5095, 8.89093, 161.079, 9.12265, 
+8.02902, 220.578, 74.5015, 3.18391, 46.0466, -12.0782, 113.445, 
+30.5579, 149.118, 115.344, 285.885, 11.0866, 63.4076, 119.496, 
+21.3215, 1227.09, 51.6233, 45.6924, 35.5513, 34.4882, 299.461, 
+86.7734, 120.669, 5.09833, 672.499, 38.728, 52.5188, 515.891, 
+1046.02, 72.8346, 92.867, 12.066, 282.087, 44.848, 274.913, 130.913, 
+538.964, 60.7766, 25.2943, 217.75, 4273.07, 104.672, 87.2302, 
+60.3566, 11.6709, 83.4133, 19.6816, 239.786, 73.9264, 36.0309, 
+33.3687, 26.1832, 28.3214, 337.965, 127.288, -0.606596, 54.0417, 
+31.1683, 13.4045, 805.616, 10.0587, 20.1677, 187.757, 11.2774, 
+328.201, 84.7311, 2.97481, 216.429, 119.826, 15.2975, 77.9347, 
+92.9012, 22.1988, 349.427, 189.126, 38.4599, 40.6279, 1433.23, 
+48.5369, 28.5485, 160.872, 143.716, 4.11928, 21.8384, 239.402, 
+10.6622, 278.97, 21.3151, 294.656, -10.3959, 8.45477, 97.329, 
+60.5502, 278.355, 107.299, 245.074, 44.4103, 7.58657, 134.182, 
+252.512, 497.34, 2769.34, 86.3409, 34.5141, 1142.92, 1870.69, 
+2.52721, 2870.88, 79.2371, 37.1837, 169.325, 107.026, 30.3164, 
+-42.5712, 17.7072, 63.9556, 82.9713, 105.271, 210.32, 312.184, 
+385.856, 132.273, 86.1813, 3268.61, 1024.69, 442.88, 159.222, 
+90.5501, 30.9035, 129.247, 34.7197, 196.487, 730.505, 44.1833, 
+2962.86, -1.73042, 34.7037, -17.6214, 16.2378, -134.863, 191.506, 
+3243.49, 1811.76, 489.651, 50.6778, 23.61, 114.661, 22.8506, 
+101.677, 10.8915, 231.014, 642.812, 94.4195, 5150.34, 59.8757, 
+101.893, 32.2673, 17.2878, 45.2713, 13.6043, 80.8419, 55.7107, 
+366.833, 55.2646, 2756.04, 99.2655, 57.991, 4.07751, 73.0566, 
+1760.5, 26.4565, 120.745, 29.9676, 44.3971, 30.3502, 111.041, 
+35.1207, 134.878, 26.4519, 2476.15, 2520.83, 50.1819, 157.964, 
+128.774, 44.9872, 81.1903, 197.019, 33.9799, 108.207, 116.09, 
+240.46, 120.025, 1987.3, 1480.16, 64.9968, 136.84, 109.756, 11.1087, 
+78.8428, 38.8894, 123.502, 93.0791, 27.0456, 40.8247, 180.841, 
+1124.35, 148.854, 0.0595516, 10.5117, 72.4034, 108.195, 41.2199, 
+27.2082, 33.6403, 34.726, -11.3763, 361.092, 480.253, 795.996, 
+373.703, 64.0276, 20.7283, 180.364, 456.108, 27.8536, 28.7937, 
+1.9343, -21.0062, 40.4928, -92.5084, 277.745, 94.2212, 165.025, 
+449.793, 202.659, 17.8172, 251.218, 83.4933, -38.6925, 23.1082, 
+54.3242, 65.7657, 38.7528, 74.0051, 47.5855, 52.602, 7.69903, 
+1.74712, -29.3427, -2.28681, 42.1297, 294.078, 18.4532, -8.80464, 
+60.0974, 116.354, 9.94368, 21.8901, 58.8993, 177.867, 10.6735, 
+-52.5324, 14.8375, 978.88, 273.75, 172.095, 286.423, 146.15, 
+26.1367, 168.8, 23.6742, 45.756, 32.3425, 9.63194, 14.6851, 83.4002, 
+529.178, 346.757, 49.8069, 35.9698, 116.649, 322.733, 101.629, 
+397.616, 19.1037, 13.7456, 104.526, 79.0888, 246.038, 1287.93, 
+177.426, 57.425, -3.21138, 2319.23, 113.941, 204.927, 223.964, 
+441.536, 85.3879, 13.6376, 227.602, 57.5928, 130.555, 5.87376, 
+2155.53, 290.081, 376.909, 92.0564, 59.0583, 31.764, 16.2211, 
+215.908, 142.984, 16.4043, 7.04334, 1406.45, 1583.27, 131.581, 
+3462.2, 7.78682, 172.987, 45.3099, 220.598, 198.221, 165.068, 
+-19.3646, 100.473, 51.6015, 20.089, 28.9834, 102.521, 35.5309, 
+318.736, 22.7341, 216.652, 137.959), Z = c(175.615, 78.7068, 
+17.378, 8.96849, 61.7044, 49.4122, 144.784, 75.0043, 60.4772, 
+10.0385, 790.943, 72.4567, 73.5309, 21.088, 40.2213, 210.561, 
+91.7803, 134.588, -40.7251, 234.953, 116.069, 62.0706, 4652.85, 
+45.1485, 74.5315, 29.4477, 33.8544, 35.2928, 102.621, 28.4838, 
+89.5884, -53.8352, 71.216, 31.3545, 23.4662, 68.812, 38.833, 
+16.6207, 188.116, 312.653, 309.973, 976.528, 19.5267, -29.0792, 
+51.8841, 5396.98, 6268.57, 8007.31, 2593.41, 2792.5, 3654.3, 
+58.9553, 6.23455, 57.7551, 143.242, 721.32, 547.635, 96.8654, 
+185.231, 96.0878, 57.448, 214.696, 204.236, 119.729, 30.2444, 
+85.6485, 334.249, 28.3019, 12.3808, -0.686965, 8.30199, 201.313, 
+154.514, 120.003, 128.271, 3949.66, -3.90832, 1.37556, 0.115654, 
+186.293, 120.317, 131.966, 33.6554, 4.97229, 30.5327, 38.4677, 
+695.874, 12.178, 130.613, 15.9664, 5821.41, 16.7248, 6.4599, 
+24.2949, 9.85454, 57.8458, 5.81503, 386.676, 1.52247, -33.954, 
+33.4058, 476.008, 126.252, 1.43033, 197.113, 30.9481, 55.8244, 
+162.076, 31.361, 12.9281, 225.702, 25.0649, 45.294, 320.477, 
+64.669, 127.117, 183.385, 217.682, 39.2494, 6.07408, 40.667, 
+38.1994, 441.567, 89.4277, 46.6241, 41.042, 78.1778, 55.5426, 
+74.4574, 7.8187, 37.2687, -41.0933, 179.983, 48.8883, 30.8553, 
+419.733, -3.71759, 17.7796, 124.578, 127.804, 163.667, 96.6763, 
+-13.882, 124.082, 102.447, 4538.63, 324.173, 180.668, 30.695, 
+24.5073, 16.98, 477.005, 62.9815, 1144.85, 39.2256, 28.1562, 
+2343.16, 123.996, 11.7146, 83.3672, 3.66428, 8.77839, 116.246, 
+4.90859, 66.3551, 246.004, 221.677, 24.1278, 93.6095, -4.99042, 
+163.165, 22.1886, 95.5136, 125.46, 359.16, 29.7101, 86.7899, 
+163.985, 55.433, 1347.3, 102.779, 12.6033, 21.714, 57.3163, 335.173, 
+192.821, 263.324, 8.9268, 789.193, 49.4697, 50.0177, 240.026, 
+484.841, 101.277, 248.77, 7.27135, 318.83, 34.0554, 346.501, 
+111.967, 689.406, 55.0139, 43.8142, 233.662, 3559.32, 69.8729, 
+146.993, 67.9381, 9.17022, 110.155, 33.0339, 451.23, 37.8454, 
+53.2007, 65.4184, 23.8741, 41.1479, 439.898, 137.748, -0.908171, 
+78.0279, 33.4717, 8.48149, 586.873, 11.0941, 20.149, 279.665, 
+18.8279, 254.824, 69.7076, 21.5575, 221.416, 91.442, 13.8932, 
+77.73, 155.463, 26.8256, 29.1519, 245.039, 6.1962, 28.6359, 2230.02, 
+56.2641, 54.0002, 198.39, 127.556, 19.2836, 23.3047, 311.924, 
+5.13927, 169.6, 31.9776, 350.559, 59.0126, 2.91583, 141.862, 
+68.935, 256.027, 112.449, 282.703, 42.7275, 26.8873, 280.86, 
+337.124, 184.335, 4173.32, 109.806, 108.091, 562.811, 2741.53, 
+-84.3726, 4270.95, 179.225, 18.4595, 243.641, 143.951, 48.7157, 
+-70.68, 21.74, 104.49, 87.1547, 88.9827, 73.4805, 91.6722, 105.905, 
+187.846, 45.3425, 5038.63, 180.624, 379.443, 287.845, 131.404, 
+55.7563, 73.7012, 70.7104, 279.954, 373.029, 67.3803, 4449.96, 
+31.9084, 23.4199, -22.3056, 13.9423, -123.237, 342.9, 5462.8, 
+2935.58, 702.04, 52.6377, 22.3381, 154.689, 23.6823, 89.1286, 
+12.0212, 526.41, 956.31, 177.783, 4498.55, 53.5631, 130.637, 
+54.5388, 61.6913, -43.8786, 3.27369, 157.966, 74.2671, 313.025, 
+93.83, 4302.85, 141.049, 50.9147, 68.8394, 104.932, 2188.28, 
+117.768, 274.929, 34.8144, 27.2235, 74.775, 129.955, 28.7763, 
+90.857, 13.7552, 3576.69, 2815.26, 52.9943, 365.15, 137.886, 
+30.0445, 274.657, 274.697, 37.5881, 128.01, 44.2284, 305.179, 
+88.4655, 2241.64, 1805.29, 69.6289, 70.4976, 125.397, -5.50171, 
+143.371, 45.7598, 297.246, 77.6654, 14.813, 48.7161, 127.716, 
+896.443, 186.552, 1.34836, 34.5627, 63.0341, 179.091, 50.86, 
+20.601, 30.4051, 37.0237, 9.2402, 540.935, 490.287, 4264.45, 
+2419.55, 99.7098, -30.8367, 200.178, 464.518, 37.6414, 16.7089, 
+1.40506, -2.41517, 38.5733, 50.9868, 214.045, 154.325, 249.752, 
+595.099, 383.625, 21.3787, 406.865, 64.4162, -43.9011, 14.5308, 
+72.7384, 75.3724, 12.3926, 45.137, 113.16, 32.784, 20.6045, 6.76257, 
+-11.4918, 16.1775, 60.4131, 441.265, 1.55004, 10.2899, 91.4198, 
+150.975, 27.8935, 23.1338, 108.075, 139.205, 1.73812, -66.9157, 
+-7.14961, 699.37, 246.651, 229.445, 210.434, 179.067, 31.2431, 
+122.683, 4.80586, 33.7739, 17.8987, 42.1504, 26.7045, 113.626, 
+316.855, 322.177, -10.3397, 44.6522, 198.4, 292.841, 147.858, 
+409.597, 39.3989, 15.6542, 113.361, 211.954, 261.276, 738.004, 
+184.868, 61.379, 6.79516, 2955.87, 62.8045, 297.49, 304.946, 
+746.325, 7.84412, 43.0373, 186.879, 319.566, 1.83518, 14.2545, 
+3321.83, 545.889, 611.534, 133.235, 53.9387, 41.8259, 6.69247, 
+225.888, 150.876, 19.3394, 17.7364, 497.67, 345.194, 157.833, 
+3569.07, -15.6659, 259.549, 77.8127, 390.22, 296.982, 277.797, 
+-26.6793, 124.435, 23.6537, 59.3599, 63.8332, 114.49, 39.6802, 
+291.709, 24.2746, 297.74, 287.749)), .Names = c("A", "B", "C", 
+"D", "E", "F", "G", "H", "I", "J", "K", "L", "M", "N", "O", "P", 
+"Q", "R", "S", "T", "U", "V", "W", "X", "Y", "Z"), row.names = c("AFFX-MurIL2_at", 
+"AFFX-MurIL10_at", "AFFX-MurIL4_at", "AFFX-MurFAS_at", "AFFX-BioB-5_at", 
+"AFFX-BioB-M_at", "AFFX-BioB-3_at", "AFFX-BioC-5_at", "AFFX-BioC-3_at", 
+"AFFX-BioDn-5_at", "AFFX-BioDn-3_at", "AFFX-CreX-5_at", "AFFX-CreX-3_at", 
+"AFFX-BioB-5_st", "AFFX-BioB-M_st", "AFFX-BioB-3_st", "AFFX-BioC-5_st", 
+"AFFX-BioC-3_st", "AFFX-BioDn-5_st", "AFFX-BioDn-3_st", "AFFX-CreX-5_st", 
+"AFFX-CreX-3_st", "AFFX-hum_alu_at", "AFFX-DapX-5_at", "AFFX-DapX-M_at", 
+"AFFX-DapX-3_at", "AFFX-LysX-5_at", "AFFX-LysX-M_at", "AFFX-LysX-3_at", 
+"AFFX-PheX-5_at", "AFFX-PheX-M_at", "AFFX-PheX-3_at", "AFFX-ThrX-5_at", 
+"AFFX-ThrX-M_at", "AFFX-ThrX-3_at", "AFFX-TrpnX-5_at", "AFFX-TrpnX-M_at", 
+"AFFX-TrpnX-3_at", "AFFX-HUMISGF3A/M97935_5_at", "AFFX-HUMISGF3A/M97935_MA_at", 
+"AFFX-HUMISGF3A/M97935_MB_at", "AFFX-HUMISGF3A/M97935_3_at", 
+"AFFX-HUMRGE/M10098_5_at", "AFFX-HUMRGE/M10098_M_at", "AFFX-HUMRGE/M10098_3_at", 
+"AFFX-HUMGAPDH/M33197_5_at", "AFFX-HUMGAPDH/M33197_M_at", "AFFX-HUMGAPDH/M33197_3_at", 
+"AFFX-HSAC07/X00351_5_at", "AFFX-HSAC07/X00351_M_at", "AFFX-HSAC07/X00351_3_at", 
+"AFFX-HUMTFRR/M11507_5_at", "AFFX-HUMTFRR/M11507_M_at", "AFFX-HUMTFRR/M11507_3_at", 
+"AFFX-M27830_5_at", "AFFX-M27830_M_at", "AFFX-M27830_3_at", "AFFX-HSAC07/X00351_3_st", 
+"AFFX-HUMGAPDH/M33197_5_st", "AFFX-HUMGAPDH/M33197_M_st", "AFFX-HUMGAPDH/M33197_3_st", 
+"AFFX-HSAC07/X00351_5_st", "AFFX-HSAC07/X00351_M_st", "AFFX-YEL002c/WBP1_at", 
+"AFFX-YEL018w/_at", "AFFX-YEL024w/RIP1_at", "AFFX-YEL021w/URA3_at", 
+"31307_at", "31308_at", "31309_r_at", "31310_at", "31311_at", 
+"31312_at", "31313_at", "31314_at", "31315_at", "31316_at", "31317_r_at", 
+"31318_at", "31319_at", "31320_at", "31321_at", "31322_at", "31323_r_at", 
+"31324_at", "31325_at", "31326_at", "31327_at", "31328_at", "31329_at", 
+"31330_at", "31331_at", "31332_at", "31333_at", "31334_at", "31335_at", 
+"31336_at", "31337_at", "31338_at", "31339_at", "31340_at", "31341_at", 
+"31342_at", "31343_at", "31344_at", "31345_at", "31346_at", "31347_at", 
+"31348_at", "31349_at", "31350_at", "31351_at", "31352_at", "31353_f_at", 
+"31354_r_at", "31355_at", "31356_at", "31357_at", "31358_at", 
+"31359_at", "31360_at", "31361_at", "31362_at", "31363_at", "31364_i_at", 
+"31365_f_at", "31366_at", "31367_at", "31368_at", "31369_at", 
+"31370_at", "31371_at", "31372_at", "31373_at", "31374_at", "31375_at", 
+"31376_at", "31377_r_at", "31378_at", "31379_at", "31380_at", 
+"31381_at", "31382_f_at", "31383_at", "31384_at", "31385_at", 
+"31386_at", "31387_at", "31388_at", "31389_at", "31390_at", "31391_at", 
+"31392_r_at", "31393_r_at", "31394_at", "31395_i_at", "31396_r_at", 
+"31397_at", "31398_at", "31399_at", "31400_at", "31401_r_at", 
+"31402_at", "31403_at", "31404_at", "31405_at", "31406_at", "31407_at", 
+"31408_at", "31409_at", "31410_at", "31411_at", "31412_at", "31413_at", 
+"31414_at", "31415_at", "31416_at", "31417_at", "31418_at", "31419_r_at", 
+"31420_at", "31421_at", "31422_at", "31423_at", "31424_at", "31425_g_at", 
+"31426_at", "31427_at", "31428_at", "31429_at", "31430_at", "31431_at", 
+"31432_g_at", "31433_at", "31434_at", "31435_at", "31436_s_at", 
+"31437_r_at", "31438_s_at", "31439_f_at", "31440_at", "31441_at", 
+"31442_at", "31443_at", "31444_s_at", "31445_at", "31446_s_at", 
+"31447_at", "31448_s_at", "31449_at", "31450_s_at", "31451_at", 
+"31452_at", "31453_s_at", "31454_f_at", "31455_r_at", "31456_at", 
+"31457_at", "31458_at", "31459_i_at", "31460_f_at", "31461_at", 
+"31462_f_at", "31463_s_at", "31464_at", "31465_g_at", "31466_at", 
+"31467_at", "31468_f_at", "31469_s_at", "31470_at", "31471_at", 
+"31472_s_at", "31473_s_at", "31474_r_at", "31475_at", "31476_g_at", 
+"31477_at", "31478_at", "31479_f_at", "31480_f_at", "31481_s_at", 
+"31482_at", "31483_g_at", "31484_at", "31485_at", "31486_s_at", 
+"31487_at", "31488_s_at", "31489_at", "31490_at", "31491_s_at", 
+"31492_at", "31493_s_at", "31494_at", "31495_at", "31496_g_at", 
+"31497_at", "31498_f_at", "31499_s_at", "31500_at", "31501_at", 
+"31502_at", "31503_at", "31504_at", "31505_at", "31506_s_at", 
+"31507_at", "31508_at", "31509_at", "31510_s_at", "31511_at", 
+"31512_at", "31513_at", "31514_at", "31515_at", "31516_f_at", 
+"31517_f_at", "31518_i_at", "31519_f_at", "31520_at", "31521_f_at", 
+"31522_f_at", "31523_f_at", "31524_f_at", "31525_s_at", "31526_f_at", 
+"31527_at", "31528_f_at", "31529_at", "31530_at", "31531_g_at", 
+"31532_at", "31533_s_at", "31534_at", "31535_i_at", "31536_at", 
+"31537_at", "31538_at", "31539_r_at", "31540_at", "31541_at", 
+"31542_at", "31543_at", "31544_at", "31545_at", "31546_at", "31547_at", 
+"31548_at", "31549_at", "31550_at", "31551_at", "31552_at", "31553_at", 
+"31554_at", "31555_at", "31556_at", "31557_at", "31558_at", "31559_at", 
+"31560_at", "31561_at", "31562_at", "31563_at", "31564_at", "31565_at", 
+"31566_at", "31567_at", "31568_at", "31569_at", "31570_at", "31571_at", 
+"31572_at", "31573_at", "31574_i_at", "31575_f_at", "31576_at", 
+"31577_at", "31578_at", "31579_at", "31580_at", "31581_at", "31582_at", 
+"31583_at", "31584_at", "31585_at", "31586_f_at", "31587_at", 
+"31588_at", "31589_at", "31590_g_at", "31591_s_at", "31592_at", 
+"31593_at", "31594_at", "31595_at", "31596_f_at", "31597_r_at", 
+"31598_s_at", "31599_f_at", "31600_s_at", "31601_s_at", "31602_at", 
+"31603_at", "31604_at", "31605_at", "31606_at", "31607_at", "31608_g_at", 
+"31609_s_at", "31610_at", "31611_s_at", "31612_at", "31613_at", 
+"31614_at", "31615_i_at", "31616_r_at", "31617_at", "31618_at", 
+"31619_at", "31620_at", "31621_s_at", "31622_f_at", "31623_f_at", 
+"31624_at", "31625_at", "31626_i_at", "31627_f_at", "31628_at", 
+"31629_at", "31630_at", "31631_f_at", "31632_at", "31633_g_at", 
+"31634_at", "31635_g_at", "31636_s_at", "31637_s_at", "31638_at", 
+"31639_f_at", "31640_r_at", "31641_s_at", "31642_at", "31643_at", 
+"31644_at", "31645_at", "31646_at", "31647_at", "31648_at", "31649_at", 
+"31650_g_at", "31651_at", "31652_at", "31653_at", "31654_at", 
+"31655_at", "31656_at", "31657_at", "31658_at", "31659_at", "31660_at", 
+"31661_at", "31662_at", "31663_at", "31664_at", "31665_s_at", 
+"31666_f_at", "31667_r_at", "31668_f_at", "31669_s_at", "31670_s_at", 
+"31671_at", "31672_g_at", "31673_s_at", "31674_s_at", "31675_s_at", 
+"31676_at", "31677_at", "31678_at", "31679_at", "31680_at", "31681_at", 
+"31682_s_at", "31683_at", "31684_at", "31685_at", "31686_at", 
+"31687_f_at", "31688_at", "31689_at", "31690_at", "31691_g_at", 
+"31692_at", "31693_f_at", "31694_at", "31695_g_at", "31696_at", 
+"31697_s_at", "31698_at", "31699_at", "31700_at", "31701_r_at", 
+"31702_at", "31703_at", "31704_at", "31705_at", "31706_at", "31707_at", 
+"31708_at", "31709_at", "31710_at", "31711_at", "31712_at", "31713_s_at", 
+"31714_at", "31715_at", "31716_at", "31717_at", "31718_at", "31719_at", 
+"31720_s_at", "31721_at", "31722_at", "31723_at", "31724_at", 
+"31725_s_at", "31726_at", "31727_at", "31728_at", "31729_at", 
+"31730_at", "31731_at", "31732_at", "31733_at", "31734_at", "31735_at", 
+"31736_at", "31737_at", "31738_at", "31739_at"), class = "data.frame")
diff --git a/debian/README.test b/debian/README.test
deleted file mode 100644
index ef34ccc..0000000
--- a/debian/README.test
+++ /dev/null
@@ -1,8 +0,0 @@
-Notes on how this package can be tested.
-────────────────────────────────────────
-
-To run the unit tests provided by the package you can do
-
-   sh run-unit-test
-
-in this directory.
diff --git a/debian/changelog b/debian/changelog
deleted file mode 100644
index a85919c..0000000
--- a/debian/changelog
+++ /dev/null
@@ -1,49 +0,0 @@
-r-bioc-genefilter (1.58.1-1) unstable; urgency=medium
-
-  * New upstream version
-  * debhelper 10
-  * Standards-Version: 4.1.0 (no changes needed)
-
- -- Andreas Tille <tille at debian.org>  Wed, 06 Sep 2017 22:53:20 +0200
-
-r-bioc-genefilter (1.56.0-1) unstable; urgency=medium
-
-  * New upstream version
-  * Convert to dh-r
-  * Generic BioConductor homepage
-
- -- Andreas Tille <tille at debian.org>  Tue, 08 Nov 2016 09:58:43 +0100
-
-r-bioc-genefilter (1.54.2-1) unstable; urgency=medium
-
-  * New upstream version
-
- -- Andreas Tille <tille at debian.org>  Sun, 22 May 2016 13:42:10 +0200
-
-r-bioc-genefilter (1.52.1-1) unstable; urgency=medium
-
-  * New upstream version (patch applied upstream)
-  * cme fix dpkg-control
-  * Add r-cran-class to Suggests and autopkgtest Depends
-
- -- Andreas Tille <tille at debian.org>  Wed, 27 Apr 2016 20:23:02 +0200
-
-r-bioc-genefilter (1.52.0-2) unstable; urgency=medium
-
-  * Apply upstream patch to fix conflicting declarations of function gf_distance
-    Closes: #812767
-
- -- Andreas Tille <tille at debian.org>  Thu, 28 Jan 2016 10:55:03 +0100
-
-r-bioc-genefilter (1.52.0-1) unstable; urgency=medium
-
-  * New upstream version
-  * Add autopkgtest
-
- -- Andreas Tille <tille at debian.org>  Sun, 08 Nov 2015 20:33:36 +0100
-
-r-bioc-genefilter (1.50.0-1) unstable; urgency=medium
-
-  * Initial release (closes: #794279)
-
- -- Andreas Tille <tille at debian.org>  Fri, 31 Jul 2015 22:15:11 +0200
diff --git a/debian/compat b/debian/compat
deleted file mode 100644
index f599e28..0000000
--- a/debian/compat
+++ /dev/null
@@ -1 +0,0 @@
-10
diff --git a/debian/control b/debian/control
deleted file mode 100644
index 42d934e..0000000
--- a/debian/control
+++ /dev/null
@@ -1,26 +0,0 @@
-Source: r-bioc-genefilter
-Maintainer: Debian Med Packaging Team <debian-med-packaging at lists.alioth.debian.org>
-Uploaders: Andreas Tille <tille at debian.org>
-Section: gnu-r
-Priority: optional
-Build-Depends: debhelper (>= 10),
-               dh-r,
-               r-base-dev,
-               r-bioc-annotationdbi,
-               r-bioc-annotate,
-               r-cran-survival
-Standards-Version: 4.1.0
-Vcs-Browser: https://anonscm.debian.org/viewvc/debian-med/trunk/packages/R/r-bioc-genefilter/trunk/
-Vcs-Svn: svn://anonscm.debian.org/debian-med/trunk/packages/R/r-bioc-genefilter/trunk/
-Homepage: https://bioconductor.org/packages/genefilter/
-
-Package: r-bioc-genefilter
-Architecture: any
-Depends: ${R:Depends},
-         ${misc:Depends},
-         ${shlibs:Depends}
-Recommends: ${R:Recommends}
-Suggests: ${R:Suggests}
-Description: methods for filtering genes from microarray experiments
- This BioConductor module provides methods for filtering genes from microarray
- experiments.  It contains some basic functions for filtering genes.
diff --git a/debian/copyright b/debian/copyright
deleted file mode 100644
index 041123b..0000000
--- a/debian/copyright
+++ /dev/null
@@ -1,107 +0,0 @@
-Format: https://www.debian.org/doc/packaging-manuals/copyright-format/1.0/
-Upstream-Name: genefilter
-Upstream-Contact: Bioconductor Package Maintainer <maintainer at bioconductor.org> 
-Source: https://bioconductor.org/packages/genefilter/
-
-Files: *
-Copyright: © 2006-2016 R. Gentleman, V. Carey, W. Huber, F. Hahne
-License: Artistic-2.0
-
-
-Files: debian/*
-Copyright: 2013-2016 Andreas Tille <tille at debian.org>
-License: Artistic-2.0
-
-License: Artistic-2.0
-			 The "Artistic License"
- .
-				Preamble
- .
- 1. You may make and give away verbatim copies of the source form of the
-    Standard Version of this Package without restriction, provided that
-    you duplicate all of the original copyright notices and associated
-    disclaimers.
- .
- 2. You may apply bug fixes, portability fixes and other modifications
-    derived from the Public Domain or from the Copyright Holder.  A
-    Package modified in such a way shall still be considered the Standard
-    Version.
- .
- 3. You may otherwise modify your copy of this Package in any way,
-    provided that you insert a prominent notice in each changed file stating
-    how and when you changed that file, and provided that you do at least
-    ONE of the following:
- .
-    a) place your modifications in the Public Domain or otherwise make them
-    Freely Available, such as by posting said modifications to Usenet or
-    an equivalent medium, or placing the modifications on a major archive
-    site such as uunet.uu.net, or by allowing the Copyright Holder to include
-    your modifications in the Standard Version of the Package.
- .
-    b) use the modified Package only within your corporation or organization.
- .
-    c) rename any non-standard executables so the names do not conflict
-    with standard executables, which must also be provided, and provide
-    a separate manual page for each non-standard executable that clearly
-    documents how it differs from the Standard Version.
- .
-    d) make other distribution arrangements with the Copyright Holder.
- .
- 4. You may distribute the programs of this Package in object code or
-    executable form, provided that you do at least ONE of the following:
- .
-    a) distribute a Standard Version of the executables and library files,
-    together with instructions (in the manual page or equivalent) on where
-    to get the Standard Version.
- .
-    b) accompany the distribution with the machine-readable source of
-    the Package with your modifications.
- .
-    c) give non-standard executables non-standard names, and clearly
-    document the differences in manual pages (or equivalent), together
-    with instructions on where to get the Standard Version.
- .
-    d) make other distribution arrangements with the Copyright Holder.
- .
- 5. You may charge a reasonable copying fee for any distribution of this
-    Package.  You may charge any fee you choose for support of this Package.
-    You may not charge a fee for this Package itself.  However, you may
-    distribute this Package in aggregate with other (possibly commercial)
-    programs as part of a larger (possibly commercial) software distribution
-    provided that you do not advertise this Package as a product of your
-    own.  You may embed this Package's interpreter within an executable of
-    yours (by linking); this shall be construed as a mere form of
-    aggregation, provided that the complete Standard Version of the
-    interpreter is so embedded.
- .
- 6. The scripts and library files supplied as input to or produced as
-    output from the programs of this Package do not automatically fall under
-    the copyright of this Package, but belong to whoever generated them, and
-    may be sold commercially, and may be aggregated with this Package.  If
-    such scripts or library files are aggregated with this Package via the
-    so-called "undump" or "unexec" methods of producing a binary executable
-    image, then distribution of such an image shall neither be construed as
-    a distribution of this Package nor shall it fall under the restrictions
-    of Paragraphs 3 and 4, provided that you do not represent such an
-    executable image as a Standard Version of this Package.
- .
- 7. C subroutines (or comparably compiled subroutines in other
-    languages) supplied by you and linked into this Package in order to
-    emulate subroutines and variables of the language defined by this
-    Package shall not be considered part of this Package, but are the
-    equivalent of input as in Paragraph 6, provided these subroutines do
-    not change the language in any way that would cause it to fail the
-    regression tests for the language.
- .
- 8. Aggregation of this Package with a commercial distribution is always
-    permitted provided that the use of this Package is embedded; that is,
-    when no overt attempt is made to make this Package's interfaces visible
-    to the end user of the commercial distribution.  Such use shall not be
-    construed as a distribution of this Package.
- .
- 9. The name of the Copyright Holder may not be used to endorse or promote
-    products derived from this software without specific prior written permission.
- .
- 10. THIS PACKAGE IS PROVIDED "AS IS" AND WITHOUT ANY EXPRESS OR
-    IMPLIED WARRANTIES, INCLUDING, WITHOUT LIMITATION, THE IMPLIED
-    WARRANTIES OF MERCHANTIBILITY AND FITNESS FOR A PARTICULAR PURPOSE.
diff --git a/debian/examples b/debian/examples
deleted file mode 100644
index 18244c8..0000000
--- a/debian/examples
+++ /dev/null
@@ -1 +0,0 @@
-vignettes
diff --git a/debian/rules b/debian/rules
deleted file mode 100755
index 68d9a36..0000000
--- a/debian/rules
+++ /dev/null
@@ -1,4 +0,0 @@
-#!/usr/bin/make -f
-
-%:
-	dh $@ --buildsystem R
diff --git a/debian/source/format b/debian/source/format
deleted file mode 100644
index 163aaf8..0000000
--- a/debian/source/format
+++ /dev/null
@@ -1 +0,0 @@
-3.0 (quilt)
diff --git a/debian/tests/control b/debian/tests/control
deleted file mode 100644
index 5f98003..0000000
--- a/debian/tests/control
+++ /dev/null
@@ -1,3 +0,0 @@
-Tests: run-unit-test
-Depends: @, r-cran-class
-Restrictions: allow-stderr
diff --git a/debian/tests/run-unit-test b/debian/tests/run-unit-test
deleted file mode 100644
index 53182d6..0000000
--- a/debian/tests/run-unit-test
+++ /dev/null
@@ -1,18 +0,0 @@
-#!/bin/sh -e
-oname=genefilter
-pkg=r-bioc-`echo $oname | tr [A-Z] [a-z]`
-
-if [ "$ADTTMP" = "" ] ; then
-  ADTTMP=`mktemp -d /tmp/${pkg}-test.XXXXXX`
-fi
-cd $ADTTMP
-cp /usr/share/doc/$pkg/examples/vignettes/* $ADTTMP
-find . -name "*.gz" -exec gunzip \{\} \;
-for rnw in `ls *.[rRS]nw` ; do
-rfile=`echo $rnw | sed 's/\.[rRS]nw/.R/'`
-R --no-save <<EOT
-  Stangle("$rnw")
-  source("$rfile", echo=TRUE)
-EOT
-done
-rm -rf *
diff --git a/debian/watch b/debian/watch
deleted file mode 100644
index c05be04..0000000
--- a/debian/watch
+++ /dev/null
@@ -1,3 +0,0 @@
-version=3
-opts=downloadurlmangle=s?^(.*)\.\.?http:$1packages/release/bioc? \
- http://www.bioconductor.org/packages/release/bioc/html/genefilter.html .*/genefilter_([\d\.]+)\.tar\.gz
diff --git a/docs/Cluster.pdf b/docs/Cluster.pdf
new file mode 100644
index 0000000..6eebe25
Binary files /dev/null and b/docs/Cluster.pdf differ
diff --git a/docs/gcluster.tex b/docs/gcluster.tex
new file mode 100644
index 0000000..d3b2545
--- /dev/null
+++ b/docs/gcluster.tex
@@ -0,0 +1,30 @@
+Notes from Cheng Li, on what he does for clustering:
+I basically followed the methods in the attached paper (page 2, upper-right
+corner).
+  
+it's not the standard avarage linkage, instead, after two genes (or nodes)
+are merged, the resultant node has expression profile as the avereage the
+the two merged ones (after standardization). A description for anther
+project using dchip is as follows:
+  
+Hierarchical clustering analysis (3) is used to group genes with same
+expression pattern. A genes is selected for clustering if (1) its expression
+values in the 20 samples has coefficient of variation (standard deviation /
+mean) between 0.5 to 10 (2) it is called ��Present�� by GeneChip? in more
+than 5 samples. Then the expression values for a gene across the 20 samples
+are standardized to have mean 0 and standard deviation 1 by linear
+transformation, and the distance between two genes is defined as 1 - r where
+r is the standard correlation coefficient between the 20 standardize values
+of two genes. Two genes with the closest distance are first merged into a
+super-gene and connected by branches with length representing their
+distance, and are deleted for future merging. The expression level of the
+newly formed super-gene is the average of standardized expression levels of
+the two genes (average-linkage) for each sample. Then the next pair of genes
+(super-genes) with the smallest distance are chosen to merge and the process
+is repeated until all genes are merged into one cluster. The dendrogram in
+Figure ? illustrates the final clustering tree, where genes close to each
+other have high similarity in their standardized expression values across
+the 20 samples.
+  
+  
+
diff --git a/docs/gfilter.tex b/docs/gfilter.tex
new file mode 100644
index 0000000..5551b98
--- /dev/null
+++ b/docs/gfilter.tex
@@ -0,0 +1,252 @@
+\documentclass{article}
+
+\begin{document}
+
+\title{Using Genefilter}
+\author{Robert Gentleman \thanks{rgentlem at hsph.harvard.edu}
+}
+\date{}
+\maketitle
+
+\section{An extended example}
+
+Consider an experiment to explore genes that are induced by cellular
+contact with a ligand (we will call the ligand F).
+The receptors are known to transduce intracellular signals when the
+cell is placed in contact with F. We want to determine which genes are
+involved in the process.
+
+The experiment was designed to use two substrates, F and an inert
+substance that will be referred to as P.
+A large number of cells were cultured and then separated and one batch
+was applied to F while the other was applied to P.
+For both conditions cells were harvested at the times, 0, 1 hour, 3
+hours and 8 hours. Those cells were processed and applied to
+Affymetrix U95Av2 chips. This process yielded expression level
+estimates for the 12,600 genes or ESTs measured by that chip.
+
+The goal of the analysis is to produce a list of genes (possibly in
+some rank order) that have patterns of expression that are different in
+the two subsets (those cells applied to F versus those cells applied
+to P).
+
+If there were just a few genes then we might try to select the
+interesting ones by using a linear model (or some other model that was
+more appropriate). In the subsequent discussion the form of the model
+is irrelevant and the linear model will be used purely for pedagogical
+reasons.
+
+Let $y_{ij}$ denote the expression level of a particular gene in
+contact with substrate $i$, ($i$ will be either F or P) at time $j$,
+($j$ is one of 0,1,3,8).
+Suppose that in consultation with the biologists we determine that a
+gene is interesting if the coeffecient for time, in a linear model, is
+different in the two subsets.
+This can easily be done (for a small handful of genes) using a linear
+model. 
+
+Let $a$ denote the substrate and $b$ denote the times. Further we
+assume that the expression data is presented in a matrix with 12,600
+rows and 8 columns. Further assume that the columns contain the data
+in the order F0, F1, F3, F8, P0, P1, P3, P8.
+Then we can fit the model using the following R code.
+
+\begin{verbatim}
+ a <- as.factor(c(rep("F",4), rep("P",4)))
+ b <- c(0,1,3,8,0,1,3,8)
+ data1 <- data.frame(a,b)
+ f1 <- y~a/b-1
+ f2 <- y~a+b
+\end{verbatim}
+
+The model \verb+f1+ fits separate regressions on \verb+b+ within
+levels of \verb+b+.
+The model \verb+f2+ fits a parallel lines regression model. So
+comparing these two models via: 
+\begin{verbatim}
+ fit1 <- lm(f1, data1)
+ fit2 <- lm(f2, data1)
+ an1 <- anova(fit1, fit2)
+ an1 
+\end{verbatim}
+From \verb+an1+ we can obtain the F--test statistic for comparing the
+two models. We would reject the hypothesis that the slopes of the two
+lines were the same if this $p$--value were sufficiently small (and
+all of our diagnostic tests confirmed that the model was appropriate).
+
+In the current setting with 12,600 genes it is not feasible to
+consider carrying out this process by hand and thus we need some
+automatic procedure for carrying it out.
+To do that we rely on some special functionality in R that is being
+used more and more to provide easy to use programs for complex
+problems (such as the current one).
+See the {\em Environments} section to get a better understanding of
+the use of environments in R.
+
+First we provide the code that will create an environment, associate
+it with both \verb+f1+ and \verb+f2+ and populate it with the
+variables \verb+a+ and \verb+b+.
+
+\begin{verbatim}
+  e1 <- new.env()
+  assign("a", a, env=e1)
+  assign("b", b, env=e1)
+  environment(f1) <- e1
+  environment(f2) <- e1
+\end{verbatim}
+Now the two formulas share the environment \verb+e1+ and all the
+variable bindings in it.
+We have not assigned any value to \verb+y+ for our formulas though.
+The reason for that is that \verb+a+ and \verb+b+ are the same for
+each gene we want to test but \verb+y+ will change.
+
+We now consider an abstract (or algorithmic) version of what we need
+to do for each gene.
+Our ultimate goal is to produce a function that takes a single
+argument, \verb+x+, the expression levels for a gene and returns
+either \verb+TRUE+ indicating that the gene is interesting or
+\verb+FALSE+ indicating that the gene is uninteresting.
+
+\begin{itemize}
+\item For each gene we need to assign the expression levels for that
+  gene to the variable \verb+y+ in the environment \verb+e1+.
+\item We fit both models \verb+f1+ and \verb+f2+.
+\item We compute the anova comparing these two models.
+\item We determine whether according to some criteria the large model
+  is needed (and hence in this case that the slopes for the expression
+  are different in the two substrates). If so we output \verb+TRUE+
+  otherwise we output \verb+FALSE+.
+\end{itemize}
+
+To operationalize this (and to make it easier to extend the ideas to
+more complex settings) we construct a closure to carry out this task.
+\begin{verbatim}
+ make3fun <- function(form1, form2, p) {
+      e1 <- environment(form1)
+      #if( !identical(e1, environment(form2)) )
+      #   stop("form1 and form2 must share the same environment")
+      function(x) {
+          assign("y", x, env=e1)
+          fit1 <- lm(form1)
+          fit2 <- lm(form2)
+          an1 <- anova(fit1, fit2)
+          if( an1$"Pr(>F)"[2] < p )
+              return(TRUE)
+          else
+              return(FALSE)
+      }
+  }
+\end{verbatim}
+%$
+The function, \verb+make3fun+ is quite simple. It takes two formulas
+and a $p$--value as arguments. It checks to see that the formulas
+share an environment and then creates and returns a function of one
+argument. That function carries out all the fitting and testing for
+us.
+It is worth pointing out that the returned function is called a
+{\em closure} and that it makes use of some of the special properties
+of environments that are discussed below.
+
+Now we can create the function that we will use to call apply.
+We do this quite simply with:
+\begin{verbatim}
+ myappfun <- make3fun(f1, f2, 0.01)
+ myappfun
+function(x) {
+          assign("y", x, env=e1)
+          fit1 <- lm(form1)
+          fit2 <- lm(form2)
+          an1 <- anova(fit1, fit2)
+          if( an1$"Pr(>F)"[2] < p )
+              return(TRUE)
+          else
+              return(FALSE)
+      }
+<environment: 02FF53B8>
+\end{verbatim}
+%$
+Thus, \verb+myappfun+ is indeed a function of one argument. It carries
+out the three steps we outlined above and will return \verb+TRUE+ if
+the $p$--value for comparing the model in \verb+f1+ to that in
+\verb+f2+ is less than $0.01$.
+
+If we assume that the data are stored in a data frame called
+\verb+gene.exprs+ then we can find the interesting ones using the
+following line of code.
+\begin{verbatim}
+  interesting.ones <- apply(gene.exprs, 1, myappfun)
+\end{verbatim}
+
+The real advantage of this approach is that it extends simply (or
+trivially) to virtually any model comparison that can be represented
+or carried out in R.
+
+\section{Environments}
+
+In R an environment can be thought of as a table. The table contains a
+list of symbols that are linked to a list of values.
+There are only a couple of operations that you need to carry out on
+environments. One is to give the name of a symbol and get the
+associated value. The other is to set the value for a symbol to some
+supplied value.
+
+The following code shows some simple manipulations that you can do.
+
+\begin{verbatim}
+
+>  e1 <- new.env()
+>  ls(env=e1)
+ character(0)
+> ls()
+ [1] "a"     "an1"   "b"     "data1" "e1"    "f1"    "f2"    "fit1"  "fit2" 
+[10] "y" 
+> #this ls() lists the objects in my workspace (which is itself
+> # an environment; it gets searched by default
+> assign("a", 4, env=e1)
+> #this assigns the value 4 to the symbol a in e1
+> #it has no effect on a in my workspace
+> a
+[1] F F F F P P P P
+Levels:  F P 
+> get("a",env=e1)
+[1] 4
+> #so the a in env1 is separate and protected from the a in my
+> # workspace
+\end{verbatim}
+
+In R every formula has an associated environment. This environment is
+used to provide bindings (or values) for the symbols in the
+formula. When we write \verb=y~a+x= we have in mind some values to
+associate with \verb+y+, \verb+a+ and \verb+x+. We can use an
+environment to specify these.
+
+\begin{verbatim}
+ substrate <- c(1,1,1,1,2,2,2,2)
+ time <- c(0,1,3,8,0,1,3,8)
+ response <- rnorm(8)
+ assign("a", substrate, env=e1)
+ assign("b", time, env=e1)
+ assign("y", response, env=e1)
+ environment(f1) <- e1
+ environment(f2) <- e1
+\end{verbatim}
+Now, both of our formulas (from section 1) share the environment
+\verb+e1+ and both can be used in any modeling context without
+specifying the data; it will be obtained automatically from the
+environment. 
+
+\section{A weighted analysis}
+
+The Li and Wong (2000) algorithm for estimating expression levels for
+gene chip samples also provides an estimate of the standard error of
+the expression level. These estimated standard errors can potentially
+be used in the analysis of the data.
+
+For example, since we have observations of the form $Y_i,
+\hat{\sigma}_i$ we could consider taking weighted averages, within
+groups. The weights would be determined by the estimated standard
+errors.
+
+
+
+\end{document}
diff --git a/inst/doc/howtogenefilter.R b/inst/doc/howtogenefilter.R
new file mode 100644
index 0000000..044db73
--- /dev/null
+++ b/inst/doc/howtogenefilter.R
@@ -0,0 +1,107 @@
+### R code from vignette source 'howtogenefilter.Rnw'
+
+###################################################
+### code chunk number 1: howtogenefilter.Rnw:41-47
+###################################################
+library("Biobase")
+library("genefilter")
+data(sample.ExpressionSet)
+varLabels(sample.ExpressionSet)
+table(sample.ExpressionSet$sex)
+table(sample.ExpressionSet$type)
+
+
+###################################################
+### code chunk number 2: howtogenefilter.Rnw:70-74
+###################################################
+f1 <- kOverA(5, 200)
+ffun <- filterfun(f1)
+wh1 <- genefilter(exprs(sample.ExpressionSet), ffun)
+sum(wh1)
+
+
+###################################################
+### code chunk number 3: howtogenefilter.Rnw:85-88
+###################################################
+f2 <- ttest(sample.ExpressionSet$type, p=0.1)
+wh2 <- genefilter(exprs(sample.ExpressionSet), filterfun(f2))
+sum(wh2)
+
+
+###################################################
+### code chunk number 4: howtogenefilter.Rnw:100-103
+###################################################
+ffun_combined <- filterfun(f1, f2)
+wh3 <- genefilter(exprs(sample.ExpressionSet), ffun_combined)
+sum(wh3)
+
+
+###################################################
+### code chunk number 5: aggregate
+###################################################
+
+ knnCV <- function(EXPR, selectfun, cov, Agg, pselect = 0.01, Scale=FALSE) {
+   nc <- ncol(EXPR)
+   outvals <- rep(NA, nc)
+   for(i in 1:nc) {
+      v1 <- EXPR[,i]
+      expr <- EXPR[,-i]
+      glist <- selectfun(expr, cov[-i], p=pselect)
+      expr <- expr[glist,]
+      if( Scale ) {
+        expr <- scale(expr)
+        v1 <- as.vector(scale(v1[glist]))
+      }
+      else
+         v1 <- v1[glist]
+      out <- paste("iter ",i, " num genes= ", sum(glist), sep="")
+      print(out)
+      Aggregate(row.names(expr), Agg)
+      if( length(v1) == 1)
+         outvals[i] <- knn(expr, v1, cov[-i], k=5)
+      else
+          outvals[i] <- knn(t(expr), v1, cov[-i], k=5)
+    }
+    return(outvals)
+  }
+
+
+###################################################
+### code chunk number 6: aggregate
+###################################################
+ gfun <- function(expr, cov, p=0.05) {
+    f2 <- ttest(cov, p=p)
+    ffun <- filterfun(f2)
+    which <- genefilter(expr, ffun)
+  }
+
+
+
+###################################################
+### code chunk number 7: aggregate
+###################################################
+  library("class")
+
+  ##scale the genes
+  ##genescale is a slightly more flexible "scale"
+  ##work on a subset -- for speed only
+  geneData <- genescale(exprs(sample.ExpressionSet)[1:75,], 1)
+
+  Agg <- new("aggregator")
+
+  testcase <- knnCV(geneData, gfun, sample.ExpressionSet$type, 
+         Agg, pselect=0.05)
+
+
+###################################################
+### code chunk number 8: aggregate
+###################################################
+sort(sapply(aggenv(Agg), c), decreasing=TRUE)
+
+
+###################################################
+### code chunk number 9: howtogenefilter.Rnw:207-208
+###################################################
+toLatex(sessionInfo())
+
+
diff --git a/inst/doc/howtogenefilter.Rnw b/inst/doc/howtogenefilter.Rnw
new file mode 100644
index 0000000..f4b3c7d
--- /dev/null
+++ b/inst/doc/howtogenefilter.Rnw
@@ -0,0 +1,212 @@
+%
+% NOTE -- ONLY EDIT howtogenefilter.Rnw!!!
+% howtogenefilter.tex file will get overwritten.
+%
+%\VignetteIndexEntry{Using the genefilter function to filter genes from a microarray dataset}
+%\VignetteDepends{Biobase, genefilter, class}
+%\VignetteKeywords{Expression Analysis}
+%\VignettePackage{genefilter}
+\documentclass{article}
+
+\usepackage{hyperref}
+
+\textwidth=6.2in
+\textheight=8.5in
+%\parskip=.3cm
+\oddsidemargin=.1in
+\evensidemargin=.1in
+\headheight=-.3in
+
+\newcommand{\classdef}[1]{%
+  {\em #1}
+}
+
+\begin{document}
+\title{Using the genefilter function to filter genes from a microarray dataset}
+
+\maketitle
+
+\section*{Introduction}
+
+The {\em genefilter} package can be used to filter (select) genes from
+a microarray dataset according to a variety of different
+filtering mechanisms.
+Here, we will consider the example dataset
+in the \verb+sample.ExpressionSet+ example from the {\em Biobase} package.
+This experiment has 26 samples, and there are 500 genes and 3
+covariates. The covariates are named \verb+sex+, \verb+type+ and
+\verb+score+. The first two have two levels and the last one is
+continuous.
+
+<<>>=
+library("Biobase")
+library("genefilter")
+data(sample.ExpressionSet)
+varLabels(sample.ExpressionSet)
+table(sample.ExpressionSet$sex)
+table(sample.ExpressionSet$type)
+@
+%$
+
+One dichotomy that can be of interest for subsequent analyses is whether the filter is
+\emph{specific} or \emph{non-specific}. Here, specific means that we are
+filtering with reference to sample metadata, for example, \texttt{type}. For example, if
+we want to select genes that are differentially expressed in the two
+groups defined by \texttt{type}, that is a specific filter.
+If on the other hand we want to select genes that are expressed in more
+than 5 samples, that is an example of a non--specific filter.
+
+First, let us see how to perform a non--specific filter.
+Suppose we want to select genes that have an expression measure above 200 in at
+least 5 samples. To do that we use the function \verb+kOverA+.
+
+There are three steps that must be performed.
+\begin{enumerate}
+\item Create function(s) implementing the filtering criteria.
+\item Assemble it (them) into a (combined) filtering function.
+\item Apply the filtering function to the expression matrix.
+\end{enumerate}
+
+<<>>=
+f1 <- kOverA(5, 200)
+ffun <- filterfun(f1)
+wh1 <- genefilter(exprs(sample.ExpressionSet), ffun)
+sum(wh1)
+@
+
+Here \verb+f1+ is a function that implies our ``expression measure above 200 in at
+least 5 samples'' criterion, the function \verb+ffun+ is the filtering
+function (which in this case consists of only one criterion), and we apply it using \verb+genefilter+.
+There were \Sexpr{sum(wh1)} genes that satisfied the criterion and passed the filter.
+
+As an example for a specific filter, let us select genes that are differentially
+expressed in the groups defined by \verb+type+.
+
+<<>>=
+f2 <- ttest(sample.ExpressionSet$type, p=0.1)
+wh2 <- genefilter(exprs(sample.ExpressionSet), filterfun(f2))
+sum(wh2)
+@
+%$
+Here, \texttt{ttest} is a function from the \texttt{genefilter}
+package which provides a suitable wrapper around \texttt{t.test} from
+package \textit{stats}. Now we see that there are \Sexpr{sum(wh2)}
+genes that satisfy the selection criterion. 
+
+Suppose that we want to combine the two filters. We want those genes
+for which at least 5 have an expression measure over 200 \emph{and} which also are differentially
+expressed between the groups defined by \verb+type+.
+
+<<>>=
+ffun_combined <- filterfun(f1, f2)
+wh3 <- genefilter(exprs(sample.ExpressionSet), ffun_combined)
+sum(wh3)
+@
+
+Now we see that there are only \Sexpr{sum(wh3)} genes  that satisfy both conditions.
+
+%%FIXME: need to replace this with something else
+%Our last example is to select genes that are
+%differentially expressed in at least one of the three groups defined
+%by \verb+cov3+.
+%To do that we use an Anova filter. This filter uses an analysis of
+%variance appraoch (via the \verb+lm+) function to test the hypothesis
+%that at least one of the three group means is different from the other
+%%two. The test is applied, then the $p$--value computed. We select
+%those genes that have a low $p$--value.
+%
+%<<>>=
+%Afilter <- Anova(eset$cov3)
+%aff <- filterfun(Afilter)
+%wh4 <- genefilter(exprs(eset), aff)
+%sum(wh4)
+%
+%@
+%%$
+%We see that there are 14 genes that pass this filter and that are
+%candidates for further exploration.
+
+
+\section*{Selecting genes that appear useful for prediction}
+
+The function \texttt{knnCV} defined below performs $k$--nearest neighbour classification
+using leave--one--out cross--validation.
+At the same time it aggregates the genes that were selected. The
+function returns the predicted classifications as its returned
+value. However, there is an additional side effect. The number of
+times that each gene was used (provided it was at least one) are
+recorded and stored in the environment of the aggregator \verb+Agg+.
+These can subsequently be retrieved and used for other purposes.
+
+<<aggregate>>=
+
+ knnCV <- function(EXPR, selectfun, cov, Agg, pselect = 0.01, Scale=FALSE) {
+   nc <- ncol(EXPR)
+   outvals <- rep(NA, nc)
+   for(i in 1:nc) {
+      v1 <- EXPR[,i]
+      expr <- EXPR[,-i]
+      glist <- selectfun(expr, cov[-i], p=pselect)
+      expr <- expr[glist,]
+      if( Scale ) {
+        expr <- scale(expr)
+        v1 <- as.vector(scale(v1[glist]))
+      }
+      else
+         v1 <- v1[glist]
+      out <- paste("iter ",i, " num genes= ", sum(glist), sep="")
+      print(out)
+      Aggregate(row.names(expr), Agg)
+      if( length(v1) == 1)
+         outvals[i] <- knn(expr, v1, cov[-i], k=5)
+      else
+          outvals[i] <- knn(t(expr), v1, cov[-i], k=5)
+    }
+    return(outvals)
+  }
+@
+%$
+
+<<aggregate>>=
+ gfun <- function(expr, cov, p=0.05) {
+    f2 <- ttest(cov, p=p)
+    ffun <- filterfun(f2)
+    which <- genefilter(expr, ffun)
+  }
+
+@
+
+Next we show how to use this function on the dataset
+\verb+geneData+.
+
+<<aggregate, results=hide>>=
+  library("class")
+
+  ##scale the genes
+  ##genescale is a slightly more flexible "scale"
+  ##work on a subset -- for speed only
+  geneData <- genescale(exprs(sample.ExpressionSet)[1:75,], 1)
+
+  Agg <- new("aggregator")
+
+  testcase <- knnCV(geneData, gfun, sample.ExpressionSet$type, 
+         Agg, pselect=0.05)
+@ 
+<<aggregate>>=
+sort(sapply(aggenv(Agg), c), decreasing=TRUE)
+@
+%$
+The environment \verb+Agg+ contains, for each gene,
+the number of times it was selected in the cross-validation.
+
+
+\section*{Session Information}
+
+The version number of R and packages loaded for generating the vignette were:
+
+<<echo=FALSE,results=tex>>=
+toLatex(sessionInfo())
+@
+
+\end{document}
+
diff --git a/inst/doc/howtogenefilter.pdf b/inst/doc/howtogenefilter.pdf
new file mode 100644
index 0000000..5584b8f
Binary files /dev/null and b/inst/doc/howtogenefilter.pdf differ
diff --git a/inst/doc/howtogenefinder.R b/inst/doc/howtogenefinder.R
new file mode 100644
index 0000000..08ca043
--- /dev/null
+++ b/inst/doc/howtogenefinder.R
@@ -0,0 +1,28 @@
+### R code from vignette source 'howtogenefinder.Rnw'
+
+###################################################
+### code chunk number 1: howtogenefinder.Rnw:45-52
+###################################################
+ library("Biobase")
+ library("genefilter")
+ data(sample.ExpressionSet)
+ igenes<- c(300,333,355,419) ##the interesting genes
+ closeg <- genefinder(sample.ExpressionSet, igenes, 10, 
+       method="euc", scale="none")
+ names(closeg)
+
+
+###################################################
+### code chunk number 2: howtogenefinder.Rnw:61-64
+###################################################
+closeg$"31539_r_at"
+Nms1 <- featureNames(sample.ExpressionSet)[closeg$"31539_r_at"$indices]
+Nms1
+
+
+###################################################
+### code chunk number 3: howtogenefinder.Rnw:106-107
+###################################################
+toLatex(sessionInfo())
+
+
diff --git a/inst/doc/howtogenefinder.Rnw b/inst/doc/howtogenefinder.Rnw
new file mode 100644
index 0000000..c09cbe0
--- /dev/null
+++ b/inst/doc/howtogenefinder.Rnw
@@ -0,0 +1,111 @@
+%\VignetteIndexEntry{How to find genes whose expression profile is similar to that of specified genes}
+%\VignetteDepends{Biobase, genefilter}
+%\VignetteKeywords{Expression Analysis}
+%\VignettePackage{genefilter}
+\documentclass{article}
+\usepackage{hyperref}
+
+\textwidth=6.2in
+\textheight=8.5in
+\oddsidemargin=.1in
+\evensidemargin=.1in
+\headheight=-.3in
+
+\newcommand{\classdef}[1]{%
+  {\em #1}
+}
+
+\begin{document}
+\title{How to find genes whose expression profile is similar to that of specified genes}
+
+\maketitle
+
+\section*{Introduction}
+
+In some cases you have certain genes of interest and you would like to
+find other genes that are {\em close} to the genes of interest.
+This can be done using the \verb+genefinder+ function.
+
+You need to specify either the index position of the genes you want
+(which row of the expression array the gene is in) or the name
+(consistent with the \verb+featureNames+ of the ExpressionSet).
+
+A vector of names can be specified and matches for all will be
+computed. The number of matches and the distance measure used can all
+be specified.
+The examples will be carried out using the artificial data set,
+\verb+sample.ExpressionSet+.
+
+Two other options for \verb+genefinder+ are \verb+scale+ and \verb+method+.
+The \verb+scale+ option controls the scaling of the rows (this is
+often desirable) while the \verb+method+ option controls the distance
+measure used between genes. The possible values and their meanings are
+listed at the end of this document.
+
+<<>>=
+ library("Biobase")
+ library("genefilter")
+ data(sample.ExpressionSet)
+ igenes<- c(300,333,355,419) ##the interesting genes
+ closeg <- genefinder(sample.ExpressionSet, igenes, 10, 
+       method="euc", scale="none")
+ names(closeg)
+@
+
+The Affymetrix identifiers (since these were originally Affymetrix
+data) are \verb+31539_r_at+, \verb+31572_at+, \verb+31594_at+ and
+\verb+31658_at+.
+We can find the nearest genes (by index) for any of these by simply
+accessing the relevant component of \verb+closeg+.
+
+<<>>=
+closeg$"31539_r_at"
+Nms1 <- featureNames(sample.ExpressionSet)[closeg$"31539_r_at"$indices]
+Nms1
+@
+%$
+You could then take these names (from \verb+Nms1+) and the {\em
+  annotate} package and explore them further. See the various HOWTO's
+  in annotate to see how to further explore your data.
+Examples include finding and searching all PubMed abstracts associated
+  with these data. Finding and downloading associated sequence information.
+The data can also be visualized using the {\em geneplotter} package
+  (again there are a number of HOWTO documents there).
+
+
+\section*{Parameter Settings}
+
+The \verb+scale+ parameter can take the following values:
+\begin{description}
+\item[none] No scaling is done.
+\item[range] Scaling is done by $(x_i - x_{(1)})/(x_{(n)}- x_{(1)})$.
+\item[zscore] Scaling is done by $(x_i - \bar{x})/ s_x$. Where $s_x$
+  is the standard deviation.
+\end{description}
+
+The \verb+method+ parameter can take the following values:
+\begin{description}
+\item[euclidean] Euclidean distance is used.
+\item[maximum]  Maximum distance between any two elements of x and y
+          (supremum norm).
+\item[manhattan] Absolute distance between the two vectors (1 norm).
+
+ \item[canberra] The $\sum (|x_i - y_i| / |x_i + y_i|)$.  Terms with zero
+          numerator and denominator are omitted from the sum and
+          treated as if the values were missing.
+\item[binary] (aka asymmetric binary): The vectors are regarded as
+          binary bits, so non-zero elements are {\em on} and zero elements
+          are {\em off}.  The distance is the proportion of bits in which
+          only one is on amongst those in which at least one is on.
+\end{description}
+
+\section*{Session Information}
+
+The version number of R and packages loaded for generating the vignette were:
+
+<<echo=FALSE,results=tex>>=
+toLatex(sessionInfo())
+@
+
+\end{document}
+
diff --git a/inst/doc/howtogenefinder.pdf b/inst/doc/howtogenefinder.pdf
new file mode 100644
index 0000000..4d52445
Binary files /dev/null and b/inst/doc/howtogenefinder.pdf differ
diff --git a/inst/doc/independent_filtering.R b/inst/doc/independent_filtering.R
new file mode 100644
index 0000000..f43bd18
--- /dev/null
+++ b/inst/doc/independent_filtering.R
@@ -0,0 +1,152 @@
+## ----knitr, echo=FALSE, results="hide"-----------------------------------
+library("knitr")
+opts_chunk$set(tidy=FALSE,dev="png",fig.show="hide",
+               fig.width=4,fig.height=4.5,dpi=240,
+               message=FALSE,error=FALSE,warning=FALSE)
+
+## ----style, eval=TRUE, echo=FALSE, results="asis"--------------------------
+BiocStyle:::latex2()
+
+## ----options,results='hide',echo=FALSE------------------------------------------------------------
+options(digits=3, width=100)
+library("pasilla") # make sure this is installed, since we need it in the next section
+
+## ----libraries,results='hide'---------------------------------------------------------------------
+library("pasilla")
+data("pasillaGenes")
+
+## ----DESeq1,results='hide'------------------------------------------------------------------------
+library("DESeq")
+
+## ----DESeq2,cache=TRUE,results='hide'-------------------------------------------------------------
+cds  = estimateSizeFactors( pasillaGenes )
+cds  = estimateDispersions( cds )
+fit1 = fitNbinomGLMs( cds, count ~ type + condition )
+fit0 = fitNbinomGLMs( cds, count ~ type  )
+
+## ----DESeq3,cache=TRUE----------------------------------------------------------------------------
+res = data.frame(
+filterstat = rowMeans(counts(cds)),
+pvalue    = nbinomGLMTest( fit1, fit0 ),
+row.names = featureNames(cds) )
+
+## ----headres--------------------------------------------------------------------------------------
+dim(res)
+head(res)
+
+## ----pass,echo=FALSE,cache=TRUE-------------------------------------------------------------------
+theta = 0.4
+pass = with(res, filterstat > quantile(filterstat, theta))
+
+## ----figscatterindepfilt--------------------------------------------------------------------------
+with(res,
+  plot(rank(filterstat)/length(filterstat), -log10(pvalue), pch=16, cex=0.45))
+
+## ----figecdffilt----------------------------------------------------------------------------------
+trsf = function(n) log10(n+1)
+plot(ecdf(trsf(res$filterstat)), xlab=body(trsf), main="")
+
+## ----badfilter1,cache=TRUE------------------------------------------------------------------------
+badfilter = as.numeric(gsub("[+]*FBgn", "", rownames(res)))
+
+## ----badfilter2,echo=FALSE------------------------------------------------------------------------
+stopifnot(!any(is.na(badfilter)))
+
+## ----figbadfilter---------------------------------------------------------------------------------
+plot(rank(badfilter)/length(badfilter), -log10(res$pvalue), pch=16, cex=0.45)
+
+## ----genefilter,results='hide'--------------------------------------------------------------------
+library("genefilter")
+
+## ----pBH1,cache=TRUE------------------------------------------------------------------------------
+theta = seq(from=0, to=0.5, by=0.1)
+pBH = filtered_p(filter=res$filterstat, test=res$pvalue, theta=theta, method="BH")
+
+## ----pBH2-----------------------------------------------------------------------------------------
+head(pBH)
+
+## ----figrejection,fig.width=5.5,fig.height=5.5----------------------------------------------------
+rejection_plot(pBH, at="sample",
+               xlim=c(0, 0.5), ylim=c(0, 2000),
+               xlab="FDR cutoff (Benjamini & Hochberg adjusted p-value)", main="")
+
+## ----filtered_R1,cache=TRUE-----------------------------------------------------------------------
+theta = seq(from=0, to=0.8, by=0.02)
+rejBH = filtered_R(alpha=0.1, filter=res$filterstat, test=res$pvalue, theta=theta, method="BH")
+
+## ----fignumreject,fig.width=5.5,fig.height=5.5----------------------------------------------------
+plot(theta, rejBH, type="l",
+     xlab=expression(theta), ylab="number of rejections")
+
+## ----differentstats,cache=TRUE--------------------------------------------------------------------
+filterChoices = data.frame(
+  `mean`   = res$filterstat,
+  `geneID` = badfilter,
+  `min`    = rowMin(counts(cds)),
+  `max`    = rowMax(counts(cds)),
+  `sd`     = rowSds(counts(cds))
+)
+rejChoices = sapply(filterChoices, function(f)
+  filtered_R(alpha=0.1, filter=f, test=res$pvalue, theta=theta, method="BH"))
+
+## ----colours,results='hide'-----------------------------------------------------------------------
+library("RColorBrewer")
+myColours = brewer.pal(ncol(filterChoices), "Set1")
+
+## ----figdifferentstats,fig.width=5.5,fig.height=5.5-----------------------------------------------
+matplot(theta, rejChoices, type="l", lty=1, col=myColours, lwd=2,
+        xlab=expression(theta), ylab="number of rejections")
+legend("bottomleft", legend=colnames(filterChoices), fill=myColours)
+
+## ----histindepfilt, fig.width=7, fig.height=5-----------------------------------------------------
+h1 = hist(res$pvalue[!pass], breaks=50, plot=FALSE)
+h2 = hist(res$pvalue[pass], breaks=50, plot=FALSE)
+colori <- c(`do not pass`="khaki", `pass`="powderblue")
+
+## ----fighistindepfilt, dev="pdf"------------------------------------------------------------------
+barplot(height = rbind(h1$counts, h2$counts), beside = FALSE,
+        col = colori, space = 0, main = "", ylab="frequency")
+text(x = c(0, length(h1$counts)), y = 0, label = paste(c(0,1)),
+     adj = c(0.5,1.7), xpd=NA)
+legend("topright", fill=rev(colori), legend=rev(names(colori)))
+
+## ----sortP, cache=TRUE----------------------------------------------------------------------------
+resFilt = res[pass,]
+orderInPlot = order(resFilt$pvalue)
+showInPlot = (resFilt$pvalue[orderInPlot] <= 0.06)
+alpha = 0.1
+
+## ----sortedP, fig.width=4.5, fig.height=4.5-------------------------------------------------------
+plot(seq(along=which(showInPlot)), resFilt$pvalue[orderInPlot][showInPlot],
+     pch=".", xlab = expression(rank(p[i])), ylab=expression(p[i]))
+abline(a=0, b=alpha/length(resFilt$pvalue), col="red3", lwd=2)
+
+## ----doBH, echo=FALSE, results='hide'-------------------------------------------------------------
+whichBH = which(resFilt$pvalue[orderInPlot] <= alpha*seq(along=resFilt$pvalue)/length(resFilt$pvalue))
+## Test some assertions:
+## - whichBH is a contiguous set of integers from 1 to length(whichBH)
+## - the genes selected by this graphical method coincide with those
+##   from p.adjust (i.e. padjFilt)
+stopifnot(length(whichBH)>0,
+          identical(whichBH, seq(along=whichBH)),
+          resFilt$FDR[orderInPlot][ whichBH] <= alpha,
+          resFilt$FDR[orderInPlot][-whichBH]  > alpha)
+
+## ----SchwSpjot, echo=FALSE, results='hide'--------------------------------------------------------
+j  = round(length(resFilt$pvalue)*c(1, .66))
+px = (1-resFilt$pvalue[orderInPlot[j]])
+py = ((length(resFilt$pvalue)-1):0)[j]
+slope = diff(py)/diff(px)
+
+## ----SchwederSpjotvoll, fig.width=4.5, fig.height=4.5---------------------------------------------
+plot(1-resFilt$pvalue[orderInPlot],
+     (length(resFilt$pvalue)-1):0, pch=".", xaxs="i", yaxs="i",
+     xlab=expression(1-p[i]), ylab=expression(N(p[i])))
+abline(a=0, slope, col="red3", lwd=2)
+abline(h=slope)
+text(x=0, y=slope, labels=paste(round(slope)), adj=c(-0.1, 1.3))
+
+## ----sessionInfo, results='asis', echo=FALSE------------------------------------------------------
+si = as.character( toLatex( sessionInfo() ) )
+cat( si[ -grep( "Locale", si ) ], sep = "\n" )
+
diff --git a/inst/doc/independent_filtering.Rnw b/inst/doc/independent_filtering.Rnw
new file mode 100644
index 0000000..837094c
--- /dev/null
+++ b/inst/doc/independent_filtering.Rnw
@@ -0,0 +1,468 @@
+%\VignetteIndexEntry{Diagnostics for independent filtering}
+%\VignettePackage{genefilter}
+%\VignetteEngine{knitr::knitr}
+
+% To compile this document
+% library('knitr'); rm(list=ls()); knit('independent_filtering.Rnw')
+
+\documentclass[10pt]{article}
+
+<<knitr, echo=FALSE, results="hide">>=
+library("knitr")
+opts_chunk$set(tidy=FALSE,dev="png",fig.show="hide",
+               fig.width=4,fig.height=4.5,dpi=240,
+               message=FALSE,error=FALSE,warning=FALSE)
+@ 
+
+<<style, eval=TRUE, echo=FALSE, results="asis">>=
+BiocStyle:::latex2()
+@
+
+\usepackage{xstring}
+\newcommand{\thetitle}{Diagnostics for independent filtering: choosing filter statistic and cutoff}
+
+\title{\textsf{\textbf{\thetitle}}}
+\author{Wolfgang Huber\\[1em]European Molecular Biology Laboratory (EMBL)}
+
+% The following command makes use of SVN's 'Date' keyword substitution
+% To activate this, I used: svn propset svn:keywords Date independent_filtering.Rnw
+\date{\Rpackage{genefilter} version \Sexpr{packageDescription("genefilter")$Version}  (Last revision \StrMid{$Date: 2016-03-22 18:37:15 -0400 (Tue, 22 Mar 2016) $}{8}{18})}
+
+
+\begin{document}
+
+<<options,results='hide',echo=FALSE>>=
+options(digits=3, width=100)
+library("pasilla") # make sure this is installed, since we need it in the next section
+@
+
+% Make title
+\maketitle
+\tableofcontents
+\vspace{.25in}
+
+\begin{abstract}
+\noindent This vignette illustrates diagnostics that are intended to help with
+\begin{itemize}
+\item the choice of filter criterion and
+\item the choice of filter cutoff
+\end{itemize}
+in independent filtering~\cite{Bourgon:2010:PNAS}. The package 
+\Biocpkg{genefilter} provides functions that might be convenient for this purpose.
+\end{abstract}
+
+%-----------------------------------------------------------
+\section{Introduction}
+%-----------------------------------------------------------
+Multiple testing approaches, with thousands of tests, are often used
+in analyses of genome-scale data. For instance, in analyses of
+differential gene expression based on RNA-Seq or microarray data, a
+common approach is to apply a statistical test, one by one, to each of
+thousands of genes, with the aim of identifying those genes that have
+evidence for a statistical association of their expression
+measurements with the experimental covariate(s) of interest.  Another
+instance is differential binding detection from ChIP-Seq data.  The
+idea of \emph{independent filtering} is to filter out those tests from
+the procedure that have no, or little chance of showing significant
+evidence, without even looking at their test statistic. Typically,
+this results in increased detection power at the same experiment-wide
+type I error, as measured in terms of the false discovery rate.  A
+good choice for a filtering criterion is one that
+\begin{enumerate}
+  \item\label{it:indp} is statistically independent from the test statistic
+    under the null hypothesis,
+  \item\label{it:corr} is correlated with the test statistic under the
+    alternative, and
+  \item\label{it:joint} does not notably change the dependence
+    structure --if there is any-- of the joint test statistics
+    (including those corresponding to true nulls and to true
+    alternatives).
+\end{enumerate}
+The benefit from filtering relies on property~\ref{it:corr}, and I will explore that
+further in Section~\ref{sec:qual}. The statistical validity of filtering relies on
+properties \ref{it:indp} and \ref{it:joint}.  For many practically useful combinations of
+filter criteria with test statistics, property~\ref{it:indp} is easy to prove (e.\,g., through
+Basu's theorem).  Property~\ref{it:joint} is more complicated, but rarely
+presents a problem in practice: if, for the multiple testing procedure that is being used,
+the correlation structure of the tests was acceptable without filtering, the filtering should 
+not change that. Please see~\cite{Bourgon:2010:PNAS} for further discussion on the
+mathematical and conceptual background.
+
+%-----------------------------------------------------------
+\section{Example data set}
+%-----------------------------------------------------------
+For illustration, let us use the \Robject{pasillaGenes} dataset from the
+Bioconductor package \Rpackage{pasilla}; this is an RNA-Seq dataset
+from which we extract gene-level read counts for two replicate samples
+the were measured for each of two biological conditions: normally
+growing cells and cells treated with dsRNA against the \emph{Pasilla}
+mRNA, which led to RNAi interference (RNAi) mediated knockdown of the
+Pasilla gene product.
+%
+<<libraries,results='hide'>>=
+library("pasilla")
+data("pasillaGenes")
+@
+%
+We perform a standard analysis with \Rpackage{DESeq} to look for genes
+that are differentially expressed between the normal and
+Pasilla-knockdown conditions, indicated by the factor variable
+\Robject{condition}. In the generalized linear model (GLM) analysis,
+we adjust for an additional experimental covariate \Robject{type},
+which is however not of interest for the differential expression. For
+more details, please see the vignette of the \Rpackage{DESeq} package.
+%
+<<DESeq1,results='hide'>>=
+library("DESeq")
+<<DESeq2,cache=TRUE,results='hide'>>=
+cds  = estimateSizeFactors( pasillaGenes )
+cds  = estimateDispersions( cds )
+fit1 = fitNbinomGLMs( cds, count ~ type + condition )
+fit0 = fitNbinomGLMs( cds, count ~ type  )
+<<DESeq3,cache=TRUE>>=
+res = data.frame(
+filterstat = rowMeans(counts(cds)),
+pvalue    = nbinomGLMTest( fit1, fit0 ),
+row.names = featureNames(cds) )
+@
+%
+The details of the anove analysis are not important for the purpose of
+this vignette, the essential output is contained in the columns of the
+dataframe \Robject{res}:
+\begin{itemize}
+  \item \texttt{filterstat}: the filter statistic, here the average
+    number of counts per gene across all samples, irrespective of
+    sample annoation,
+  \item \texttt{pvalue}: the test $p$-values,
+\end{itemize}
+Each row of the dataframe corresponds to one gene:
+<<headres>>=
+dim(res)
+head(res)
+@
+
+%--------------------------------------------------
+\section{Qualitative assessment of the filter statistic}\label{sec:qual}
+%--------------------------------------------------
+<<pass,echo=FALSE,cache=TRUE>>=
+theta = 0.4
+pass = with(res, filterstat > quantile(filterstat, theta))
+@
+%
+First, consider Figure~\ref{figscatterindepfilt}, which shows that
+among the approximately \Sexpr{100*theta}\% of genes with lowest overall counts, \Robject{filterstat},
+there are essentially none that achieved an (unadjusted) $p$-value less than
+\Sexpr{signif(quantile(res$pvalue[!pass], 0.0001, na.rm=TRUE), 1)}
+(this corresponds to about \Sexpr{signif(-log10(quantile(res$pvalue[!pass], 0.0001, na.rm=TRUE)), 2)} on the $-\log_{10}$-scale).
+%
+<<figscatterindepfilt>>=
+with(res,
+  plot(rank(filterstat)/length(filterstat), -log10(pvalue), pch=16, cex=0.45))
+@
+<<figecdffilt>>=
+trsf = function(n) log10(n+1)
+plot(ecdf(trsf(res$filterstat)), xlab=body(trsf), main="")
+@
+\begin{figure}[ht]
+\centering
+\includegraphics[width=.49\textwidth]{figure/figscatterindepfilt-1}
+\includegraphics[width=.49\textwidth]{figure/figecdffilt-1}
+\caption{Left: scatterplot of the rank (scaled to $[0,1]$) of the
+  filter criterion \Robject{filterstat} ($x$-axis) versus the negative
+  logarithm of the test \Robject{pvalue} ($y$-axis). Right: the
+  empirical cumulative distribution function (ECDF) shows the
+  relationships between the values of \Robject{filterstat} and its
+  quantiles.}
+\label{figscatterindepfilt}
+\end{figure}
+%
+This means that by dropping the 40\% genes with lowest \Robject{filterstat},
+we do not loose anything substantial from our subsequent
+results.
+
+For comparison, suppose you had chosen a less useful filter statistic,
+say, the gene identifiers interpreted as a decimal number. The
+analogous scatterplot to that of Figure~\ref{figscatterindepfilt} is
+shown in Figure~\ref{figbadfilter}.
+%
+<<badfilter1,cache=TRUE>>=
+badfilter = as.numeric(gsub("[+]*FBgn", "", rownames(res)))
+@
+<<badfilter2,echo=FALSE>>=
+stopifnot(!any(is.na(badfilter)))
+@
+<<figbadfilter>>=
+plot(rank(badfilter)/length(badfilter), -log10(res$pvalue), pch=16, cex=0.45)
+@
+\begin{figure}[ht]
+\centering
+\includegraphics[width=.49\textwidth]{figure/figbadfilter-1}
+\caption{Scatterplot analogous to Figure~\ref{figscatterindepfilt}, but with \Robject{badfilter}.}
+\label{figbadfilter}
+\end{figure}
+
+%--------------------------------------------------
+\section{How to choose the filter statistic and the cutoff?}\label{sec:indepfilterchoose}
+%--------------------------------------------------
+The \texttt{filtered\_p} function in the \Rpackage{genefilter} package
+calculates adjusted $p$-values over a range of possible filtering
+thresholds. Here, we call this function on our results from above and
+compute adjusted $p$-values using the method of Benjamini and Hochberg (BH)
+for a range of different filter cutoffs.
+%
+\begin{figure}[tb]
+\begin{center}
+\includegraphics[width=0.49\textwidth]{figure/figrejection-1}
+\includegraphics[width=0.49\textwidth]{figure/fignumreject-1}
+\caption{Left panel: the plot shows the number of rejections (i.\,e.\ genes detected as
+  differentially expressed) as a function of the FDR threshold
+  ($x$-axis) and the filtering cutoff $\theta$ (line colours,
+  specified as quantiles of the distribution of the
+  filter statistic). The plot is produced by the \texttt{rejection\_plot}
+  function. Note that the lines for $\theta=0\%$ and
+  $10\%$ are overplotted by the line for $\theta=20\%$, since for the
+  data shown here, these quantiles correspond all to the same set of
+  filtered genes (cf.~Figure~\ref{figscatterindepfilt}). Right panel:
+  the number of rejections at FDR=10\% as a function of
+  $\theta$.}
+\label{figrej}
+\end{center}
+\end{figure}
+%
+<<genefilter,results='hide'>>=
+library("genefilter")
+<<pBH1,cache=TRUE>>=
+theta = seq(from=0, to=0.5, by=0.1)
+pBH = filtered_p(filter=res$filterstat, test=res$pvalue, theta=theta, method="BH")
+<<pBH2>>=
+head(pBH)
+@
+%
+The rows of this matrix correspond to the genes (i.\,e., the rows of \Robject{res}) and
+the columns to the BH-adjusted $p$-values for the different possible
+choices of cutoff \Robject{theta}. A value of \Robject{NA} indicates
+that the gene was filtered out at the corresponding filter cutoff.
+The \Rfunction{rejection\_plot} function takes such a matrix and
+shows how rejection count ($R$) relates to the choice of cutoff for the
+$p$-values. For these data, over a reasonable range of FDR cutoffs, increased
+filtering corresponds to increased rejections.
+%
+<<figrejection,fig.width=5.5,fig.height=5.5>>=
+rejection_plot(pBH, at="sample",
+               xlim=c(0, 0.5), ylim=c(0, 2000),
+               xlab="FDR cutoff (Benjamini & Hochberg adjusted p-value)", main="")
+@
+The plot is shown in the left panel of Figure~\ref{figrej}.
+
+
+%------------------------------------------------------------
+\subsection{Choice of filtering cutoff}\label{choose:cutoff}
+%------------------------------------------------------------
+If we select a fixed cutoff for the adjusted $p$-values, we can also look more closely at
+the relationship between the fraction of null hypotheses filtered and the total number of
+discoveries. The \texttt{filtered\_R} function wraps \texttt{filtered\_p} and just returns
+rejection counts. It requires you to choose a particular $p$-value cutoff, specified
+through the argument \Robject{alpha}.
+%
+<<filtered_R1,cache=TRUE>>=
+theta = seq(from=0, to=0.8, by=0.02)
+rejBH = filtered_R(alpha=0.1, filter=res$filterstat, test=res$pvalue, theta=theta, method="BH")
+@
+
+Because overfiltering (or use of a filter which is inappropriate for the
+application domain) discards both false and true null hypotheses, very large
+values of $\theta$ reduce power in this example:
+
+<<fignumreject,fig.width=5.5,fig.height=5.5>>=
+plot(theta, rejBH, type="l",
+     xlab=expression(theta), ylab="number of rejections")
+@
+The plot is shown in the right panel of Figure~\ref{figrej}.
+
+%------------------------------------------------------------
+\subsection{Choice of filtering statistic}\label{choose:filterstat}
+%------------------------------------------------------------
+We can use the analysis of the previous section~\ref{choose:cutoff} also to inform
+ourselves about different possible choices of filter statistic. We construct a dataframe
+with a number of different choices.
+
+<<differentstats,cache=TRUE>>=
+filterChoices = data.frame(
+  `mean`   = res$filterstat,
+  `geneID` = badfilter,
+  `min`    = rowMin(counts(cds)),
+  `max`    = rowMax(counts(cds)),
+  `sd`     = rowSds(counts(cds))
+)
+rejChoices = sapply(filterChoices, function(f)
+  filtered_R(alpha=0.1, filter=f, test=res$pvalue, theta=theta, method="BH"))
+<<colours,results='hide'>>=
+library("RColorBrewer")
+myColours = brewer.pal(ncol(filterChoices), "Set1")
+<<figdifferentstats,fig.width=5.5,fig.height=5.5>>=
+matplot(theta, rejChoices, type="l", lty=1, col=myColours, lwd=2,
+        xlab=expression(theta), ylab="number of rejections")
+legend("bottomleft", legend=colnames(filterChoices), fill=myColours)
+@
+%
+The result is shown in Figure~\ref{figdifferentstats}. It indicates that for the data at
+hand, \Robject{mean}, \Robject{max} and \Robject{sd} provide similar performance, whereas
+the other choices are less effective.
+\begin{figure}[tb]
+\begin{center}
+\includegraphics[width=0.49\textwidth]{figure/figdifferentstats-1}
+\caption{The number of rejections at FDR=10\% as a function of
+  $\theta$ (analogous to the right panel in Figure~\ref{figrej}) for a number of different choices of the filter statistic.}
+\label{figdifferentstats}
+\end{center}
+\end{figure}
+
+%--------------------------------------------------
+\section{Some more plots pertinent to multiple testing}
+%--------------------------------------------------
+%--------------------------------------------------
+\subsection{Joint distribution of filter statistic and  $p$-values}\label{sec:pvalhist}
+%--------------------------------------------------
+The left panel of Figure~\ref{figscatterindepfilt} shows the joint distribution of filter
+statistic and $p$-values. An alternative, perhaps simpler view is provided by the
+$p$-value histograms in Figure~\ref{fighistindepfilt}.  It shows how the filtering ameliorates the multiple testing
+problem -- and thus the severity of a multiple testing adjustment -- by removing a
+background set of hypotheses whose $p$-values are distributed more or less uniformly in
+$[0,1]$.
+<<histindepfilt, fig.width=7, fig.height=5>>=
+h1 = hist(res$pvalue[!pass], breaks=50, plot=FALSE)
+h2 = hist(res$pvalue[pass], breaks=50, plot=FALSE)
+colori <- c(`do not pass`="khaki", `pass`="powderblue")
+<<fighistindepfilt, dev="pdf">>=
+barplot(height = rbind(h1$counts, h2$counts), beside = FALSE,
+        col = colori, space = 0, main = "", ylab="frequency")
+text(x = c(0, length(h1$counts)), y = 0, label = paste(c(0,1)),
+     adj = c(0.5,1.7), xpd=NA)
+legend("topright", fill=rev(colori), legend=rev(names(colori)))
+@
+\begin{figure}[ht]
+\centering
+\includegraphics[width=.5\textwidth]{figure/fighistindepfilt-1}
+\caption{Histogram of $p$-values for all tests.
+  The area shaded in blue indicates the subset of those that pass the filtering,
+  the area in khaki those that do not pass.}
+\label{fighistindepfilt}
+\end{figure}
+
+%-----------------------------------------------------
+\subsection{Illustration of the Benjamini-Hochberg method}
+%------------------------------------------------------
+The Benjamini-Hochberg multiple testing adjustment
+procedure \cite{BH:1995} has a simple graphical illustration, which is
+produced in the following code chunk. Its result is shown in the left
+panel of Figure \ref{figmulttest}.
+%
+<<sortP, cache=TRUE>>=
+resFilt = res[pass,]
+orderInPlot = order(resFilt$pvalue)
+showInPlot = (resFilt$pvalue[orderInPlot] <= 0.06)
+alpha = 0.1
+<<sortedP, fig.width=4.5, fig.height=4.5>>=
+plot(seq(along=which(showInPlot)), resFilt$pvalue[orderInPlot][showInPlot],
+     pch=".", xlab = expression(rank(p[i])), ylab=expression(p[i]))
+abline(a=0, b=alpha/length(resFilt$pvalue), col="red3", lwd=2)
+@
+<<doBH, echo=FALSE, results='hide'>>=
+whichBH = which(resFilt$pvalue[orderInPlot] <= alpha*seq(along=resFilt$pvalue)/length(resFilt$pvalue))
+## Test some assertions:
+## - whichBH is a contiguous set of integers from 1 to length(whichBH)
+## - the genes selected by this graphical method coincide with those
+##   from p.adjust (i.e. padjFilt)
+stopifnot(length(whichBH)>0,
+          identical(whichBH, seq(along=whichBH)),
+          resFilt$FDR[orderInPlot][ whichBH] <= alpha,
+          resFilt$FDR[orderInPlot][-whichBH]  > alpha)
+@
+%
+%-----------------------------------------------------
+\subsection{Schweder and Spj\o{}tvoll plot}
+%------------------------------------------------------
+Schweder and Spj\o{}tvoll \cite{SchwederSpjotvoll1982} suggested a diagnostic plot
+of the observed $p$-values which permits estimation of the fraction of true null
+hypotheses. For a series of hypothesis tests $H_1, \ldots, H_m$ with $p$-values
+$p_i$, they suggested plotting
+%
+\begin{equation}
+  \left( 1-p_i, N(p_i) \right) \mbox{ for } i \in 1, \ldots, m,
+\end{equation}
+%
+where $N(p)$ is the number of $p$-values greater than $p$. An application of
+this diagnostic plot to \Robject{resFilt\$pvalue} is shown in the right panel of
+Figure \ref{figmulttest}.
+When all null hypotheses are true, the $p$-values are each uniformly distributed
+in $[0,1]$, Consequently, the cumulative distribution function of $(p_1, \ldots,
+p_m)$ is expected to be close to the line $F(t)=t$. By symmetry, the same
+applies to $(1 - p_1, \ldots, 1 - p_m)$.
+When (without loss of generality) the first $m_0$ null hypotheses are true and
+the other $m-m_0$ are false, the cumulative distribution function of $(1-p_1,
+\ldots, 1-p_{m_0})$ is again expected to be close to the line $F_0(t)=t$. The
+cumulative distribution function of $(1-p_{m_0+1}, \ldots, 1-p_{m})$, on the
+other hand, is expected to be close to a function $F_1(t)$ which stays below
+$F_0$ but shows a steep increase towards 1 as $t$ approaches $1$.
+In practice, we do not know which of the null hypotheses are true, so we can
+only observe a mixture whose cumulative distribution function is expected to be
+close to
+%
+\begin{equation}
+  F(t) = \frac{m_0}{m} F_0(t) + \frac{m-m_0}{m} F_1(t).
+\end{equation}
+%
+Such a situation is shown in the right panel of
+Figure \ref{figmulttest}. If
+$F_1(t)/F_0(t)$ is small for small $t$, then the mixture fraction
+$\frac{m_0}{m}$ can be estimated by fitting a line to the left-hand portion of
+the plot, and then noting its height on the right. Such a fit is shown by the
+red line in the right panel of Figure \ref{figmulttest}.
+%
+<<SchwSpjot, echo=FALSE, results='hide'>>=
+j  = round(length(resFilt$pvalue)*c(1, .66))
+px = (1-resFilt$pvalue[orderInPlot[j]])
+py = ((length(resFilt$pvalue)-1):0)[j]
+slope = diff(py)/diff(px)
+@
+<<SchwederSpjotvoll, fig.width=4.5, fig.height=4.5>>=
+plot(1-resFilt$pvalue[orderInPlot],
+     (length(resFilt$pvalue)-1):0, pch=".", xaxs="i", yaxs="i",
+     xlab=expression(1-p[i]), ylab=expression(N(p[i])))
+abline(a=0, slope, col="red3", lwd=2)
+abline(h=slope)
+text(x=0, y=slope, labels=paste(round(slope)), adj=c(-0.1, 1.3))
+@
+
+\begin{figure}[ht]
+\centering
+\includegraphics[width=.49\textwidth]{figure/sortedP-1}
+\includegraphics[width=.49\textwidth]{figure/SchwederSpjotvoll-1}
+\caption{\emph{Left:} illustration of the Benjamini-Hochberg multiple testing
+  adjustment procedure \cite{BH:1995}.  The black line shows the
+  $p$-values ($y$-axis) versus their rank ($x$-axis), starting with
+  the smallest $p$-value from the left, then the second smallest, and
+  so on. Only the first \Sexpr{sum(showInPlot)} $p$-values are shown.
+  The red line is a straight line with slope $\alpha/n$, where
+  $n=\Sexpr{length(resFilt[["pvalue"]])}$ is the number of tests, and
+  $\alpha=\Sexpr{alpha}$ is a target false discovery rate (FDR).  FDR
+  is controlled at the value $\alpha$ if the genes are selected
+  that lie to the left of the rightmost intersection between the red and black
+  lines: here, this results in \Sexpr{length(whichBH)} genes.
+  \emph{Right:} Schweder and Spj\o{}tvoll plot, as described in the text.}
+\label{figmulttest}
+\end{figure}
+
+
+%--------------------------------------------------
+\section*{Session information}
+%--------------------------------------------------
+<<sessionInfo, results='asis', echo=FALSE>>=
+si = as.character( toLatex( sessionInfo() ) )
+cat( si[ -grep( "Locale", si ) ], sep = "\n" )
+@
+
+
+\bibliography{library}
+
+\end{document}
diff --git a/inst/doc/independent_filtering.pdf b/inst/doc/independent_filtering.pdf
new file mode 100644
index 0000000..692fde6
Binary files /dev/null and b/inst/doc/independent_filtering.pdf differ
diff --git a/inst/doc/independent_filtering_plots.R b/inst/doc/independent_filtering_plots.R
new file mode 100644
index 0000000..1945c97
--- /dev/null
+++ b/inst/doc/independent_filtering_plots.R
@@ -0,0 +1,79 @@
+## ----knitr, echo=FALSE, results="hide"-----------------------------------
+library("knitr")
+opts_chunk$set(tidy=FALSE,dev="png",fig.show="hide",
+               fig.width=4,fig.height=4.5,dpi=240,
+               message=FALSE,error=FALSE,warning=FALSE)
+
+## ----style, eval=TRUE, echo=FALSE, results="asis"--------------------------
+BiocStyle:::latex2()
+
+## ----setup, echo=FALSE--------------------------------------------------------
+options( width = 80 )
+
+## ----libraries----------------------------------------------------------------
+library("genefilter")
+library("ALL")
+data("ALL")
+
+## ----sample_data, cache=TRUE--------------------------------------------------
+bcell <- grep("^B", as.character(ALL$BT))
+moltyp <- which(as.character(ALL$mol.biol) %in% 
+                c("NEG", "BCR/ABL"))
+ALL_bcrneg <- ALL[, intersect(bcell, moltyp)]
+ALL_bcrneg$mol.biol <- factor(ALL_bcrneg$mol.biol)
+n1 <- n2 <- 3
+set.seed(1969)
+use <- unlist(tapply(1:ncol(ALL_bcrneg), 
+                     ALL_bcrneg$mol.biol, sample, n1))
+subsample <- ALL_bcrneg[,use]
+
+## ----stats, cache=TRUE--------------------------------------------------------
+S <- rowSds( exprs( subsample ) )
+temp <- rowttests( subsample, subsample$mol.biol )
+d <- temp$dm
+p <- temp$p.value
+t <- temp$statistic
+
+## ----filter_volcano, include=FALSE--------------------------------------------
+S_cutoff <- quantile(S, .50)
+filter_volcano(d, p, S, n1, n2, alpha=.01, S_cutoff)
+
+## ----kappa, include=FALSE-----------------------------------------------------
+t <- seq(0, 5, length=100)
+plot(t, kappa_t(t, n1, n2) * S_cutoff, 
+     xlab="|T|", ylab="Fold change bound", type="l")
+
+## ----table--------------------------------------------------------------------
+table(ALL_bcrneg$mol.biol)
+
+## ----filtered_p---------------------------------------------------------------
+S2 <- rowVars(exprs(ALL_bcrneg))
+p2 <- rowttests(ALL_bcrneg, "mol.biol")$p.value
+theta <- seq(0, .5, .1)
+p_bh <- filtered_p(S2, p2, theta, method="BH")
+
+## ----p_bh---------------------------------------------------------------------
+head(p_bh)
+
+## ----rejection_plot-----------------------------------------------------------
+rejection_plot(p_bh, at="sample",
+               xlim=c(0,.3), ylim=c(0,1000),
+               main="Benjamini & Hochberg adjustment")
+
+## ----filtered_R---------------------------------------------------------------
+theta <- seq(0, .80, .01)
+R_BH <- filtered_R(alpha=.10, S2, p2, theta, method="BH")
+
+## ----R_BH---------------------------------------------------------------------
+head(R_BH)
+
+## ----filtered_R_plot----------------------------------------------------------
+plot(theta, R_BH, type="l",
+     xlab=expression(theta), ylab="Rejections",
+     main="BH cutoff = .10"
+     )
+
+## ----sessionInfo, results='asis', echo=FALSE----------------------------------
+si <- as.character( toLatex( sessionInfo() ) )
+cat( si[ -grep( "Locale", si ) ], sep = "\n" )
+
diff --git a/inst/doc/independent_filtering_plots.Rnw b/inst/doc/independent_filtering_plots.Rnw
new file mode 100644
index 0000000..a433218
--- /dev/null
+++ b/inst/doc/independent_filtering_plots.Rnw
@@ -0,0 +1,238 @@
+%\VignetteIndexEntry{Additional plots for: Independent filtering increases power for detecting differentially expressed genes, Bourgon et al., PNAS (2010)}
+%\VignettePackage{genefilter}
+%\VignetteEngine{knitr::knitr}
+
+% To compile this document
+% library('knitr'); rm(list=ls()); knit('independent_filtering_plots.Rnw')
+
+\documentclass[10pt]{article}
+
+<<knitr, echo=FALSE, results="hide">>=
+library("knitr")
+opts_chunk$set(tidy=FALSE,dev="png",fig.show="hide",
+               fig.width=4,fig.height=4.5,dpi=240,
+               message=FALSE,error=FALSE,warning=FALSE)
+@ 
+
+<<style, eval=TRUE, echo=FALSE, results="asis">>=
+BiocStyle:::latex2()
+@
+
+\usepackage{xstring}
+\newcommand{\thetitle}{Additional plots for: Independent filtering increases power for detecting differentially expressed genes, Bourgon et al., PNAS (2010)}
+
+\title{\thetitle}
+\author{Richard Bourgon}
+
+% The following command makes use of SVN's 'Date' keyword substitution
+% To activate this, I used: svn propset svn:keywords Date independent_filtering_plots.Rnw
+\date{\Rpackage{genefilter} version \Sexpr{packageDescription("genefilter")$Version} (Last revision \StrMid{$Date: 2016-03-22 18:37:15 -0400 (Tue, 22 Mar 2016) $}{8}{18})}
+
+\begin{document}
+
+<<setup, echo=FALSE>>=
+options( width = 80 )
+@ 
+
+% Make title
+\maketitle
+\tableofcontents
+\vspace{.25in}
+
+
+%%%%%%%% Main text
+
+\section{Introduction}
+
+This vignette illustrates use of some functions in the
+\emph{genefilter} package that provide useful diagnostics 
+for independent filtering~\cite{BourgonIndependentFiltering}:
+
+\begin{itemize}
+  \item \texttt{kappa\_p} and \texttt{kappa\_t}
+  \item \texttt{filtered\_p} and \texttt{filtered\_R}
+  \item \texttt{filter\_volcano}
+  \item \texttt{rejection\_plot}
+\end{itemize}
+
+\section{Data preparation}
+
+Load the ALL data set and the \emph{genefilter} package:
+
+<<libraries>>=
+library("genefilter")
+library("ALL")
+data("ALL")
+@
+
+Reduce to just two conditions, then take a small subset of arrays from these,
+with 3 arrays per condition:
+
+<<sample_data, cache=TRUE>>=
+bcell <- grep("^B", as.character(ALL$BT))
+moltyp <- which(as.character(ALL$mol.biol) %in% 
+                c("NEG", "BCR/ABL"))
+ALL_bcrneg <- ALL[, intersect(bcell, moltyp)]
+ALL_bcrneg$mol.biol <- factor(ALL_bcrneg$mol.biol)
+n1 <- n2 <- 3
+set.seed(1969)
+use <- unlist(tapply(1:ncol(ALL_bcrneg), 
+                     ALL_bcrneg$mol.biol, sample, n1))
+subsample <- ALL_bcrneg[,use]
+@
+
+We now use functions from \emph{genefilter} to compute overall standard devation
+filter statistics as well as standard two-sample $t$ and releated statistics.
+
+<<stats, cache=TRUE>>=
+S <- rowSds( exprs( subsample ) )
+temp <- rowttests( subsample, subsample$mol.biol )
+d <- temp$dm
+p <- temp$p.value
+t <- temp$statistic
+@ 
+
+
+\section{Filtering volcano plot}
+
+Filtering on overall standard deviation and then using a standard $t$-statistic
+induces a lower bound of fold change, albeit one which varies somewhat with the
+significance of the $t$-statistic. The \texttt{filter\_volcano} function allows
+you to visualize this effect.
+
+<<filter_volcano, include=FALSE>>=
+S_cutoff <- quantile(S, .50)
+filter_volcano(d, p, S, n1, n2, alpha=.01, S_cutoff)
+@ 
+The output is shown in the left panel of Fig.~\ref{fig:volcano}.
+
+\begin{figure}[tb]
+\begin{center}
+\includegraphics[width=0.49\textwidth]{figure/filter_volcano-1}
+\includegraphics[width=0.49\textwidth]{figure/kappa-1}
+\caption{Left panel: plot produced by the \texttt{filter\_volcano} function.
+Right panel: graph of the \texttt{kappa\_t} function.}
+\label{fig:volcano}
+\end{center}
+\end{figure}
+
+The \texttt{kappa\_p} and \texttt{kappa\_t} functions, used to make the volcano
+plot, compute the fold change bound multiplier as a function of either a
+$t$-test $p$-value or the $t$-statistic itself. The actual induced bound on the
+fold change is $\kappa$ times the filter's cutoff on the overall standard
+deviation. Note that fold change bounds for values of $|T|$ which are close to 0
+are not of practical interest because we will not reject the null hypothesis
+with test statistics in this range.
+
+<<kappa, include=FALSE>>=
+t <- seq(0, 5, length=100)
+plot(t, kappa_t(t, n1, n2) * S_cutoff, 
+     xlab="|T|", ylab="Fold change bound", type="l")
+@
+The plot is shown in the right panel of Fig.~\ref{fig:volcano}.
+
+
+
+\section{Rejection count plots}
+
+\subsection{Across $p$-value cutoffs}
+
+The \texttt{filtered\_p} function permits easy simultaneous calculation of
+unadjusted or adjusted $p$-values over a range of filtering thresholds
+($\theta$). Here, we return to the full ``BCR/ABL'' versus ``NEG'' data set, and
+compute adjusted $p$-values using the method of Benjamini and Hochberg, for a
+range of different filter stringencies.
+
+\begin{figure}[tb]
+\begin{center}
+\includegraphics[width=0.49\textwidth]{figure/rejection_plot-1}
+\includegraphics[width=0.49\textwidth]{figure/filtered_R_plot-1}
+\caption{Left panel: plot produced by the \texttt{rejection\_plot} function.
+Right panel: graph of \texttt{theta}.}
+\label{fig:rej}
+\end{center}
+\end{figure}
+
+
+<<table>>=
+table(ALL_bcrneg$mol.biol)
+@
+
+<<filtered_p>>=
+S2 <- rowVars(exprs(ALL_bcrneg))
+p2 <- rowttests(ALL_bcrneg, "mol.biol")$p.value
+theta <- seq(0, .5, .1)
+p_bh <- filtered_p(S2, p2, theta, method="BH")
+@
+
+<<p_bh>>=
+head(p_bh)
+@ 
+
+The \texttt{rejection\_plot} function takes sets of $p$-values corresponding to
+different filtering choices --- in the columns of a matrix or in a list --- and
+shows how rejection count ($R$) relates to the choice of cutoff for the
+$p$-values. For these data, over a reasonable range of FDR cutoffs, increased
+filtering corresponds to increased rejections.
+
+<<rejection_plot>>=
+rejection_plot(p_bh, at="sample",
+               xlim=c(0,.3), ylim=c(0,1000),
+               main="Benjamini & Hochberg adjustment")
+@
+The plot is shown in the left panel of Fig.~\ref{fig:rej}.
+
+
+
+
+\subsection{Across filtering fractions}
+
+If we select a fixed cutoff for the adjusted $p$-values, we can also look more
+closely at the relationship between the fraction of null hypotheses filtered and
+the total number of discoveries. The \texttt{filtered\_R} function wraps
+\texttt{filtered\_p} and just returns rejection counts. It requires a $p$-value
+cutoff. 
+
+<<filtered_R>>=
+theta <- seq(0, .80, .01)
+R_BH <- filtered_R(alpha=.10, S2, p2, theta, method="BH")
+@
+
+<<R_BH>>=
+head(R_BH)
+@
+
+Because overfiltering (or use of a filter which is inappropriate for the
+application domain) discards both false and true null hypotheses, very large
+values of $\theta$ reduce power in this example:
+
+<<filtered_R_plot>>=
+plot(theta, R_BH, type="l",
+     xlab=expression(theta), ylab="Rejections",
+     main="BH cutoff = .10"
+     )
+@
+The plot is shown in the right panel of Fig.~\ref{fig:rej}.
+
+
+
+%%%%%%%% Session info
+
+\section*{Session information}
+
+<<sessionInfo, results='asis', echo=FALSE>>=
+si <- as.character( toLatex( sessionInfo() ) )
+cat( si[ -grep( "Locale", si ) ], sep = "\n" )
+@
+
+
+\begin{thebibliography}{10}
+\bibitem{BourgonIndependentFiltering}
+Richard Bourgon, Robert Gentleman and Wolfgang Huber.
+\newblock Independent filtering increases power for detecting differentially
+expressed genes.
+\end{thebibliography}
+
+
+
+\end{document}
diff --git a/inst/doc/independent_filtering_plots.pdf b/inst/doc/independent_filtering_plots.pdf
new file mode 100644
index 0000000..a4ba52e
Binary files /dev/null and b/inst/doc/independent_filtering_plots.pdf differ
diff --git a/inst/wFun/Anova.xml b/inst/wFun/Anova.xml
new file mode 100644
index 0000000..49e0a97
--- /dev/null
+++ b/inst/wFun/Anova.xml
@@ -0,0 +1,30 @@
+<?xml version="1.0"?>
+ <wFun xmlns:bt="http://www.bioconductor.org/WINVOKE">
+	<funName>Anova</funName>
+	<funArgList>
+		<funArg>
+			<argName>cov</argName>
+			<argDefault></argDefault>
+			<argType>numeric</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>TypeIn</argWidgetType>
+			<argRequired>TRUE</argRequired>
+		</funArg>
+		<funArg>
+			<argName>p</argName>
+			<argDefault>0.05</argDefault>
+			<argType>numeric</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>TypeIn</argWidgetType>
+			<argRequired>FALSE</argRequired>
+		</funArg>
+		<funArg>
+			<argName>na.rm</argName>
+			<argDefault>TRUE</argDefault>
+			<argType>logical</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>Radio</argWidgetType>
+			<argRequired>FALSE</argRequired>
+		</funArg>
+	</funArgList>
+</wFun>
\ No newline at end of file
diff --git a/inst/wFun/coxfilter.xml b/inst/wFun/coxfilter.xml
new file mode 100644
index 0000000..72a9eff
--- /dev/null
+++ b/inst/wFun/coxfilter.xml
@@ -0,0 +1,30 @@
+<?xml version="1.0"?>
+ <wFun xmlns:bt="http://www.bioconductor.org/WINVOKE">
+	<funName>coxfilter</funName>
+	<funArgList>
+		<funArg>
+			<argName>surt</argName>
+			<argDefault></argDefault>
+			<argType>numeric</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>TypeIn</argWidgetType>
+			<argRequired>TRUE</argRequired>
+		</funArg>
+		<funArg>
+			<argName>cens</argName>
+			<argDefault></argDefault>
+			<argType>numeric</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>TypeIn</argWidgetType>
+			<argRequired>TRUE</argRequired>
+		</funArg>
+		<funArg>
+			<argName>p</argName>
+			<argDefault></argDefault>
+			<argType>numeric</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>TypeIn</argWidgetType>
+			<argRequired>TRUE</argRequired>
+		</funArg>
+	</funArgList>
+</wFun>
\ No newline at end of file
diff --git a/inst/wFun/cv.xml b/inst/wFun/cv.xml
new file mode 100644
index 0000000..613f2cc
--- /dev/null
+++ b/inst/wFun/cv.xml
@@ -0,0 +1,30 @@
+<?xml version="1.0"?>
+ <wFun xmlns:bt="http://www.bioconductor.org/WINVOKE">
+	<funName>cv</funName>
+	<funArgList>
+		<funArg>
+			<argName>a</argName>
+			<argDefault>1</argDefault>
+			<argType>numeric</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>TypeIn</argWidgetType>
+			<argRequired>FALSE</argRequired>
+		</funArg>
+		<funArg>
+			<argName>b</argName>
+			<argDefault>Inf</argDefault>
+			<argType>numeric</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>TypeIn</argWidgetType>
+			<argRequired>FALSE</argRequired>
+		</funArg>
+		<funArg>
+			<argName>na.rm</argName>
+			<argDefault>TRUE</argDefault>
+			<argType>logical</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>Radio</argWidgetType>
+			<argRequired>FALSE</argRequired>
+		</funArg>
+	</funArgList>
+</wFun>
\ No newline at end of file
diff --git a/inst/wFun/gapFilter.xml b/inst/wFun/gapFilter.xml
new file mode 100644
index 0000000..91ab43a
--- /dev/null
+++ b/inst/wFun/gapFilter.xml
@@ -0,0 +1,46 @@
+<?xml version="1.0"?>
+ <wFun xmlns:bt="http://www.bioconductor.org/WINVOKE">
+	<funName>gapFilter</funName>
+	<funArgList>
+		<funArg>
+			<argName>Gap</argName>
+			<argDefault></argDefault>
+			<argType>numeric</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>TypeIn</argWidgetType>
+			<argRequired>TRUE</argRequired>
+		</funArg>
+		<funArg>
+			<argName>IQR</argName>
+			<argDefault></argDefault>
+			<argType>numeric</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>TypeIn</argWidgetType>
+			<argRequired>TRUE</argRequired>
+		</funArg>
+		<funArg>
+			<argName>Prop</argName>
+			<argDefault></argDefault>
+			<argType>nemeric</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>TypeIn</argWidgetType>
+			<argRequired>TRUE</argRequired>
+		</funArg>
+		<funArg>
+			<argName>na.rm</argName>
+			<argDefault>TRUE</argDefault>
+			<argType>logical</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>Radio</argWidgetType>
+			<argRequired>FALSE</argRequired>
+		</funArg>
+		<funArg>
+			<argName>neg.rm</argName>
+			<argDefault>TRUE</argDefault>
+			<argType>logical</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>Radio</argWidgetType>
+			<argRequired>FALSE</argRequired>
+		</funArg>
+	</funArgList>
+</wFun>
\ No newline at end of file
diff --git a/inst/wFun/kOverA.xml b/inst/wFun/kOverA.xml
new file mode 100644
index 0000000..891312e
--- /dev/null
+++ b/inst/wFun/kOverA.xml
@@ -0,0 +1,30 @@
+<?xml version="1.0"?>
+ <wFun xmlns:bt="http://www.bioconductor.org/WINVOKE">
+	<funName>kOverA</funName>
+	<funArgList>
+		<funArg>
+			<argName>k</argName>
+			<argDefault></argDefault>
+			<argType>numeric</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>TypeIn</argWidgetType>
+			<argRequired>TRUE</argRequired>
+		</funArg>
+		<funArg>
+			<argName>A</argName>
+			<argDefault>100</argDefault>
+			<argType>numeric</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>TypeIn</argWidgetType>
+			<argRequired>FALSE</argRequired>
+		</funArg>
+		<funArg>
+			<argName>na.rm</argName>
+			<argDefault>TRUE</argDefault>
+			<argType>logical</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>Radio</argWidgetType>
+			<argRequired>FALSE</argRequired>
+		</funArg>
+	</funArgList>
+</wFun>
\ No newline at end of file
diff --git a/inst/wFun/maxA.xml b/inst/wFun/maxA.xml
new file mode 100644
index 0000000..b9b5fce
--- /dev/null
+++ b/inst/wFun/maxA.xml
@@ -0,0 +1,22 @@
+<?xml version="1.0"?>
+ <wFun xmlns:bt="http://www.bioconductor.org/WINVOKE">
+	<funName>maxA</funName>
+	<funArgList>
+		<funArg>
+			<argName>A</argName>
+			<argDefault>75</argDefault>
+			<argType>numeric</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>TypeIn</argWidgetType>
+			<argRequired>FALSE</argRequired>
+		</funArg>
+		<funArg>
+			<argName>na.rm</argName>
+			<argDefault>TRUE</argDefault>
+			<argType>logical</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>Radio</argWidgetType>
+			<argRequired>FALSE</argRequired>
+		</funArg>
+	</funArgList>
+</wFun>
\ No newline at end of file
diff --git a/inst/wFun/pOverA.xml b/inst/wFun/pOverA.xml
new file mode 100644
index 0000000..8561312
--- /dev/null
+++ b/inst/wFun/pOverA.xml
@@ -0,0 +1,30 @@
+<?xml version="1.0"?>
+ <wFun xmlns:bt="http://www.bioconductor.org/WINVOKE">
+	<funName>pOverA</funName>
+	<funArgList>
+		<funArg>
+			<argName>p</argName>
+			<argDefault>0.05</argDefault>
+			<argType>numeric</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>TypeIn</argWidgetType>
+			<argRequired>FALSE</argRequired>
+		</funArg>
+		<funArg>
+			<argName>A</argName>
+			<argDefault>100</argDefault>
+			<argType>numeric</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>TypeIn</argWidgetType>
+			<argRequired>FALSE</argRequired>
+		</funArg>
+		<funArg>
+			<argName>na.rm</argName>
+			<argDefault>TRUE</argDefault>
+			<argType>logical</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>Radio</argWidgetType>
+			<argRequired>FALSE</argRequired>
+		</funArg>
+	</funArgList>
+</wFun>
\ No newline at end of file
diff --git a/inst/wFun/ttest.xml b/inst/wFun/ttest.xml
new file mode 100644
index 0000000..cdc087c
--- /dev/null
+++ b/inst/wFun/ttest.xml
@@ -0,0 +1,30 @@
+<?xml version="1.0"?>
+ <wFun xmlns:bt="http://www.bioconductor.org/WINVOKE">
+	<funName>ttest</funName>
+	<funArgList>
+		<funArg>
+			<argName>m</argName>
+			<argDefault></argDefault>
+			<argType>numeric</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>TypeIn</argWidgetType>
+			<argRequired>TRUE</argRequired>
+		</funArg>
+		<funArg>
+			<argName>p</argName>
+			<argDefault>0.05</argDefault>
+			<argType>numeric</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>TypeIn</argWidgetType>
+			<argRequired>FALSE</argRequired>
+		</funArg>
+		<funArg>
+			<argName>na.rm</argName>
+			<argDefault>TRUE</argDefault>
+			<argType>logical</argType>
+			<argLocation>main</argLocation>
+			<argWidgetType>Radio</argWidgetType>
+			<argRequired>FALSE</argRequired>
+		</funArg>
+	</funArgList>
+</wFun>
\ No newline at end of file
diff --git a/man/Anova.Rd b/man/Anova.Rd
new file mode 100644
index 0000000..04d25af
--- /dev/null
+++ b/man/Anova.Rd
@@ -0,0 +1,44 @@
+\name{Anova}
+\alias{Anova}
+\title{A filter function for Analysis of Variance }
+\description{
+  \code{Anova} returns a function of one argument with bindings for
+  \code{cov} and \code{p}.
+  The function, when evaluated, performs an ANOVA using \code{cov} as
+  the covariate. It returns \code{TRUE} if the p value for a difference
+  in means is less than \code{p}. 
+}
+\usage{
+Anova(cov, p=0.05, na.rm=TRUE)
+}
+\arguments{
+  \item{cov}{The covariate. It must have length equal to the number of
+    columns of the array that \code{Anova} will be applied to. }
+  \item{p}{ The p-value for the test. }
+  \item{na.rm}{If set to \code{TRUE} any \code{NA}'s will be removed. }
+}
+
+\details{
+  The function returned by \code{Anova} uses \code{lm} to fit a linear
+  model of the form
+  \code{lm(x ~ cov)}, where \code{x} is the set of gene expressions.
+  The F statistic for an overall effect is computed and if it has a
+  \emph{p}-value less than \code{p} the function returns \code{TRUE},
+  otherwise it returns \code{FALSE} for that gene.
+  }
+\value{
+ \code{Anova} returns a function with bindings for \code{cov} and
+ \code{p} that will perform a one-way ANOVA.
+
+  The covariate can be continuous, in which case the test is for a linear 
+  effect for the covariate.
+}
+\author{R. Gentleman }
+\seealso{\code{\link{kOverA}}, \code{\link{lm}} }
+
+\examples{
+  set.seed(123)
+  af <- Anova(c(rep(1,5),rep(2,5)), .01)
+  af(rnorm(10))
+}
+\keyword{manip}
diff --git a/man/coxfilter.Rd b/man/coxfilter.Rd
new file mode 100644
index 0000000..0632fd1
--- /dev/null
+++ b/man/coxfilter.Rd
@@ -0,0 +1,38 @@
+\name{coxfilter}
+\alias{coxfilter}
+
+\title{A filter function for univariate Cox regression. }
+\description{
+  A function that performs Cox regression with bindings for \code{surt},
+  \code{cens}, and \code{p} is returned. This function filters genes
+  according to the attained p-value from a Cox regression using
+  \code{surt} as the survival times, and \code{cens} as the censoring
+  indicator. It requires \code{survival}.
+}
+\usage{
+coxfilter(surt, cens, p)
+}
+\arguments{
+  \item{surt}{Survival times.}
+  \item{cens}{Censoring indicator. }
+  \item{p}{The p-value to use in filtering. }
+}
+
+\value{
+  Calls to the \code{\link[survival]{coxph}} function in the \code{survival}
+    library are used to fit a Cox model. The filter function returns
+    \code{TRUE} if the p-value in the fit is less than \code{p}.
+}
+
+\author{R. Gentleman }
+\seealso{\code{\link{Anova}}}
+
+\examples{
+   set.seed(-5)
+   sfun <- coxfilter(rexp(10), ifelse(runif(10) < .7, 1, 0), .05)
+   ffun <- filterfun(sfun)
+   dat <- matrix(rnorm(1000), ncol=10)
+   out <- genefilter(dat, ffun)
+}
+\keyword{manip}
+
diff --git a/man/cv.Rd b/man/cv.Rd
new file mode 100644
index 0000000..a7005d4
--- /dev/null
+++ b/man/cv.Rd
@@ -0,0 +1,37 @@
+\name{cv}
+\alias{cv}
+\title{A filter function for the coefficient of variation.}
+\description{
+  \code{cv} returns a function with values for \code{a} and \code{b}
+  bound. This function takes a single argument. It computes the
+  coefficient of variation for the input vector and returns \code{TRUE} if
+  the coefficient of variation is between \code{a} and
+  \code{b}. Otherwise it returns \code{FALSE}
+}
+\usage{
+cv(a=1, b=Inf, na.rm=TRUE)
+}
+\arguments{
+  \item{a}{The lower bound for the cv. }
+  \item{b}{The upper bound for the cv. }
+  \item{na.rm}{If set to \code{TRUE} any \code{NA}'s will be removed. }
+}
+\details{
+  The coefficient of variation is the standard deviation divided by the 
+  absolute value of the mean.
+}
+\value{
+ It returns a function of one argument. The function has an environment
+ with bindings for \code{a} and \code{b}.
+}
+\author{R. Gentleman }
+\seealso{\code{\link{pOverA}}, \code{\link{kOverA}} }
+
+\examples{
+  set.seed(-3)
+  cvfun <- cv(1,10)
+  cvfun(rnorm(10,10))
+  cvfun(rnorm(10))
+}
+\keyword{manip}
+
diff --git a/man/dist2.Rd b/man/dist2.Rd
new file mode 100644
index 0000000..da19878
--- /dev/null
+++ b/man/dist2.Rd
@@ -0,0 +1,67 @@
+\name{dist2}
+\alias{dist2}
+
+\title{
+  Calculate an n-by-n matrix by applying a function to
+  all pairs of columns of an m-by-n matrix.
+}
+\description{
+  Calculate an n-by-n matrix by applying a function to
+  all pairs of columns of an m-by-n matrix.
+}
+\usage{
+  dist2(x, fun, diagonal=0)
+}
+
+\arguments{
+  \item{x}{A matrix.}
+  \item{fun}{A symmetric function of two arguments that may be columns of \code{x}.}
+  \item{diagonal}{The value to be used for the diagonal elements of the
+    resulting matrix.}
+}
+\details{
+  With the default value of \code{fun}, this function calculates
+  for each pair of columns of \code{x} the mean of the absolute values
+  of their differences (which is proportional to the L1-norm of their
+  difference). This is a distance metric.
+
+  The implementation assumes that
+  \code{fun(x[,i], x[,j])} can be evaluated for all pairs of \code{i}
+  and \code{j} (see examples), and that
+  \code{fun} is symmetric, i.e.
+  \code{fun(a, b) = fun(b, a)}.
+  \code{fun(a, a)} is not actually evaluated, instead the value of \code{diagonal}
+  is used to fill the diagonal elements of the returned matrix.
+
+  Note that \code{\link[stats:dist]{dist}} computes distances between rows of
+  \code{x}, while this function computes relations between columns of
+  \code{x} (see examples).
+}
+\value{
+  A symmetric matrix of size \code{n x n}.
+}
+\author{
+  Wolfgang Huber, James Reid
+}
+\examples{
+
+  # example matrix
+  z = matrix(1:15693, ncol=3)
+  matL1 = dist2(z)
+  matL2 = dist2(z, fun=function(a,b) sqrt(sum((a-b)^2, na.rm=TRUE)))
+
+  euc = as.matrix(dist(t(z)))
+
+  stopifnot(identical(dim(matL2), dim(euc)),
+            all(euc==matL2))
+
+}
+\keyword{manip}
+
+
+
+
+
+
+
+
diff --git a/man/eSetFilter.Rd b/man/eSetFilter.Rd
new file mode 100644
index 0000000..b701a8b
--- /dev/null
+++ b/man/eSetFilter.Rd
@@ -0,0 +1,58 @@
+\name{eSetFilter}
+\alias{eSetFilter}
+\alias{getFilterNames}
+\alias{getFuncDesc}
+\alias{getRdAsText}
+\alias{parseDesc}
+\alias{parseArgs}
+\alias{setESetArgs}
+\alias{isESet}
+\alias{showESet}
+\title{A function to filter an eSet object}
+\description{
+  Given a Bioconductor's ExpressionSet object, this function filters
+  genes using a set of selected filters.
+}
+\usage{
+eSetFilter(eSet)
+getFilterNames()
+getFuncDesc(lib = "genefilter", funcs = getFilterNames())
+getRdAsText(lib)
+parseDesc(text)
+parseArgs(text)
+showESet(eSet)
+setESetArgs(filter)
+isESet(eSet)
+}
+\arguments{
+  \item{eSet}{\code{eSet} an ExpressionSet object}
+  \item{lib}{\code{lib} a character string for the name of an R library
+    where functions of interests reside}
+  \item{funcs}{\code{funcs} a vector of character strings for names of
+    functions of interest}
+  \item{text}{\code{text} a character of string from a filed
+    (e. g. description, argument, ..) filed of an Rd file for a
+    fucntion}
+  \item{filter}{\code{filter} a character string for the name of a
+  filter function} 
+}
+\details{
+  A set of filters may be selected to filter genes in through each of
+  the filters in the order the filters have been selected
+}
+\value{
+  A logical vector of length equal to the number of rows of 'expr'.
+  The values in that vector indicate whether the corresponding row
+  of 'expr' passed the set of filter functions.
+}
+\author{Jianhua Zhang}
+
+\seealso{\code{\link{genefilter}}}
+\examples{
+ if( interactive() ) {
+   data(sample.ExpressionSet)      
+   res <- eSetFilter(sample.ExpressionSet)
+ }
+}
+\keyword{manip}
+
diff --git a/man/filter_volcano.Rd b/man/filter_volcano.Rd
new file mode 100644
index 0000000..c0d3695
--- /dev/null
+++ b/man/filter_volcano.Rd
@@ -0,0 +1,81 @@
+\name{filter_volcano}
+
+\Rdversion{1.1}
+
+\alias{filter_volcano}
+
+\title{Volcano plot for overall variance filtering}
+
+\description{
+  Generate a volcano plot contrasting p-value with fold change (on the
+  log scale), in order to visualize the effect of filtering on overall
+  variance and also assign significance via p-value.
+}
+
+\usage{
+filter_volcano(
+               d, p, S,
+               n1, n2,
+               alpha, S_cutoff,
+               cex = 0.5, pch = 19,
+               xlab = expression(paste(log[2], " fold change")),
+               ylab = expression(paste("-", log[10], " p")),
+               cols = c("grey80", "grey50", "black"),
+               ltys = c(1, 3),
+               use_legend = TRUE,
+               ...
+               )
+}
+
+\arguments{
+  \item{d}{Fold changes, typically on the log scale, base 2.}
+  
+  \item{p}{The p-values}
+
+  \item{S}{
+    The overall standard deviation filter statistics, i.e., the
+    square roots of the overall variance filter statistics.
+  }
+
+  \item{n1}{Sample size for group 1.}
+
+  \item{n2}{Sample size for group 2.}
+  
+  \item{alpha}{Significance cutoff used for p-values.}
+  
+  \item{S_cutoff}{
+    Filter cutoff used for the overall standard deviation in \code{S}.
+  }
+  
+  \item{cex}{Point size for plotting.}
+
+  \item{pch}{Point character for plotting.}
+  
+  \item{xlab}{Label for x-axis.}
+  
+  \item{ylab}{Label for y-axis.}
+  
+  \item{cols}{
+    A vector of three colors used for plotting. These correspond to
+    filtered data, data which pass the filter but are insignificant, and
+    data pass the filter and are also statistically significant.
+  }
+  
+  \item{ltys}{
+    The induced bound on log-scale fold change is plotted, as is the
+    significance cutoff for data passing the filter. The \code{ltys}
+    argument gives line styles for these drawing these two thresholds on
+    the plot.
+  }
+
+  \item{use_legend}{Should a legend for point color be produced?}
+
+  \item{\dots}{Other arguments for \code{plot}.}
+  
+}
+
+\author{Richard Bourgon <bourgon at ebi.ac.uk>}
+
+\examples{
+# See the vignette: Diagnostic plots for independent filtering
+}
diff --git a/man/filtered_p.Rd b/man/filtered_p.Rd
new file mode 100644
index 0000000..59a8251
--- /dev/null
+++ b/man/filtered_p.Rd
@@ -0,0 +1,87 @@
+\name{filtered_p}
+
+\Rdversion{1.1}
+
+\alias{filtered_p}
+\alias{filtered_R}
+
+\title{
+  Compute and adjust p-values, with filtering
+}
+
+\description{
+  Given filter and test statistics in the form of unadjusted p-values,
+  or functions able to compute these statistics from the data, filter
+  and then correct the p-values across a range of filtering
+  stringencies. 
+}
+
+\usage{
+filtered_p(filter, test, theta, data, method = "none")
+filtered_R(alpha, filter, test, theta, data, method = "none")
+}
+
+\arguments{
+
+  \item{alpha}{
+    A cutoff to which p-values, possibly adjusted for multiple testing,
+    will be compared.
+  }
+  
+  \item{filter}{
+    A vector of stage-one filter statistics, or a function which is able
+    to compute this vector from \code{data}, if \code{data} is supplied.
+  }
+  
+  \item{test}{
+    A vector of unadjusted p-values, or a function which is able
+    to compute this vector from the filtered portion of \code{data}, if
+    \code{data} is supplied. The option to supply a function is useful
+    when the value of the test statistic depends on which hypotheses are
+    filtered out at stage one. (The \pkg{limma} t-statistic is an
+    example.) 
+  }
+  
+  \item{theta}{
+    A vector with one or more filtering fractions to consider. Actual
+    cutoffs are then computed internally by applying
+    \code{\link{quantile}} to the filter statistics contained in (or
+    produced by) the \code{filter} argument.
+  }
+  
+  \item{data}{
+    If \code{filter} and/or \code{test} are functions rather than
+    vectors of statistics, they will be applied to \code{data}. The
+    functions will be passed the whole \code{data} object, and must work
+    over rows, etc. themselves as appropriate.
+  }
+  
+  \item{method}{
+    The unadjusted p-values contained in (or produced by) \code{test}
+    will be adjusted for multiple testing after filtering, using the
+    \code{\link{p.adjust}} function in the \pkg{stats} package. See the
+    \code{method} argument there for options.
+  }p
+  
+}
+
+\value{
+  For \code{filtered_p}, a matrix of p-values, possible adjusted for
+  multiple testing, with one row per null hypothesis and one column per
+  filtering fraction given in \code{theta}. For a given column, entries
+  which have been filtered out are \code{NA}.
+
+  For \code{filtered_R}, a count of the entries in the \code{filtered_p}
+  result which are less than \code{alpha}.
+}
+
+\author{Richard Bourgon <bourgon at ebi.ac.uk>}
+
+\examples{
+# See the vignette: Diagnostic plots for independent filtering
+}
+
+\seealso{
+  See \code{\link{rejection_plot}} for visualization of
+  \code{filtered_p} results.
+}
diff --git a/man/filterfun.Rd b/man/filterfun.Rd
new file mode 100644
index 0000000..218e8de
--- /dev/null
+++ b/man/filterfun.Rd
@@ -0,0 +1,37 @@
+\name{filterfun}
+\alias{filterfun}
+\title{Creates a first FALSE exiting function from the list of
+  filter functions it is given. }
+\description{
+  This function creates a function that takes a single argument. The
+  filtering functions are bound in the environment of the returned
+  function and are applied sequentially to the argument of the returned
+  function. When the first filter function evaluates to \code{FALSE} the
+  function returns \code{FALSE} otherwise it returns \code{TRUE}.
+}
+\usage{
+filterfun(...)
+}
+\arguments{
+  \item{...}{Filtering functions. }
+}
+
+\value{
+ \code{filterfun} returns a function that takes a single argument. It
+ binds the filter functions given to it in the environment of the
+ returned function. These functions are applied sequentially (in the
+ order they were given to \code{filterfun}). The function returns
+ \code{FALSE} (and exits) when the first filter function returns
+ \code{FALSE} otherwise it returns \code{TRUE}.
+}
+\author{R. Gentleman }
+\seealso{\code{\link{genefilter}} }
+\examples{
+ set.seed(333)
+ x <- matrix(rnorm(100,2,1),nc=10)
+ cvfun <- cv(.5,2.5)
+ ffun <- filterfun(cvfun)
+ which <- genefilter(x, ffun)
+}
+\keyword{manip}
+
diff --git a/man/findLargest.Rd b/man/findLargest.Rd
new file mode 100644
index 0000000..bbd64c0
--- /dev/null
+++ b/man/findLargest.Rd
@@ -0,0 +1,45 @@
+\name{findLargest}
+\alias{findLargest}
+\title{Find the Entrez Gene ID corresponding to the largest statistic}
+\description{
+  Most microarrays have multiple probes per gene (Entrez). This function
+  finds all replicates, and then selects the one with the largest value
+  of the test statistic.
+}
+\usage{
+findLargest(gN, testStat, data = "hgu133plus2")
+}
+
+\arguments{
+  \item{gN}{A vector of probe identifiers for the chip.}
+  \item{testStat}{A vector of test statistics, of the same length as
+    \code{gN} with the per probe test statistics.}
+  \item{data}{The character string identifying the chip.}
+}
+\details{
+  All the probe identifiers, \code{gN}, are mapped to Entrez Gene IDs
+  and the duplicates determined.  For any set of probes that map to the
+  same Gene ID, the one with the largest test statistic is found. The
+  return vector is the named vector of selected probe identifiers. The
+  names are the Entrez Gene IDs.
+
+  This could be extended in different ways, such as allowing the user to
+  use a different selection criterion.  Also, matching on different
+  identifiers seems like another alternative.
+}
+\value{
+ A named vector of probe IDs. The names are Entrez Gene IDs.
+}
+
+\author{R. Gentleman}
+
+\seealso{\code{\link{sapply}}}
+\examples{
+  library("hgu95av2.db")
+  set.seed(124)
+  gN <- sample(ls(hgu95av2ENTREZID), 200)
+  stats <- rnorm(200)
+  findLargest(gN, stats, "hgu95av2")
+
+}
+\keyword{manip}
diff --git a/man/gapFilter.Rd b/man/gapFilter.Rd
new file mode 100644
index 0000000..076050c
--- /dev/null
+++ b/man/gapFilter.Rd
@@ -0,0 +1,51 @@
+\name{gapFilter}
+\alias{gapFilter}
+\title{ A filter to select genes based on there being a gap. }
+\description{
+  The \code{gapFilter} looks for genes that might usefully discriminate
+  between two groups (possibly unknown at the time of filtering).
+  To do this we look for a gap in the ordered expression values. The gap
+  must come in the central portion (we exclude jumps in the initial
+  \code{Prop} values or the final \code{Prop} values).
+  Alternatively, if the IQR for the gene is large that will also pass
+  our test and the gene will be selected.
+}
+\usage{
+gapFilter(Gap, IQR, Prop, na.rm=TRUE, neg.rm=TRUE)
+}
+\arguments{
+  \item{Gap}{The size of the gap required to pass the test. }
+  \item{IQR}{The size of the IQR required to pass the test. }
+  \item{Prop}{The proportion (or number) of samples to exclude at either
+  end.}
+  \item{na.rm}{If \code{TRUE} then \code{NA}'s will be removed before
+    processing. }
+  \item{neg.rm}{ If \code{TRUE} then negative values in \code{x} will be
+    removed before processing.}
+}
+\details{
+  As stated above we are interested in 
+}
+\value{
+ A function that returns either \code{TRUE} or \code{FALSE} depending on
+ whether the vector supplied has a gap larger than \code{Gap} or an IQR
+ (inter quartile range) larger than \code{IQR}. For computing the gap we
+ want to exclude a proportion, \code{Prop} from either end of the sorted
+ values. The reason for this requirement is that genes which differ in
+ expression levels only for a few samples are not likely to be interesting.
+}
+
+\author{R. Gentleman }
+
+\seealso{\code{\link{ttest}}, \code{\link{genefilter}} }
+
+\examples{
+ set.seed(256)
+ x <- c(rnorm(10,100,3), rnorm(10, 100, 10))
+ y <- x + c(rep(0,10), rep(100,10))
+ tmp <- rbind(x,y) 
+ Gfilter <- gapFilter(200, 100, 5)
+ ffun <- filterfun(Gfilter)
+ genefilter(tmp, ffun)
+}
+\keyword{manip}
diff --git a/man/genefilter.Rd b/man/genefilter.Rd
new file mode 100644
index 0000000..748861d
--- /dev/null
+++ b/man/genefilter.Rd
@@ -0,0 +1,54 @@
+\name{genefilter}
+\alias{genefilter}
+\title{A function to filter genes.}
+\description{
+   \code{genefilter} filters genes in the array \code{expr} using the
+   filter functions in \code{flist}. It returns an array of logical
+   values (suitable for subscripting) of the same length as there are
+   rows in \code{expr}. For each row of \code{expr} the returned value
+   is \code{TRUE} if the row passed all the filter functions. Otherwise
+   it is set to \code{FALSE}.
+}
+\usage{
+genefilter(expr, flist)
+}
+\arguments{
+  \item{expr}{A \code{matrix} or \code{ExpressionSet} that the
+    filter functions will be applied to.}
+  \item{flist}{A \code{list} of filter functions to apply to the array.}
+}
+\details{
+   This package uses a very simple but powerful protocol for
+   \emph{filtering} genes. The user simply constructs any number of
+   tests that they want to apply. A test is simply a function (as
+   constructed using one of the many helper functions in this package)
+   that returns \code{TRUE} if the gene of interest passes the test (or
+   filter) and \code{FALSE} if the gene of interest fails.
+
+   The benefit of this approach is that each test is constructed
+   individually (and can be tested individually). The tests are then
+   applied sequentially to each gene. The function returns a logical
+   vector indicating whether the gene passed all tests functions or
+   failed at least one of them.
+
+   Users can construct their own filters. These filters should accept
+   a vector of values, corresponding to a row of the \code{expr} object.
+   The user defined function should return a length 1 logical vector,
+   with value \code{TRUE} or \code{FALSE}. User-defined functions can be 
+   combined with \code{\link{filterfun}}, just as built-in filters.
+}
+\value{
+  A logical \code{vector} of length equal to the number of rows of
+  \code{expr}. The values in that \code{vector} indicate whether the
+  corresponding row of \code{expr} passed the set of filter functions.
+}
+\author{R. Gentleman}
+\seealso{\code{\link{genefilter}}, \code{\link{kOverA}}}
+\examples{
+   set.seed(-1)
+   f1 <- kOverA(5, 10)
+   flist <- filterfun(f1)
+   exprA <- matrix(rnorm(1000, 10), ncol = 10)
+   ans <- genefilter(exprA, flist)
+}
+\keyword{manip}
diff --git a/man/genefinder.Rd b/man/genefinder.Rd
new file mode 100644
index 0000000..f7ac2e8
--- /dev/null
+++ b/man/genefinder.Rd
@@ -0,0 +1,98 @@
+\name{genefinder}
+\alias{genefinder}
+\alias{genefinder,ExpressionSet,vector-method}
+\alias{genefinder,matrix,vector-method}
+\title{Finds genes that have similar patterns of expression.}
+\description{
+  Given an \code{ExpressionSet} or a \code{matrix} of gene expressions, and the
+  indices of the genes of interest, \code{genefinder} returns a \code{list} of the
+  \code{numResults} closest genes.
+  The user can specify one of the standard distance measures listed
+  below.
+  The number of values to return can be specified. The return value is a
+  \code{list} with two components:
+  genes (measured through the desired distance method) to the genes
+  of interest (where X is the number of desired results returned) and
+  their distances.
+}
+\usage{
+genefinder(X, ilist, numResults=25, scale="none", weights, method="euclidean")
+}
+\arguments{
+  \item{X}{A numeric \code{matrix} where columns represent patients and rows
+    represent genes.}
+  \item{ilist}{A \code{vector} of genes of interest. Contains indices of genes
+    in matrix X.}
+  \item{numResults}{Number of results to display, starting from the least
+    distance to the greatest.}
+  \item{scale}{One of "none", "range", or "zscore". Scaling
+    is carried out separately on each row.}
+  \item{weights}{A vector of weights applied across the columns of
+    \code{X}. If no weights are supplied, no weights are applied.}
+  \item{method}{One of "euclidean", "maximum", "manhattan", "canberra", 
+        "correlation", "binary".}
+}
+\details{
+  If the \code{scale} option is "range", then the input matrix is scaled using
+  \code{genescale()}. If it is "zscore", then the input matrix is scaled using
+  the \code{scale} builtin with no arguments.
+
+  The method option specifies the metric used for gene comparisons. The
+  metric is applied, row by row, for each gene specified in \code{ilist}.
+
+  The "correlation" option for the distance method will return a value
+  equal to 1-correlation(x).
+
+  See \code{\link{dist}} for a more detailed description of the distances.
+}
+\value{
+  The returned value is a \code{list} containing an entry for each gene
+  specified in \code{ilist}. Each \code{list} entry contains an array of
+  distances for that gene of interest.
+}
+\author{J. Gentry and M. Kajen}
+\seealso{\code{\link{genescale}}}
+\examples{
+set.seed(12345)
+
+#create some fake expression profiles
+m1 <- matrix (1:12, 4, 3)
+v1 <- 1
+nr <- 2
+
+#find the 2 rows of m1 that are closest to row 1
+genefinder (m1, v1, nr, method="euc")
+
+v2 <- c(1,3)
+genefinder (m1, v2, nr)
+
+genefinder (m1, v2, nr, scale="range")
+
+genefinder (m1, v2, nr, method="manhattan")
+
+m2 <- matrix (rnorm(100), 10, 10)
+v3 <- c(2, 5, 6, 8)
+nr2 <- 6
+genefinder (m2, v3, nr2, scale="zscore")
+
+\testonly{
+	m1 <- matrix(rnorm(1000),100,10)
+	v1 <- c(3,5,8,42)
+	nr2 <- 35
+	genefinder(m1,v1,nr2,method="euclidean")
+	genefinder(m1,v1,nr2,method="maximum")
+	genefinder(m1,v1,nr2,method="canberra")
+	genefinder(m1,v1,nr2,method="binary")
+	genefinder(m1,v1,nr2,method="correlation")
+	
+	m2 <- matrix(rnorm(10000),1000,10)
+	v1 <- c(1,100,563,872,921,3,52,95,235,333)
+	nr <- 100
+	genefinder(m2,v1,nr2,scale="zscore",method="euclidean")
+	genefinder(m2,v1,nr2,scale="range",method="maximum")
+	genefinder(m2,v1,nr2,scale="zscore",method="canberra")
+	genefinder(m2,v1,nr2,scale="range",method="binary")
+	genefinder(m2,v1,nr2,scale="zscore",method="correlation")
+	}
+}
+\keyword{manip}
diff --git a/man/genescale.Rd b/man/genescale.Rd
new file mode 100644
index 0000000..5464a3c
--- /dev/null
+++ b/man/genescale.Rd
@@ -0,0 +1,42 @@
+\name{genescale}
+\alias{genescale}
+\title{Scales a matrix or vector.}
+\description{
+  \code{genescale} returns a scaled version of the input matrix m by applying
+  the following formula to each column of the matrix:
+     \deqn{y[i] = ( x[i] - min(x) ) / ( max(x) - min(x) )}
+}
+\usage{
+genescale(m, axis=2, method=c("Z", "R"), na.rm=TRUE)
+}
+
+\arguments{
+  \item{m}{Input a matrix or a vector with numeric elements. }
+  \item{axis}{An integer indicating which axis of \code{m} to scale.}
+  \item{method}{Either "Z" or "R", indicating whether a Z scaling or a
+    range scaling should be performed.}
+  \item{na.rm}{A boolean indicating whether \code{NA}'s should be
+    removed.}
+}
+\details{
+  Either the rows or columns of \code{m} are scaled. This is done either
+  by subtracting the mean and dividing by the standard deviation ("Z")
+  or by subtracing the minimum and dividing by the range.
+}
+\value{
+  A scaled version of the input.
+  If \code{m} is a \code{matrix} or a \code{dataframe} then the
+  dimensions of the returned value agree with that of \code{m},
+  in both cases the returned value is a \code{matrix}.
+}
+
+\author{ R. Gentleman }
+
+\seealso{ \code{\link{genefinder}},\code{\link{scale}} }
+
+\examples{
+  m <- matrix(1:12, 4, 3)
+  genescale(m)
+}
+\keyword{ manip }
+
diff --git a/man/half.range.mode.Rd b/man/half.range.mode.Rd
new file mode 100755
index 0000000..9a37c17
--- /dev/null
+++ b/man/half.range.mode.Rd
@@ -0,0 +1,105 @@
+\name{half.range.mode}
+\alias{half.range.mode}
+\title{Mode estimation for continuous data}
+
+\description{
+  For data assumed to be drawn from a unimodal, continuous distribution,
+  the mode is estimated by the \dQuote{half-range} method. Bootstrap resampling
+  for variance reduction may optionally be used.
+}
+
+\usage{
+half.range.mode(data, B, B.sample, beta = 0.5, diag = FALSE)
+}
+
+\arguments{
+  \item{data}{A numeric vector of data from which to estimate the mode.}
+  \item{B}{
+    Optionally, the number of bootstrap resampling rounds to use. Note
+    that \code{B = 1} resamples 1 time, whereas omitting \code{B}
+    uses \code{data} as is, without resampling.
+  }
+  \item{B.sample}{
+    If bootstrap resampling is requested, the size of the bootstrap
+    samples drawn from \code{data}. Default is to use a sample which is
+    the same size as \code{data}. For large data sets, this may be slow
+    and unnecessary.
+  }
+  \item{beta}{
+    The fraction of the remaining range to use at each iteration.
+  }
+  \item{diag}{
+    Print extensive diagnostics. For internal testing only... best left
+    \code{FALSE}.
+  }
+}
+
+\details{
+  Briefly, the mode estimator is computed by iteratively identifying
+  densest half ranges. (Other fractions of the current range can be
+  requested by setting \code{beta} to something other than 0.5.) A densest half
+  range is an interval whose width equals half the current range, and
+  which contains the maximal number of observations. The subset of
+  observations falling in the selected densest half range is then used to compute
+  a new range, and the procedure is iterated. See the references for
+  details.
+
+  If bootstrapping is requested, \code{B} half-range mode estimates are
+  computed for \code{B} bootstrap samples, and their average is returned
+  as the final estimate.
+}
+
+\value{
+  The mode estimate.
+}
+
+\references{
+  \itemize{
+    \item DR Bickel, \dQuote{Robust estimators of the mode and skewness of
+    continuous data.} \emph{Computational Statistics & Data Analysis}
+    39:153-163 (2002).
+
+    \item SB Hedges and P Shah, \dQuote{Comparison of
+    mode estimation methods and application in molecular clock analysis.} \emph{BMC
+    Bioinformatics} 4:31-41 (2003).
+  }
+}
+
+\author{Richard Bourgon <bourgon at stat.berkeley.edu>}
+\seealso{\code{\link{shorth}}}
+\keyword{univar}
+\keyword{robust}
+
+\examples{
+## A single normal-mixture data set
+
+x <- c( rnorm(10000), rnorm(2000, mean = 3) )
+M <- half.range.mode( x )
+M.bs <- half.range.mode( x, B = 100 )
+
+if(interactive()){
+hist( x, breaks = 40 )
+abline( v = c( M, M.bs ), col = "red", lty = 1:2 )
+legend(
+       1.5, par("usr")[4],
+       c( "Half-range mode", "With bootstrapping (B = 100)" ),
+       lwd = 1, lty = 1:2, cex = .8, col = "red"
+       )
+}
+
+# Sampling distribution, with and without bootstrapping
+
+X <- rbind(
+           matrix( rnorm(1000 * 100), ncol = 100 ),
+           matrix( rnorm(200 * 100, mean = 3), ncol = 100 )
+           )
+M.list <- list(
+               Simple = apply( X, 2, half.range.mode ),
+               BS = apply( X, 2, half.range.mode, B = 100 )
+               )
+
+if(interactive()){
+boxplot( M.list, main = "Effect of bootstrapping" )
+abline( h = 0, col = "red" )
+}
+}
diff --git a/man/kOverA.Rd b/man/kOverA.Rd
new file mode 100644
index 0000000..b4c15d3
--- /dev/null
+++ b/man/kOverA.Rd
@@ -0,0 +1,31 @@
+\name{kOverA}
+\alias{kOverA}
+\title{A filter function for k elements larger than A. }
+\description{
+  \code{kOverA} returns a filter function with bindings for \code{k} and
+  \code{A}. This function evaluates to \code{TRUE} if at least \code{k}
+  of the arguments elements are larger than \code{A}.
+}
+\usage{
+kOverA(k, A=100, na.rm=TRUE)
+}
+\arguments{
+  \item{A}{The value you want to exceed. }
+  \item{k}{The number of elements that have to exceed A.}
+  \item{na.rm}{If set to \code{TRUE} any \code{NA}'s will be removed. }
+}
+
+\value{
+ A function with bindings for \code{A} and \code{k}.
+}
+
+\author{R. Gentleman}
+
+\seealso{\code{\link{pOverA}}}
+
+\examples{
+   fg <- kOverA(5, 100)
+   fg(90:100)
+   fg(98:110)
+}
+\keyword{manip}
diff --git a/man/kappa_p.Rd b/man/kappa_p.Rd
new file mode 100644
index 0000000..00b8f11
--- /dev/null
+++ b/man/kappa_p.Rd
@@ -0,0 +1,42 @@
+\name{kappa_p}
+
+\Rdversion{1.1}
+
+\alias{kappa_p}
+\alias{kappa_t}
+
+\title{
+  Compute proportionality constant for fold change bound.
+}
+
+\description{
+  Filtering on overall variance induces a lower bound on fold
+  change. This bound depends on the significance of the evidence against
+  the null hypothesis, an is a multiple of the cutoff used for an
+  overall variance filter. It also depends on sample size in both of the
+  groups being compared. These functions compute the multiplier for the
+  supplied p-values or t-statistics.
+}
+
+\usage{
+kappa_p(p, n1, n2 = n1)
+kappa_t(t, n1, n2 = n1)
+}
+
+\arguments{
+  \item{p}{The p-values at which to compute the multiplier.}
+  \item{t}{The t-statistics at which to compute the multiplier.}
+  \item{n1}{Sample size for class 1.}
+  \item{n2}{Sample size for class 2.}
+}
+
+\value{
+  A vector of multipliers: one per p-value or t-static in
+  \code{p} or \code{t}.
+}
+
+\author{Richard Bourgon <bourgon at ebi.ac.uk>}
+
+\examples{
+# See the vignette: Diagnostic plots for independent filtering
+}
diff --git a/man/maxA.Rd b/man/maxA.Rd
new file mode 100644
index 0000000..5729938
--- /dev/null
+++ b/man/maxA.Rd
@@ -0,0 +1,33 @@
+\name{maxA}
+\alias{maxA}
+\title{ A filter function to filter according to the maximum. }
+\description{
+  \code{maxA} returns a function with the parameter \code{A} bound.
+  The returned function evaluates to \code{TRUE} if any element of its
+  argument is larger than \code{A}.
+}
+\usage{
+maxA(A=75, na.rm=TRUE)
+}
+\arguments{
+  \item{A}{The value that at least one element must exceed. }
+  \item{na.rm}{If \code{TRUE} then \code{NA}'s are removed. }
+}
+
+\value{
+ \code{maxA} returns a function with an environment containing a binding
+ for \code{A}.
+ 
+}
+
+\author{R. Gentleman }
+
+\seealso{\code{\link{pOverA}} }
+
+\examples{
+   ff <- maxA(30)
+   ff(1:10)
+   ff(28:31)
+}
+\keyword{manip}
+
diff --git a/man/nsFilter.Rd b/man/nsFilter.Rd
new file mode 100644
index 0000000..16e169f
--- /dev/null
+++ b/man/nsFilter.Rd
@@ -0,0 +1,206 @@
+\name{nsFilter}
+
+\alias{nsFilter}
+\alias{varFilter}
+\alias{featureFilter}
+\alias{nsFilter,ExpressionSet-method}
+
+\title{Filtering of Features in an ExpressionSet}
+
+\description{The function \code{nsFilter} tries to provide a one-stop shop for
+  different options of filtering (removing) features from an ExpressionSet. 
+  Filtering features exhibiting little variation, or a consistently low
+  signal, across samples can be advantageous for
+  the subsequent data analysis (Bourgon et al.).
+  Furthermore, one may decide that there is little value in considering
+  features with insufficient annotation.
+}
+
+\usage{
+nsFilter(eset, require.entrez=TRUE,
+    require.GOBP=FALSE, require.GOCC=FALSE,
+    require.GOMF=FALSE, require.CytoBand=FALSE,
+    remove.dupEntrez=TRUE, var.func=IQR,
+    var.cutoff=0.5, var.filter=TRUE,
+    filterByQuantile=TRUE, feature.exclude="^AFFX", ...)
+
+varFilter(eset, var.func=IQR, var.cutoff=0.5, filterByQuantile=TRUE)
+
+featureFilter(eset, require.entrez=TRUE,
+    require.GOBP=FALSE, require.GOCC=FALSE,
+    require.GOMF=FALSE, require.CytoBand=FALSE,
+    remove.dupEntrez=TRUE, feature.exclude="^AFFX")
+}
+
+\arguments{
+  \item{eset}{an \code{ExpressionSet} object}
+  \item{var.func}{The function used as the per-feature filtering
+    statistic. This function should return a numeric vector of length
+    one when given a numeric vector as input.}
+  \item{var.filter}{A logical indicating whether to perform
+      filtering based on \code{var.func}.}  
+  \item{filterByQuantile}{A logical indicating whether \code{var.cutoff}
+    is to be interprested as a quantile of all \code{var.func} values
+    (the default), or as an absolute value.}
+  \item{var.cutoff}{A numeric value. If \code{var.filter} is TRUE,
+    features whose value of \code{var.func} is less than either:
+    the \code{var.cutoff}-quantile of all \code{var.func} values
+    (if \code{filterByQuantile} is TRUE), or
+    \code{var.cutoff} (if \code{filterByQuantile} is FALSE)
+    will be removed.}
+  \item{require.entrez}{If \code{TRUE}, filter out features
+    without an Entrez Gene ID annotation. If using an annotation
+    package where an identifier system other than Entrez Gene IDs is
+    used as the central ID, then that ID will be required instead.}
+  \item{require.GOBP, require.GOCC, require.GOMF}{If \code{TRUE}, filter out features
+    whose target genes are not annotated to at least one GO term in
+    the BP, CC or MF ontology, respectively.}
+  \item{require.CytoBand}{If \code{TRUE}, filter out features
+    whose target genes have no mapping to cytoband locations.} 
+  \item{remove.dupEntrez}{If \code{TRUE} and there are features
+      mapping to the same Entrez Gene ID (or equivalent), then the feature with
+      the largest value of \code{var.func} will be retained and the
+      other(s) removed.}
+  \item{feature.exclude}{A character vector of regular expressions.
+    Feature identifiers (i.e. value of \code{featureNames(eset)})
+    that match one of the specified patterns will be filtered out.
+    The default value is intended to filter out Affymetrix quality control
+    probe sets.}
+  \item{...}{Unused, but available for specializing methods.}
+}
+\details{
+  In this Section, the effect of filtering on the type I error rate
+  estimation / control of subsequent hypothesis testing is explained.
+  See also the paper by Bourgon et al.
+  
+  \emph{Marginal type I errors}:
+  Filtering on the basis of a statistic which is independent of the test
+  statistic used for detecting differential gene expression can increase
+  the detection rate at the same marginal type I error. This is
+  clearly the case for filter criteria that do not depend on the data,
+  such as the annotation based criteria provided by the \code{nsFilter}
+  and \code{featureFilter} functions. However, marginal type I error can
+  also be controlled for certain types of data-dependent criteria.
+  Call \eqn{U^I}{U^1} the stage 1 filter statistic, which is a function
+  that is applied feature by feature,
+  based on whose value the feature is or is not accepted to
+  pass to stage 2, and which depends only on the data for that feature
+  and not any other feature, and call
+  \eqn{U^{II}}{U^2} the stage 2 test statistic for differential expression.
+  Sufficient conditions for marginal type-I error control are:
+  \itemize{
+    
+    \item \eqn{U^I}{U^1} the overall (across all samples) variance or
+    mean, 
+    \eqn{U^{II}}{U^2} the t-statistic (or any other scale and location
+    invariant statistic),
+    data normal distributed and exchangeable across samples.
+
+    \item \eqn{U^I}{U^1} the overall mean, 
+    \eqn{U^{II}}{U^2} the moderated t-statistic
+    (as in limma's \code{\link[limma:ebayes]{eBayes}} function),
+    data normal distributed and exchangeable.
+    
+    \item \eqn{U^I}{U^1} a sample-class label independent function
+    (e.g. overall mean, median, variance, IQR),
+    \eqn{U^{II}}{U^2} the Wilcoxon rank sum statistic,
+    data exchangeable.
+  }
+
+  \emph{Experiment-wide type I error}:
+  Marginal type-I error control provided by the conditions above
+  is sufficient for control of the family wise error rate (FWER).
+  Note, however, that common false discovery rate (FDR) methods depend 
+  not only on the marginal behaviour of the test statistics under the
+  null hypothesis, but also on their joint distribution.
+  The joint distribution can be affected by filtering,
+  even when this filtering leaves the marginal distributions of 
+  true-null test statistics unchanged. Filtering might, for example, 
+  change correlation structure. The
+  effect of this is negligible in many cases in practice, but this
+  depends on the dataset and the filter used, and the assessment 
+  is in the responsibility of the data analyst.
+  
+  \emph{Annotation Based Filtering} Arguments \code{require.entrez},
+  \code{require.GOBP}, \code{require.GOCC}, \code{require.GOMF} and
+  \code{require.CytoBand}
+  filter based on available annotation data.  The annotation
+  package is determined by calling \code{annotation(eset)}.
+
+  \emph{Variance Based Filtering} The \code{var.filter},
+  \code{var.func}, \code{var.cutoff} and \code{varByQuantile} arguments
+  control numerical cutoff-based filtering.
+  Probes for which \code{var.func} returns \code{NA} are
+  removed.
+  The default \code{var.func} is \code{IQR}, which we here define as
+  \code{rowQ(eset, ceiling(0.75 * ncol(eset))) - rowQ(eset, floor(0.25 * ncol(eset)))};
+  this choice is motivated by the observation that unexpressed genes are
+  detected most reliably through low variability of their features
+  across samples.
+  Additionally, \code{IQR} is robust to outliers (see note below). The
+  default \code{var.cutoff} is \code{0.5} and is motivated by a rule of
+  thumb that in many tissues only 40\% of genes are expressed.
+  Please adapt this value to your data and question.
+
+  By default the numerical-filter cutoff is interpreted
+  as a quantile, so with the default settings, 
+  50\% of the genes are filtered. 
+
+  Variance filtering is performed last, so that
+  (if \code{varByQuantile=TRUE} and \code{remove.dupEntrez=TRUE}) the
+  final number of genes does indeed exclude precisely the \code{var.cutoff} 
+  fraction of unique genes remaining after all other filters were
+  passed.
+  
+  The stand-alone function \code{varFilter} does only
+  \code{var.func}-based filtering
+  (and no annotation based filtering).
+  \code{featureFilter} does only
+  annotation based filtering and duplicate removal; it always
+  performs duplicate removal to retain the highest-IQR
+  probe for each gene.
+}
+
+\value{
+  For \code{nsFilter} a list consisting of:
+  \item{eset}{the filtered \code{ExpressionSet}}
+  \item{filter.log}{a list giving details of how many probe sets where
+    removed for each filtering step performed.}
+
+  For both \code{varFilter} and \code{featureFilter} the filtered
+  \code{ExpressionSet}.
+}
+
+\author{Seth Falcon (somewhat revised by Assaf Oron)}
+
+\note{\code{IQR} is a reasonable variance-filter choice when the dataset
+  is split into two roughly equal and relatively homogeneous phenotype
+  groups. If your dataset has important groups smaller than 25\% of the
+  overall sample size, or if you are interested in unusual
+  individual-level patterns, then \code{IQR} may not be sensitive enough
+  for your needs. In such cases, you should consider using less robust
+  and more sensitive measures of variance (the simplest of which would
+  be \code{sd}).}
+
+\references{
+  R. Bourgon, R. Gentleman, W. Huber,
+  Independent filtering increases power for detecting differentially
+  expressed genes, Technical Report.
+}
+
+\examples{
+  library("hgu95av2.db")
+  library("Biobase")
+  data(sample.ExpressionSet)
+  ans <- nsFilter(sample.ExpressionSet)
+  ans$eset
+  ans$filter.log
+
+  ## skip variance-based filtering
+  ans <- nsFilter(sample.ExpressionSet, var.filter=FALSE)
+
+  a1 <- varFilter(sample.ExpressionSet)
+  a2 <- featureFilter(sample.ExpressionSet)
+}
+
+\keyword{manip}
diff --git a/man/pOverA.Rd b/man/pOverA.Rd
new file mode 100644
index 0000000..38590d8
--- /dev/null
+++ b/man/pOverA.Rd
@@ -0,0 +1,39 @@
+\name{pOverA}
+\alias{pOverA}
+
+\title{A filter function to filter according to the proportion of
+  elements larger than A. }
+\description{
+  A function that returns a function with values for \code{A}, \code{p}
+  and \code{na.rm} bound to the specified values. The function takes a
+  single vector, \code{x}, as an argument.
+  When the returned function is evaluated it returns \code{TRUE} if the
+  proportion of values in \code{x} that are larger than \code{A} is at
+  least \code{p}. 
+}
+\usage{
+pOverA(p=0.05, A=100, na.rm=TRUE)
+}
+\arguments{
+  \item{A}{The value to be exceeded. }
+  \item{p}{The proportion that need to exceed \code{A} for \code{TRUE}
+    to be returned. }
+  \item{na.rm}{ If \code{TRUE} then \code{NA}'s are removed. }
+}
+
+\value{
+ \code{pOverA} returns a function with bindings for \code{A}, \code{p}
+ and \code{na.rm}. This function evaluates to \code{TRUE} if the
+  proportion of values in \code{x} that are larger than \code{A} exceeds
+  \code{p}. 
+}
+\author{R. Gentleman}
+
+\seealso{  \code{\link{cv}} }
+
+\examples{
+  ff<- pOverA(p=.1, 10)
+  ff(1:20)
+  ff(1:5)
+}
+\keyword{manip}
diff --git a/man/rejection_plot.Rd b/man/rejection_plot.Rd
new file mode 100644
index 0000000..e2f6101
--- /dev/null
+++ b/man/rejection_plot.Rd
@@ -0,0 +1,111 @@
+\name{rejection_plot}
+
+\Rdversion{1.1}
+
+\alias{rejection_plot}
+
+\title{
+  Plot rejections vs. p-value cutoff
+}
+
+\description{
+  Plot the number, or fraction, of null hypotheses rejected as a
+  function of the p-value cutoff. Multiple sets of p-values are
+  accepted, in a list or in the columns of a matrix, in order to permit
+  comparisons. 
+}
+
+\usage{
+rejection_plot(p,
+               col, lty = 1, lwd = 1,   
+               xlab = "p cutoff", ylab = "number of rejections",
+               xlim = c(0, 1), ylim,
+               legend = names(p),
+               at = c("all", "sample"),
+               n_at = 100,
+               probability = FALSE,
+               ...
+               )
+}
+
+\arguments{
+  
+  \item{p}{
+    The p-values to be used for plotting. These may be in the columns of
+    a matrix, or in the elements of a list. One curve will be generated
+    for each column/element, and all \code{NA} entries will be
+    dropped. If column or element names are supplied, they are used by
+    default for a plot legend.
+  }
+
+  \item{col}{
+    Colors to be used for each curve plotted. Recycled if necessary. If
+    \code{col} is omitted, \code{\link{rainbow}} is used to generate a
+    set of colors.
+  }
+  
+  \item{lty}{
+    Line styles to be used for each curve plotted. Recycled if necessary.
+  }
+  
+  \item{lwd}{
+    Line widths to be used for each curve plotted. Recycled if necessary.
+  }
+  
+  \item{xlab}{
+    X-axis text label.
+  }
+  
+  \item{ylab}{
+    Y-axis text label.
+  }
+  
+  \item{xlim}{
+    X-axis limits.
+  }
+  
+  \item{ylim}{
+    Y-axis limits.
+  }
+  
+  \item{legend}{
+    Text for legend. Matrix column names or list element names (see
+    \code{p} above) are used by default. If \code{NULL}, no legend is
+    plotted.
+  }
+  
+  \item{at}{
+    Should step functions be plotted with a step at every value in
+    \code{p}, or should linear interpolation be used at a sample of
+    points spanning \code{xlim}? The latter looks when there are many
+    p-values.
+  }
+  
+  \item{n_at}{
+    When \code{at = "sample"} is given, how many sample points should be
+    used for interpolation and plotting?
+  }
+  
+  \item{probability}{
+    Should the fraction of null hypotheses rejected be reported instead
+    of the count? See the \code{probability} argument to
+    \code{\link{hist}}. 
+  }
+  
+  \item{\dots}{
+    Other arguments to pass to the \code{\link{plot}} call which sets up
+    the axes. Note that the \code{...} argument will not be passed to
+    the \code{\link{lines}} calls which actually generate the curves.
+  }
+  
+}
+
+\value{
+  A list of the step functions used for plotting is returned invisibly.
+}
+
+\author{Richard Bourgon <bourgon at ebi.ac.uk>}
+
+\examples{
+# See the vignette: Diagnostic plots for independent filtering
+}
diff --git a/man/rowFtests.Rd b/man/rowFtests.Rd
new file mode 100644
index 0000000..0bbb462
--- /dev/null
+++ b/man/rowFtests.Rd
@@ -0,0 +1,188 @@
+\name{rowFtests}
+\alias{rowFtests}
+\alias{rowFtests,matrix,factor-method}
+\alias{rowFtests,ExpressionSet,factor-method}
+\alias{rowFtests,ExpressionSet,character-method}
+
+\alias{colFtests}
+\alias{colFtests,matrix,factor-method}
+\alias{colFtests,ExpressionSet,factor-method}
+\alias{colFtests,ExpressionSet,character-method}
+
+\alias{rowttests}
+\alias{rowttests,matrix,factor-method}
+\alias{rowttests,matrix,missing-method}
+\alias{rowttests,ExpressionSet,factor-method}
+\alias{rowttests,ExpressionSet,character-method}
+\alias{rowttests,ExpressionSet,missing-method}
+
+\alias{colttests}
+\alias{colttests,matrix,factor-method}
+\alias{colttests,matrix,missing-method}
+\alias{colttests,ExpressionSet,factor-method}
+\alias{colttests,ExpressionSet,character-method}
+\alias{colttests,ExpressionSet,missing-method}
+
+\alias{fastT}
+
+\title{t-tests and F-tests for rows or columns of a matrix}
+\description{t-tests and F-tests for rows or columns of a
+  matrix, intended to be speed efficient.}
+\usage{
+rowttests(x, fac, tstatOnly = FALSE) 
+colttests(x, fac, tstatOnly = FALSE)
+fastT(x, ig1, ig2, var.equal = TRUE)
+
+rowFtests(x, fac, var.equal = TRUE)
+colFtests(x, fac, var.equal = TRUE)
+}
+\arguments{
+  \item{x}{Numeric matrix. The matrix must not contain \code{NA} values.
+    For \code{rowttests} and \code{colttests}, \code{x} can also be an
+    \code{\link[Biobase:class.ExpressionSet]{ExpressionSet}}.}
+
+  \item{fac}{Factor which codes the grouping to be tested.
+    There must be 1 or 2 groups for the t-tests (corresponding to one-
+    and two-sample t-test), and 2 or more for the F-tests. If \code{fac}
+    is missing, this is taken as a one-group test (i.e. is only allowed
+    for the t-tests). The length
+    of the factor needs to correspond to the sample size:
+    for the \code{row*} functions, the length of the factor must be
+    the same as the number of columns of \code{x},
+    for the \code{col*} functions, it must be the same as the number
+    of rows of \code{x}.
+
+    If \code{x} is an
+    \code{\link[Biobase:class.ExpressionSet]{ExpressionSet}}, then 
+    \code{fac} may also be a character vector of length 1 with the
+    name of a covariate in \code{x}.}
+
+  \item{tstatOnly}{A logical variable indicating whether to calculate
+    p-values from the t-distribution with appropriate degrees of
+    freedom. If \code{TRUE}, just the t-statistics are
+    returned. This can be considerably faster.}
+
+  \item{ig1}{The indices of the columns of \code{x} that correspond
+    to group 1.}
+  \item{ig2}{The indices of the columns of \code{x} that correspond
+    to group 2.}
+
+  \item{var.equal}{A logical variable indicating whether to treat the
+    variances in the samples as equal.  If 'TRUE', a simple F test for
+    the equality of means in a one-way analysis of variance is
+    performed.  If 'FALSE', an approximate method of Welch (1951) is
+    used, which generalizes the commonly known 2-sample Welch test to
+    the case of arbitrarily many samples.}
+}
+
+\details{
+  If \code{fac} is specified, \code{rowttests} performs for each
+  row of \code{x} a two-sided, two-class t-test with equal variances.
+  \code{fac} must be a factor of length \code{ncol(x)} with two levels,
+  corresponding to the two groups. The sign of the resulting t-statistic
+  corresponds to "group 1 minus group 2".
+  If \code{fac} is missing, \code{rowttests} performs for each row of
+  \code{x} a two-sided one-class t-test against the null hypothesis 'mean=0'.
+  
+  \code{rowttests} and \code{colttests} are implemented in C and
+  should be reasonably fast and memory-efficient.
+  \code{fastT} is an alternative implementation, in Fortran, possibly useful
+  for certain legacy code.
+  \code{rowFtests} and \code{colFtests} are currently implemented using
+  matrix algebra in R. Compared to the \code{rowttests} and
+  \code{colttests} functions,
+  they are slower and use more memory.
+}
+
+\value{
+  A \code{data.frame} with columns \code{statistic},
+  \code{p.value} (optional in the case of the t-test functions) and
+  \code{dm}, the difference of the group means (only in the
+  case of the t-test functions).
+  The \code{row.names} of the data.frame are taken from the
+  corresponding dimension names of \code{x}.
+  
+  The degrees of freedom are provided in the attribute \code{df}.
+  For the F-tests, if \code{var.equal} is 'FALSE', \code{nrow(x)+1}
+  degree of freedoms 
+  are given, the first one is the first degree of freedom (it is the
+  same for each row) and the other ones are the second degree of freedom
+  (one for each row). 
+}
+\references{B. L. Welch (1951), On the comparison of several mean values: an
+     alternative approach. Biometrika, *38*, 330-336}
+\author{Wolfgang Huber <whuber at embl.de>}
+\seealso{\code{\link[multtest:mt.teststat]{mt.teststat}}}
+\examples{
+   ##
+   ## example data
+   ##
+   x  = matrix(runif(40), nrow=4, ncol=10)
+   f2 = factor(floor(runif(ncol(x))*2))
+   f4 = factor(floor(runif(ncol(x))*4))
+
+   ##
+   ## one- and two group row t-test; 4-group F-test
+   ##
+   r1 = rowttests(x)
+   r2 = rowttests(x, f2)
+   r4 = rowFtests(x, f4)
+
+   ## approximate equality
+   about.equal = function(x,y,tol=1e-10)
+     stopifnot(is.numeric(x), is.numeric(y), length(x)==length(y), all(abs(x-y) < tol))
+
+   ##
+   ## compare with the implementation in t.test
+   ##
+   for (j in 1:nrow(x)) {
+     s1 = t.test(x[j,])
+     about.equal(s1$statistic, r1$statistic[j])
+     about.equal(s1$p.value,   r1$p.value[j])
+
+     s2 = t.test(x[j,] ~ f2, var.equal=TRUE)
+     about.equal(s2$statistic, r2$statistic[j])
+     about.equal(s2$p.value,   r2$p.value[j])
+
+     dm = -diff(tapply(x[j,], f2, mean))
+     about.equal(dm, r2$dm[j])
+
+     s4 = summary(lm(x[j,] ~ f4))
+     about.equal(s4$fstatistic["value"], r4$statistic[j])
+   }
+
+   ##
+   ## colttests
+   ##
+   c2 = colttests(t(x), f2)
+   stopifnot(identical(r2, c2))
+
+   ##
+   ## missing values
+   ##
+   f2n = f2
+   f2n[sample(length(f2n), 3)] = NA
+   r2n = rowttests(x, f2n)
+   for(j in 1:nrow(x)) {
+     s2n = t.test(x[j,] ~ f2n, var.equal=TRUE)
+     about.equal(s2n$statistic, r2n$statistic[j])
+     about.equal(s2n$p.value,   r2n$p.value[j])
+   }
+
+   ##
+   ## larger sample size
+   ##
+   x  = matrix(runif(1000000), nrow=4, ncol=250000)
+   f2 = factor(floor(runif(ncol(x))*2))
+   r2 = rowttests(x, f2) 
+   for (j in 1:nrow(x)) {
+     s2 = t.test(x[j,] ~ f2, var.equal=TRUE)
+     about.equal(s2$statistic, r2$statistic[j])
+     about.equal(s2$p.value,   r2$p.value[j])
+   }
+
+   ## single row matrix
+   rowFtests(matrix(runif(10),1,10),as.factor(c(rep(1,5),rep(2,5))))
+   rowttests(matrix(runif(10),1,10),as.factor(c(rep(1,5),rep(2,5))))
+}
+\keyword{math}
diff --git a/man/rowROC-class.Rd b/man/rowROC-class.Rd
new file mode 100644
index 0000000..4c1bd51
--- /dev/null
+++ b/man/rowROC-class.Rd
@@ -0,0 +1,103 @@
+\name{rowROC-class}
+\docType{class}
+\alias{rowROC}
+\alias{rowROC-class}
+\alias{pAUC}
+\alias{AUC}
+\alias{sens}
+\alias{spec}
+\alias{area}
+\alias{pAUC,rowROC,numeric-method}
+\alias{plot,rowROC,missing-method}
+\alias{AUC,rowROC-method}
+\alias{spec,rowROC-method}
+\alias{sens,rowROC-method}
+\alias{area,rowROC-method}
+\alias{show,rowROC-method}
+\alias{[,rowROC-method}
+
+
+\title{Class "rowROC"}
+\description{A class to model ROC curves and corresponding area under
+  the curve as produced by rowpAUCs.}
+\section{Objects from the Class}{
+Objects can be created by calls of the form \code{new("rowROC", ...)}.
+}
+\section{Slots}{
+	 \describe{
+    \item{\code{data}:}{Object of class \code{"matrix"} The input data.}
+    \item{\code{ranks}:}{Object of class \code{"matrix"} The ranked
+      input data. }
+    \item{\code{sens}:}{Object of class \code{"matrix"} Matrix of
+      senitivity values for each gene at each cutpoint. }
+    \item{\code{spec}:}{Object of class \code{"matrix"} Matrix of
+      specificity values for each gene at each cutpoint.}
+    \item{\code{pAUC}:}{Object of class \code{"numeric"} The partial
+      area under the curve (integrated from 0 to \code{p}. }
+    \item{\code{AUC}:}{Object of class \code{"numeric"} The total area
+      under the curve. }
+    \item{\code{factor}:}{Object of class \code{"factor"} The factor
+      used for classification.}
+    \item{\code{cutpoints}:}{Object of class \code{"matrix"} The values
+      of the cutpoints at which specificity ans sensitivity was
+calculated. (Note: the data is ranked prior to computation
+      of ROC curves, the cutpoints map to the ranked data.}
+    \item{\code{caseNames}:}{Object of class \code{"character"} The
+      names of the two classification cases.}
+    \item{\code{p}:}{Object of class \code{"numeric"} The limit to which
+\code{pAUC} is integrated. }
+  }
+}
+\section{Methods}{
+  \describe{
+    \item{show \code{signature(object="rowROC")}}{Print nice info
+      about the object.}
+     \item{[ \code{signature(x="rowROC", j="missing")}}{Subset the
+       object according to rows/genes.}
+     \item{plot \code{signature(x="rowROC", y="missing")}}{Plot the ROC
+       curve of the first row of the object along with the \code{pAUC}.
+       To plot the curve for a specific row/gene subsetting should be done
+       first (i.e. \code{plot(rowROC[1])}.}
+    \item{pAUC \code{signature(object="rowROC", p="numeric", flip="logical")}}{Integrate
+      area under the curve from \code{0} to \code{p}. This method
+      returns a new \code{rowROC} object.}
+    \item{AUC \code{signature(object="rowROC")}}{Integrate
+      total area under the curve. This method returns a new
+      \code{rowROC} object.}
+    \item{sens \code{signature(object="rowROC")}}{Accessor method for
+      sensitivity slot.}
+    \item{spec \code{signature(object="rowROC")}}{Accessor method for
+      specificity slot.}
+    \item{area \code{signature(object="rowROC", total="logical")}}{Accessor method for
+       pAUC slot.}
+  }
+}
+\references{Pepe MS, Longton G, Anderson GL,
+Schummer M.: Selecting
+differentially expressed genes from microarray
+experiments. \emph{Biometrics. 2003 Mar;59(1):133-42.}}
+\author{Florian Hahne <fhahne at fhcrc.org>}
+
+
+\seealso{
+  \code{\link[genefilter:rowpAUCs]{rowpAUCs}}
+}
+\examples{
+library(Biobase)
+require(genefilter)
+data(sample.ExpressionSet)
+roc <- rowpAUCs(sample.ExpressionSet, "sex", p=0.5)
+roc
+area(roc[1:3])
+
+if(interactive()) {
+par(ask=TRUE)
+plot(roc)
+plot(1-spec(roc[1]), sens(roc[2]))
+par(ask=FALSE)
+}
+
+pAUC(roc, 0.1)
+roc
+}
+\keyword{classes}
diff --git a/man/rowSds.Rd b/man/rowSds.Rd
new file mode 100644
index 0000000..6ba02f2
--- /dev/null
+++ b/man/rowSds.Rd
@@ -0,0 +1,37 @@
+\name{rowSds}
+\alias{rowSds}
+\alias{rowVars}
+\title{Row variance and standard deviation of a numeric array}
+\description{
+  Row  variance and standard deviation of a numeric array
+}
+\usage{
+rowVars(x, ...)
+rowSds(x, ...)
+}
+\arguments{
+  \item{x}{An array of two or more dimensions, containing numeric,
+          complex, integer or logical values, or a numeric data frame.}
+  \item{...}{Further arguments that get passed on to
+    \code{\link{rowMeans}} and \code{\link{rowSums}}.}
+}
+
+\value{
+  A numeric or complex array of suitable size, or a vector if the
+  result is one-dimensional.  The `dimnames' (or `names' for a
+  vector result) are taken from the original array.
+}
+\details{These are very simple convenience functions, the main work is done in
+  \code{\link{rowMeans}} and \code{\link{rowSums}}. See the function
+  definition of \code{rowVars}, it is very simple.
+}
+\author{Wolfgang Huber \url{http://www.ebi.ac.uk/huber}}
+\seealso{\code{\link{rowMeans}} and \code{\link{rowSums}}}
+
+\examples{
+   a = matrix(rnorm(1e4), nrow=10)
+   rowSds(a)
+}
+
+\keyword{array}
+\keyword{manip}
diff --git a/man/rowpAUCs.Rd b/man/rowpAUCs.Rd
new file mode 100644
index 0000000..0750fcf
--- /dev/null
+++ b/man/rowpAUCs.Rd
@@ -0,0 +1,133 @@
+\name{rowpAUCs-methods}
+\docType{methods}
+\alias{rowpAUCs-methods}
+\alias{rowpAUCs}
+\alias{rowpAUCs,matrix,factor-method}
+\alias{rowpAUCs,matrix,numeric-method}
+\alias{rowpAUCs,ExpressionSet,ANY-method}
+\alias{rowpAUCs,ExpressionSet,character-method}
+\title{Rowwise ROC and pAUC computation}
+\description{Methods for fast rowwise computation of ROC curves and
+  (partial) area under the curve (pAUC) using the simple classification
+  rule \code{x > theta}, where \code{theta} is a value in the range of
+  \code{x}
+}
+\usage{
+rowpAUCs(x, fac, p=0.1, flip=TRUE, caseNames=c("1", "2"))
+}
+\arguments{
+  \item{x}{\code{ExpressionSet} or numeric \code{matrix}. The
+    \code{matrix} must not contain \code{NA} values.}
+
+  \item{fac}{A \code{factor} or \code{numeric} or \code{character} that can
+    be coerced to a \code{factor}. If \code{x} is an \code{ExpressionSet},
+    this may also be a character \code{vector} of length 1 with the name of
+    a covariate variable in \code{x}. \code{fac} must have exactly 2 levels.
+    For better control over the classification, use integer values in 0 and 1,
+    where 1 indicates the "Disease" class in the sense of the Pepe et al paper
+    (see below).}
+ 
+  \item{p}{Numeric \code{vector} of length 1. Limit in (0,1) to integrate pAUC
+    to.}
+  
+  \item{flip}{Logical. If \code{TRUE}, both classification rules \code{x
+  > theta} and \code{x < theta} are tested and the (partial) area under
+  the curve of the better one of the two is returned. This is
+  appropriate for the cases in which the classification is not
+  necessarily linked to higher expression values, but instead it is
+  symmetric and one would assume both over- and under-expressed genes for
+  both classes. You can set \code{flip} to \code{FALSE} if you only want
+  to screen for genes which discriminate Disease from Control with the
+  \code{x > theta} rule.}
+
+  \item{caseNames}{The class names that are used when plotting the
+    data. If \code{fac} is the name of the covariate variable in the
+    \code{ExpressionSet} the function will use its levels as
+    \code{caseNames}.}
+}
+\details{
+  Rowwise calculation of Receiver Operating Characteristic (ROC) curves
+  and the corresponding partial area under the curve (pAUC) for a given
+  data matrix or \code{ExpressionSet}. The function is implemented in C
+  and thus reasonably fast and memory efficient. Cutpoints (\code{theta}
+  are calculated before the first, in between and after the last data
+  value. By default, both classification rules \code{x > theta} and
+  \code{x < theta} are tested and the (partial) area under the curve of
+  the better one of the two is returned. This is only valid for
+  symmetric cases, where the classification is independent of the
+  magnitude of \code{x} (e.g., both over- and under-expression of
+  different genes in the same class).  For unsymmetric cases in which
+  you expect x to be consistently higher/lower in of of the two classes
+  (e.g. presence or absence of a single biomarker) set \code{flip=FALSE}
+  or use the functionality provided in the \code{ROC} package. For
+  better control over the classification (i.e., the choice of "Disease"
+  and "Control" class in the sense of the Pepe et al paper), argument
+  \code{fac} can be an integer in \code{[0,1]} where 1 indicates
+  "Disease" and 0 indicates "Control". 
+}
+\section{Methods}{
+  \describe{
+    Methods exist for \code{rowPAUCs}:
+    \item{rowPAUCs}{\code{signature(x="matrix", fac="factor")}}
+    \item{rowPAUCs}{\code{signature(x="matrix", fac="numeric")}}
+    \item{rowPAUCs}{\code{signature(x="ExpressionSet")}}
+    \item{rowPAUCs}{\code{signature(x="ExpressionSet", fac="character")}}
+  }
+}
+\value{
+  An object of class \code{\link[genefilter:rowROC-class]{rowROC}} with the
+  calculated specificities and sensitivities for each row and the
+  corresponding pAUCs and AUCs values. See
+  \code{\link[genefilter:rowROC-class]{rowROC}} for details.
+}
+\references{Pepe MS, Longton G, Anderson GL,
+Schummer M.: Selecting
+    differentially expressed genes from microarray
+    experiments. \emph{Biometrics. 2003 Mar;59(1):133-42.}} 
+\author{Florian Hahne <fhahne at fhcrc.org>}
+\seealso{\code{\link[ROC:rocdemo.sca]{rocdemo.sca},
+    \link[ROC:AUC]{pAUC}, \link[genefilter:rowROC-class]{rowROC}}}
+\examples{
+library(Biobase)
+data(sample.ExpressionSet)
+
+r1 = rowttests(sample.ExpressionSet, "sex")
+r2 = rowpAUCs(sample.ExpressionSet, "sex", p=0.1)
+
+plot(area(r2, total=TRUE), r1$statistic, pch=16)
+sel <- which(area(r2, total=TRUE) > 0.7)
+plot(r2[sel])
+
+## this compares performance and output of rowpAUCs to function pAUC in
+## package ROC 
+if(require(ROC)){
+  ## performance
+  myRule = function(x)
+    pAUC(rocdemo.sca(truth = as.integer(sample.ExpressionSet$sex)-1 ,
+         data = x, rule = dxrule.sca), t0 = 0.1)
+  nGenes = 200
+  cat("computation time for ", nGenes, "genes:\n")
+  cat("function pAUC: ")
+  print(system.time(r3 <- esApply(sample.ExpressionSet[1:nGenes, ], 1, myRule)))
+  cat("function rowpAUCs: ")
+  print(system.time(r2 <- rowpAUCs(sample.ExpressionSet[1:nGenes, ],
+  "sex", p=1)))
+
+  ## compare output
+  myRule2 = function(x)
+   pAUC(rocdemo.sca(truth = as.integer(sample.ExpressionSet$sex)-1 ,
+                    data = x, rule = dxrule.sca), t0 = 1)
+  r4 <-  esApply(sample.ExpressionSet[1:nGenes, ], 1, myRule2)
+  plot(r4,area(r2), xlab="function pAUC", ylab="function rowpAUCs",
+  main="pAUCs")
+
+  plot(r4, area(rowpAUCs(sample.ExpressionSet[1:nGenes, ],
+  "sex", p=1, flip=FALSE)), xlab="function pAUC", ylab="function rowpAUCs",
+  main="pAUCs")
+
+  r4[r4<0.5] <- 1-r4[r4<0.5]
+  plot(r4, area(r2), xlab="function pAUC", ylab="function rowpAUCs",
+  main="pAUCs")
+ }
+}
+\keyword{math}
diff --git a/man/shorth.Rd b/man/shorth.Rd
new file mode 100644
index 0000000..f778b81
--- /dev/null
+++ b/man/shorth.Rd
@@ -0,0 +1,75 @@
+\name{shorth}
+\alias{shorth}
+\title{A location estimator based on the shorth}
+\description{A location estimator based on the shorth}
+\usage{shorth(x, na.rm=FALSE, tie.action="mean", tie.limit=0.05)}
+\arguments{
+  \item{x}{Numeric}
+  \item{na.rm}{Logical. If \code{TRUE}, then non-finite (according to
+    \code{\link{is.finite}}) values in \code{x} are ignored. Otherwise,
+    presence of non-finite or \code{NA} values will lead to an error message.}
+  \item{tie.action}{Character scalar. See details.}
+  \item{tie.limit}{Numeric scalar. See details.}
+}
+
+\details{The shorth is the shortest interval that covers half of the
+  values in \code{x}. This function calculates the mean of the \code{x}
+  values that lie in the shorth. This was proposed by Andrews (1972) as a 
+  robust estimator of location.
+
+  Ties: if there are multiple shortest intervals,
+  the action specified in \code{ties.action} is applied.
+  Allowed values are \code{mean} (the default), \code{max} and \code{min}.
+  For \code{mean}, the average value is considered; however, an error is
+  generated if the start indices of the different shortest intervals
+  differ by more than the fraction \code{tie.limit} of \code{length(x)}.
+  For \code{min} and \code{max}, the left-most or right-most, respectively, of
+  the multiple shortest intervals is considered.
+
+  Rate of convergence: as an estimator of location of a unimodal
+  distribution, under regularity conditions,
+  the quantity computed here has an asymptotic rate of only \eqn{n^{-1/3}} and a
+  complicated limiting distribution. 
+
+  See \code{\link{half.range.mode}} for an iterative version
+  that refines the estimate iteratively and has a builtin bootstrapping option.
+}
+
+\value{The mean of the \code{x} values that lie in the shorth.}
+
+\references{
+  \itemize{
+    \item G Sawitzki, \dQuote{The Shorth Plot.}
+    Available at http://lshorth.r-forge.r-project.org/TheShorthPlot.pdf 
+
+    \item DF Andrews, \dQuote{Robust Estimates of Location.}
+    Princeton University Press (1972).
+
+    \item R Grueble, \dQuote{The Length of the Shorth.} Annals of
+    Statistics 16, 2:619-628 (1988).
+
+    \item DR Bickel and R Fruehwirth, \dQuote{On a fast, robust
+    estimator of the mode: Comparisons to other robust estimators
+    with applications.} Computational Statistics & Data Analysis
+    50, 3500-3530 (2006).
+  }
+}
+
+\author{Wolfgang Huber \url{http://www.ebi.ac.uk/huber}, Ligia Pedroso Bras}
+\seealso{\code{\link{half.range.mode}}}
+
+\examples{
+ 
+  x = c(rnorm(500), runif(500) * 10)
+  methods = c("mean", "median", "shorth", "half.range.mode")
+  ests = sapply(methods, function(m) get(m)(x))
+
+  if(interactive()) {
+    colors = 1:4
+    hist(x, 40, col="orange")
+    abline(v=ests, col=colors, lwd=3, lty=1:2)
+    legend(5, 100, names(ests), col=colors, lwd=3, lty=1:2) 
+  }
+}
+\keyword{arith}
+
diff --git a/man/tdata.Rd b/man/tdata.Rd
new file mode 100644
index 0000000..37b887a
--- /dev/null
+++ b/man/tdata.Rd
@@ -0,0 +1,22 @@
+\name{tdata}
+\alias{tdata}
+\non_function{}
+\title{A small test dataset of Affymetrix Expression data. }
+\usage{data(tdata)}
+\description{
+The \code{tdata} data frame has 500 rows and 26 columns.
+The columns correspond to samples while the rows correspond to genes.
+The row names are Affymetrix accession numbers.
+}
+\format{
+  This data frame contains 26 columns.
+}
+
+\source{
+ An unknown data set.
+}
+
+\examples{
+data(tdata)
+}
+\keyword{datasets}
diff --git a/man/ttest.Rd b/man/ttest.Rd
new file mode 100644
index 0000000..e71a279
--- /dev/null
+++ b/man/ttest.Rd
@@ -0,0 +1,53 @@
+\name{ttest}
+\alias{ttest}
+\title{A filter function for a t.test }
+\description{
+  \code{ttest} returns a function of one argument with bindings for
+  \code{cov} and \code{p}.
+  The function, when evaluated, performs a t-test using \code{cov} as
+  the covariate. It returns \code{TRUE} if the p value for a difference
+  in means is less than \code{p}. 
+}
+\usage{
+ttest(m, p=0.05, na.rm=TRUE)
+}
+\arguments{
+  \item{m}{If \code{m} is of length one then it is assumed that elements
+  one through \code{m} of \code{x} will be one group. Otherwise \code{m}
+  is presumed to be the same length as \code{x} and constitutes the
+  groups.}
+  \item{p}{ The p-value for the test. }
+  \item{na.rm}{If set to \code{TRUE} any \code{NA}'s will be removed. }
+}
+\details{
+   When the data can be split into two groups (diseased and normal for
+   example) then we often want to select genes on their ability to
+   distinguish those two groups. The t-test is well suited to this and
+   can be used as a filter function.
+
+   This helper function creates a t-test (function) for the specified
+   covariate and considers a gene to have passed the filter if the
+   p-value for the gene is less than the prespecified \code{p}.
+  }
+\value{
+ \code{ttest} returns a function with bindings for \code{m} and
+ \code{p} that will perform a t-test.
+}
+\author{R. Gentleman }
+\seealso{\code{\link{kOverA}}, \code{\link{Anova}}, \code{\link{t.test}} }
+
+\examples{
+  dat <- c(rep(1,5),rep(2,5))
+  set.seed(5)
+  y <- rnorm(10)
+  af <- ttest(dat, .01)
+  af(y)
+  af2 <- ttest(5, .01)
+  af2(y)
+  y[8] <- NA
+  af(y)
+  af2(y)
+  y[1:5] <- y[1:5]+10
+  af(y)
+}
+\keyword{manip}
diff --git a/src/genefilter.h b/src/genefilter.h
new file mode 100644
index 0000000..3c39381
--- /dev/null
+++ b/src/genefilter.h
@@ -0,0 +1,9 @@
+/* Copyright Bioconductor Foundation NA, 2007, all rights reserved */
+#include <R.h>
+#include <Rinternals.h>
+
+typedef int RSInt;
+
+void gf_distance(double *x, RSInt *nr, RSInt *nc, RSInt *g, double *d, 
+		 RSInt *iRow, RSInt *nInterest, RSInt *nResults, 
+		 RSInt *method, double *wval);
diff --git a/src/half_range_mode.cpp b/src/half_range_mode.cpp
new file mode 100644
index 0000000..04d9bea
--- /dev/null
+++ b/src/half_range_mode.cpp
@@ -0,0 +1,125 @@
+#include <R.h>
+
+#include <vector>
+#include <algorithm>
+
+using namespace std;
+
+double half_range_mode( double *start, double *end, double beta, int diag ) {
+
+  // The end pointer is one step beyond the data...
+
+  double w, w_prime;
+  double *last, *new_start, *new_end;
+  vector<int> counts, J;
+  vector<double> w_range;
+  int i, s, e;
+  int N, N_prime, N_double_prime;
+  double lo, hi;
+
+  last = end - 1;
+  N = end - start;
+
+  // How many elements are in the set? Terminate recursion appropriately...
+
+  switch ( N ) {
+
+  case 1:
+    return *start;
+
+  case 2:
+    return .5 * ( *start + *last );
+
+  // Main recursive code begins here
+
+  default:
+    
+    w = beta * ( *last - *start ); 
+
+    // If all values are identical, return immediately...
+
+    if ( w == 0 ) return *start;
+
+    // If we're at the end of the data, counts can only get worse, so there's no point in continuing...
+    e = 0;
+    for( s = 0; s < N && e < N; s++ ) {
+      while ( e < N && start[ e ] <= start[ s ] + w ) { e++; }
+      counts.push_back( e - s );
+    }
+
+    // Maximum count, and its multiplicity
+
+    N_prime = *( max_element( counts.begin(), counts.end() ) );
+
+    for ( i = 0; i < (int) counts.size(); i++ ) if ( counts[i] == N_prime ) J.push_back( i );
+    
+    // Do we have more than one maximal interval?
+
+    if ( J.size() == 1 ) { 
+      // No... the interval's unique.
+      new_start = start + J[0];
+      new_end = start + J[0] + N_prime;
+    }
+    
+    else {
+
+      // Yes.. What's the smallest range?
+      for ( i = 0; i < (int) J.size(); i++ ) w_range.push_back( start[ J[i] + N_prime - 1 ] - start[ J[i] ] );
+      w_prime = *( min_element( w_range.begin(), w_range.end() ) );
+
+      // Set new start and end. We skip the more cumbersome V.min and V.max of the Bickel algorithm
+
+      i = 0;
+      while( w_range[ i ] > w_prime ) i++;
+      new_start = start + J[i];
+      new_end = start + J[i] + N_prime;
+      
+      // If there are any more maximal-count, minimal-range intervals, adjust
+      // new_end accordingly.
+      for ( i++; i < (int) J.size(); i++ ) if ( w_range[ i ] == w_prime ) new_end = start + J[i] + N_prime; 
+      
+    }
+    
+    // Adjustments in rare cases where the interval hasn't shrunk. Trim one end,
+    // the other, or both if lo == hi. Originally, this was inside the else
+    // block above. With discrete data with a small number of levels, it is
+    // possible, however for |J| = 1 AND N_double_prime = N, leading to an
+    // infinite recursion.
+    
+    N_double_prime = new_end - new_start;
+    
+    if (N_double_prime == N ) {
+      lo = new_start[1] - new_start[0];
+      hi = new_start[ N - 1 ] - new_start[ N - 2 ];
+      if ( lo <= hi ) { new_end--; }
+      if ( lo >= hi ) { new_start++; }
+    }
+
+    // Diagnostic output if requested
+
+    if (diag) Rprintf( "N = %i, N'' = %i, w = %.4f, |J| = %i\n", N, N_double_prime, w, J.size() );
+
+    // Clean up and then go in recursively
+
+    counts.clear(); J.clear(); w_range.clear();
+
+    return half_range_mode( new_start, new_end, beta, diag ); 
+
+  }
+  
+}
+
+
+
+
+extern "C" {
+
+  void half_range_mode( double *data, int *n, double *beta, int *diag, double *M ) {
+
+    // We assume that that data is already sorted for us...
+
+    *M = half_range_mode( data, data + *n, *beta, *diag );
+
+  }
+    
+}
diff --git a/src/init.c b/src/init.c
new file mode 100644
index 0000000..937c74c
--- /dev/null
+++ b/src/init.c
@@ -0,0 +1,15 @@
+/* Copyright Bioconductor Foundation of NA, 2007, all rights reserved */
+
+#include "R.h"
+#include "genefilter.h"
+#include "R_ext/Rdynload.h"
+
+static const R_CMethodDef CEntries[] = {
+    {"gf_distance", (DL_FUNC) &gf_distance, 10},
+    {NULL, NULL, 0}
+};
+
+void R_init_genefilter(DllInfo *dll)
+{
+    R_registerRoutines(dll, CEntries, NULL, NULL, NULL);
+}
diff --git a/src/nd.c b/src/nd.c
new file mode 100644
index 0000000..72dd2ae
--- /dev/null
+++ b/src/nd.c
@@ -0,0 +1,346 @@
+/* Copyright The Bioconductor Foundation 2007, all rights reserved */
+/* this is patterned on the R code in library/stats/src/distance.c as
+   we want to have similar values, but does not handle NA/Inf
+   identically, allows weights and solves the problem of finding
+   distances to a particular value, not necessarily all pairwise
+   distances */
+
+/* Modified in April 2007 for use with S-PLUS ArrayAnalyzer
+   by Insightful Corp.
+
+   Replaced all int declarations with RSInt declarations.
+   RSInt is defined in S-PLUS's R.h as:
+
+       typedef long RSInt;
+
+   Other changes are if-def-ed with if defined(_R_) around the
+   original code.
+ */
+
+/* and further modified since S.h in R defines USING_R - not
+  _R_ !!
+*/
+
+#include "S.h"
+
+#if defined(USING_R) /*( R-specific stuff */
+
+#define  S_CDECL
+#ifdef HAVE_CONFIG_H
+# include <config.h>
+#endif
+/* we need this first to get the right options for math.h */
+#include <R_ext/Arith.h>
+
+#include "genefilter.h"
+#include <Rmath.h>
+#include "R_ext/Error.h"
+#include "R_ext/Applic.h" 
+
+#else /*) Splus-specific stuff */
+
+#define S_COMPATIBILITY 1
+#include "rsplus.h"
+#endif
+
+typedef struct {
+    RSInt geneNum;
+    double geneDist;
+} gene_t;
+
+
+static void detectTies(RSInt geneNum, RSInt nResults, RSInt nRows, gene_t *data) {
+    /* Will scan through the first nResults+1 distances in the */
+    /* data array, and if it detects any ties, will flag a R */
+    /* warning */
+    RSInt i; /* Loop indices */
+    
+    /* If nResults == nRows, do not exceed nResults - otherwise exceed it */
+    /* by 1 in order to see if there were trailing ties */
+    if (nResults == nRows) {
+	nResults = nRows-1;
+    }
+    
+    for (i = 1; i < nResults; i++) {
+	if (data[i].geneDist == data[i+1].geneDist) {
+	    PROBLEM "There are distance ties in the data for gene %d\n",geneNum
+            WARN;
+	    break;
+	}
+    }
+}
+static int S_CDECL distCompare(const void *p1, const void *p2)
+{
+    const gene_t *i = p1;
+    const gene_t *j = p2;
+
+    if (!R_FINITE(i->geneDist ))
+      return(1);
+    if (!R_FINITE(j->geneDist))
+      return(-1);
+
+    if (i->geneDist > j->geneDist) 
+	return (1);
+    if (i->geneDist < j->geneDist) 
+	return (-1);
+    return (0);
+    
+}
+
+static double gf_correlation(double *x, double *wval, RSInt nr, RSInt nc, RSInt i1, RSInt i2) {
+  RSInt i; /* Loop index */
+  RSInt a,b; /* Used as array indices for i1 and i2 */
+  double xAvg, yAvg; /* Averages of the i1 and i2 rows */
+  double wA, wB; /* Weighted x[a] and x[b] */
+  double upTot = 0; /* Upper summation */
+  double botTotL, botTotR; /* The lower two summations */
+  double botVal; /* Bottom value for Rho */
+  double Rho, ans;
+  
+  botTotL = botTotR = 0;
+  xAvg = yAvg = 0;
+  a = i1;
+  b = i2;
+  
+  /* Calculate the averages for the i1 and i2 rows */
+  for (i = 0; i < nc; i++) {
+    if (R_FINITE(x[a])) {
+      xAvg += (wval[i] * x[a]);
+	}
+    if (R_FINITE(x[b])) {
+      yAvg += (wval[i] * x[b]);
+    }
+    a += nr;
+    b += nr;
+    }
+  xAvg /= (double)nc;
+  yAvg /= (double)nc;
+    /* Reset a & b */
+  a = i1; b = i2;
+  
+  /* Build up the three summations in the equation */
+  for (i = 0; i < nc; i++) {
+        if (R_FINITE(x[a]) && R_FINITE(x[b])) {
+	  wA = (x[a] - xAvg);
+	  wB = (x[b] - yAvg);
+	  upTot += wval[i]*wA*wB;
+	  botTotL += wval[i]*pow(wA,2);
+	  botTotR += wval[i]*pow(wB,2);
+        }
+        a += nr;
+        b += nr;
+  }
+  
+  /* Compute Rho & Distance (1 - R) */
+  botVal = sqrt((botTotL * botTotR));
+  Rho = upTot / botVal;
+  ans = 1 - Rho;
+    
+  return(ans);
+}
+
+static double gf_euclidean(double *x, double *wval, RSInt nr, RSInt nc, RSInt i1, RSInt i2) 
+{
+    double dev, ans;
+    RSInt ct, j;
+    
+    ct = 0;
+    ans = 0;
+
+    for(j = 0 ; j < nc ; j++) {
+	if(R_FINITE(x[i1]) && R_FINITE(x[i2])) {
+	    dev = (x[i1] - x[i2]);
+	    dev = dev * dev;
+	    /* Apply weight and add the total */
+	    ans += (wval[j] * dev);
+	    ct++;
+	}
+	i1 += nr;
+	i2 += nr;
+    }
+    if(ct == 0) return NA_REAL;
+    if(ct != nc) ans /= ((double)ct/nc);
+    return sqrt(ans);
+}
+
+static double gf_maximum(double *x, double *wval, RSInt nr, RSInt nc, RSInt i1, RSInt i2) 
+{
+    double dev, ans;
+    RSInt ct, j;
+
+    ct = 0;
+    ans = -DBL_MAX;
+    for(j = 0 ; j < nc ; j++) {
+	if(R_FINITE(x[i1]) && R_FINITE(x[i2])) {
+	    dev = fabs(x[i1] - x[i2]);
+	    /* apply the weight */
+	    dev *= wval[j];
+	    if(dev > ans)
+		ans = dev;
+	    ct++;
+	}
+	i1 += nr;
+	i2 += nr;
+    }
+    if(ct == 0) return NA_REAL;
+    return ans;
+}
+
+static double gf_manhattan(double *x, double *wval, RSInt nr, RSInt nc, RSInt i1, RSInt i2)
+{
+    double ans;
+    RSInt ct, j;
+
+    ct = 0;
+    ans = 0;
+    for(j = 0 ; j < nc ; j++) {
+	if(R_FINITE(x[i1]) && R_FINITE(x[i2])) {
+	    ans += (wval[j] * fabs(x[i1] - x[i2]));	    
+	    ct++;
+	}
+	i1 += nr;
+	i2 += nr;
+    }
+    if(ct == 0) return NA_REAL;
+    if(ct != nc) ans /= ((double)ct/nc);
+    return ans;
+}
+
+
+static double gf_canberra(double *x, double *wval, RSInt nr, RSInt nc, RSInt i1, RSInt i2)
+{
+    double ans, sum, diff;
+    RSInt ct, j;
+
+
+    ct = 0;
+    ans = 0;
+    for(j = 0 ; j < nc ; j++) {
+	if(R_FINITE(x[i1]) && R_FINITE(x[i2])) {
+	    sum = fabs(x[i1] + x[i2]);
+	    diff = fabs(x[i1] - x[i2]);
+	    if (sum > DBL_MIN || diff > DBL_MIN) {
+		ans += wval[j]*(diff/sum);
+		ct++;
+	    }
+	}
+	i1 += nr;
+	i2 += nr;
+    }
+    if(ct == 0) return NA_REAL;
+    if(ct != nc) ans /= ((double)ct/nc);
+    return ans;
+}
+
+static double gf_dist_binary(double *x, double *wval, RSInt nr, RSInt nc, RSInt i1, RSInt i2)
+{
+    RSInt total, ct, ans;
+    RSInt j;
+
+    total = 0;
+    ct = 0;
+    ans = 0;
+    for(j = 0 ; j < nc ; j++) {
+      if(R_FINITE(x[i1]) && R_FINITE(x[i2])) {
+	if(x[i1] || x[i2]){
+	  ct += wval[j];
+	  if( !(x[i1] && x[i2]) ) ans += wval[j];
+	}
+	total++;
+      }
+      i1 += nr;
+      i2 += nr;
+    }
+    
+
+
+    if(total == 0) return NA_REAL;
+    if(ct == 0) return 0;
+    return (double) ans / ct;
+}
+
+
+
+enum { EUCLIDEAN=1, MAXIMUM, MANHATTAN, CANBERRA, CORRELATION, BINARY};
+/* == 1,2,..., defined by order in the R function dist */
+
+void gf_distance(double *x, RSInt *nr, RSInt *nc, RSInt *g, double *d, 
+		 RSInt *iRow, RSInt *nInterest, RSInt *nResults, 
+		 RSInt *method, double *wval) {
+    /*
+      x -> Data Array
+      nr -> Number of rows in X
+      nc -> number of columns in X
+      g -> The nResults closest genes to the genes of interest
+      d -> The distances of the genes from g, 1 to 1 mapping
+      iRow -> rows of X that we are interested in
+      nInterest -> Number of elements in iRow
+      nResults -> The top X results to pass back
+      method -> which distance method to use
+    */
+    
+    RSInt  i,j, k;  /* Loop indices */
+    RSInt baseIndex; /* Used to index data arrays */
+    gene_t *tmp; /* Temporary array to hold the distance data */
+    double (*distfun)(double*, double*, RSInt, RSInt, RSInt, RSInt) = NULL;
+
+    /* Sanity check the nResults vs. number of rows in the data */
+    if (*nResults > *nr) {
+	warning("Number of results selected is greater than number of rows, using the number of rows instead\n");
+	*nResults = *nr-1;
+    }
+    
+    /* Size of tmp == *nr, as each gene we're interested in will
+       generate *nr distance points */
+
+    tmp = (gene_t *)R_alloc(*nr, sizeof(gene_t));
+    
+    /* Determine which distance function to use */
+    switch(*method) {
+    case EUCLIDEAN:
+	distfun = gf_euclidean;
+	break;
+    case MAXIMUM:
+	distfun = gf_maximum;
+	break;
+    case MANHATTAN:
+	distfun = gf_manhattan;
+	break;
+    case CANBERRA:
+	distfun = gf_canberra;
+	break;
+    case CORRELATION:
+	distfun = gf_correlation;
+	break;
+    case BINARY:
+	distfun = gf_dist_binary;
+	break;
+    default:
+	error("invalid distance");
+    }
+
+    for (j = 0; j < *nInterest; j++) {  
+	/* Get the distances for this gene, store in tmp array */
+
+	for(i = 0 ; i < (*nr) ; i++) {
+	    tmp[i].geneNum = i; 
+	    tmp[i].geneDist = distfun(x, wval, *nr, *nc, 
+				      iRow[j]-1, i);       
+	}
+	
+	/* Run a sort on the temp array */
+	qsort(tmp, *nr, sizeof(gene_t), distCompare);    
+
+	/* Detect any ties */
+	detectTies(iRow[j], *nResults, *nr, tmp); 
+
+	/* Copy the 1<->nResults data points into the final array */
+	baseIndex = *nResults * j;
+	for (k = 1; k <= *nResults; k++) {
+	    g[baseIndex + (k-1)] = tmp[k].geneNum; 
+	    d[baseIndex + (k-1)] = tmp[k].geneDist; 
+	}
+    }
+}
+
+
diff --git a/src/pAUC.c b/src/pAUC.c
new file mode 100644
index 0000000..0e4ebc9
--- /dev/null
+++ b/src/pAUC.c
@@ -0,0 +1,179 @@
+/*
+ * F. Hahne  10/24/2006
+ */
+
+#include <R.h>
+#include <Rinternals.h>
+#include <Rdefines.h>
+#include <R_ext/Rdynload.h>
+#include <R_ext/Utils.h>
+
+#include <stdlib.h>
+
+/*-----------------------------------------------------------------
+  internal c function for calculation of pAUCs
+  -----------------------------------------------------------------*/
+
+void pAUC_c(double *spec, double *sens, double *area, double *auc, double *p,
+	    int columns, int rows, int flip) {
+
+    int i, j, k, d;
+    double *x, *y;
+    double a, ta, tmp, lim, xsum ,ysum;
+
+    x   = (double *) R_alloc(columns+1, sizeof(double));
+    y   = (double *) R_alloc(columns+1, sizeof(double));
+
+
+    /* this computes pAUC for roc curve in row k*/
+    for(k=0; k<rows; k++){   /* iterate over rows (genes) */
+	xsum = ysum = 0;
+	for(i=k,d=0; i<rows*columns; i+=rows,d++){ /* iterate over cut points */
+	    x[d] = 1 - spec[i];
+	    y[d] = sens[i];
+	    xsum += x[d];
+	    ysum += y[d];
+	}/* for i,d */
+	/*rotate 180° if necessary*/
+	if(flip && xsum > ysum){
+	    for(i=k*columns,d=0; i<k*columns+columns; i++,d++){
+		spec[i] = 1 - sens[i];
+		sens[i] = x[d];
+		x[d] = 1-spec[i];
+		y[d] = sens[i];
+	    }/* for i,d */
+	}
+	d--;
+
+	/* reverse order if necessary */
+	if(x[0] > x[d]){
+	    for(i=0, j=d; i<=d/2; i++, j--){
+		tmp=x[i]; x[i]=x[j]; x[j]=tmp;
+		tmp=y[i]; y[i]=y[j]; y[j]=tmp;
+	    }
+	}
+	x[columns]=1;
+	y[columns]=y[columns-1];
+
+
+	/* compute area by trapezoidal rule*/
+	lim = x[0] < (*p) ? x[0] : *p; /*right border of first segment*/
+	a = (lim*y[0])/2; /*area of 1. segement (from x1=0 to x2=lim)*/
+	i=1;
+	while(x[i] < (*p)){
+	    a += ((x[i]-x[i-1])*(y[i]-y[i-1])/2) + ((x[i]-x[i-1])*y[i-1]);
+	    i++;
+	}
+
+	if(i > 2) /*last segment (from xn to p)*/
+	    a += (((*p)-x[i-1])*(y[i]-y[i-1])/2) + (((*p)-x[i-1])*y[i-1]);
+	ta = a;
+	/*compute full AUC and flip curve if necessary*/
+	if((*p) < 1){
+	    ta += ((x[i]-(*p))*(y[i]-y[i-1])/2) + ((x[i]-(*p))*y[i-1]);
+	    i++;
+	    while(i < columns+1 && x[i] < 1){
+		ta += ((x[i]-x[i-1])*(y[i]-y[i-1])/2) + ((x[i]-x[i-1])*y[i-1]);
+		i++;
+	    }
+	    ta += ((1-x[i-1])*(1-y[i-1])/2) + ((1-x[i-1])*y[i-1]);
+	}else{
+	    d=1;
+	}
+	if(flip && (*p)==1 && ta < 0.5){ /*rotate 180° if area < 0.5*/
+	    a = (*p) - a;
+	    ta = 1-ta;
+	}
+	if(a>1){
+	    error("Internal error");
+	}
+	area[k] = a;
+	auc[k] = ta;
+    }
+}
+
+
+
+
+
+
+
+/*-----------------------------------------------------------------
+  interface to R with arguments:
+  spec :    matrix of numerics (specificity)
+  sens:   matrix of numerics (sensitivity)
+  p:        numeric in 0<p<1, limit to integrate pAUC to
+  ------------------------------------------------------------------*/
+
+SEXP pAUC(SEXP _spec, SEXP _sens, SEXP _p, SEXP _flip)
+{
+    SEXP res, namesres;      /* return value: a list */
+    SEXP area;  /* list element for constructing
+		   the return value */
+    SEXP auc;  /* list element for constructing
+		  the return value */
+    SEXP dimSpec; /* dimensions for spec and sens matrices */
+    SEXP dimSens;
+
+    double *spec;
+    double *sens;
+    double *p;
+    int flip;
+    int rows, columns;  /* dimensions of spec and sens  */
+
+
+    /* check input argument spec */
+    PROTECT(dimSpec = getAttrib(_spec, R_DimSymbol));
+    if((!isReal(_spec)) | isNull(dimSpec) | (LENGTH(dimSpec)!=2))
+	error("Invalid argument 'spec': must be a real matrix.");
+    spec   = REAL(_spec);
+    rows = INTEGER(dimSpec)[1];
+    columns = INTEGER(dimSpec)[0];
+    UNPROTECT(1);
+    /* done with spec */
+
+    /* check input argument sens */
+    PROTECT(dimSens = getAttrib(_sens, R_DimSymbol));
+    if((!isReal(_sens)) | isNull(dimSens) | (LENGTH(dimSens)!=2))
+	error("Invalid argument 'sens': must be a real matrix.");
+    sens   = REAL(_sens);
+    if(rows != INTEGER(dimSens)[1] | columns != INTEGER(dimSens)[0])
+	error("'spec' and 'sens' must be matrices with equal dimensions");
+    UNPROTECT(1);
+    /* done with sens */
+
+    /* check input argument p */
+    if(!isReal(_p) || length(_p)!=1)
+	error("'p' must be numeric.");
+    p = REAL(_p);
+    if(((*p)<0)||((*p)>1))
+	error("'p' must be between 0 and 1.");
+    /* done with p */
+
+    /* check input argument flip */
+    if(!isInteger(_flip))
+	error("'flip' must be an integer.");
+    flip = (int)INTEGER(_flip)[0];
+    /* done with flip */
+
+    /* allocate memory for return values */
+    PROTECT(area = allocVector(REALSXP, columns));
+    PROTECT(auc = allocVector(REALSXP, columns));
+
+    /* Do it! */
+    pAUC_c(spec, sens, REAL(area), REAL(auc), p, rows, columns, flip);
+
+    /* return value: a list with elements spec sens and area */
+    PROTECT(res = allocVector(VECSXP, 2));
+    SET_VECTOR_ELT(res, 0, area);
+    SET_VECTOR_ELT(res, 1, auc);
+
+
+    PROTECT(namesres = allocVector(STRSXP, 2));
+    SET_STRING_ELT(namesres, 0, mkChar("pAUC"));
+    SET_STRING_ELT(namesres, 1, mkChar("AUC"));
+    setAttrib(res, R_NamesSymbol, namesres);
+
+    UNPROTECT(4); /* done with res, namesres, pAUC, auc */
+    return(res);
+}
diff --git a/src/rowPAUCs.c b/src/rowPAUCs.c
new file mode 100644
index 0000000..78e690c
--- /dev/null
+++ b/src/rowPAUCs.c
@@ -0,0 +1,225 @@
+/*
+ * F. Hahne  10/26/2005
+ */
+
+#include <R.h>
+#include <Rinternals.h>
+#include <Rdefines.h>
+#include <R_ext/Rdynload.h>
+#include <R_ext/Utils.h>
+
+#include <stdlib.h>
+
+/*-----------------------------------------------------------------
+  internal c function for calculation of ROC curves and pAUCs
+  -----------------------------------------------------------------*/
+
+void ROCpAUC_c(double *data, int nrd, int ncd, double *cutp, int ncc,
+	       int *truth, double *spec, double *sens, double *area,
+	       double *auc, double *p, int flip) {
+
+    int i, j, k, pred, d, rsum, csum, rcount, ccount;
+    double *x, *y;
+    double a, ta, tmp, lim, xsum, ysum;
+
+    x   = (double *) R_alloc(ncc+1, sizeof(double));
+    y   = (double *) R_alloc(ncc+1, sizeof(double));
+
+    /* this code computes roc for a given n * n matrix at given
+       cut points */
+    //printf("Computing ROC curves for %d rows at %d cutpoints ...\n", nrd, ncc);
+    for(k=0; k<nrd; k++){   /* iterate over rows (genes) */
+	for(i=k; i<ncc*nrd; i+=nrd){   /* iterate over cut points */
+	    rsum = csum = rcount = ccount = 0;
+	    for(j=k, d=0; j<nrd*ncd; j+=nrd, d++){   /* iterate over columns (samples) */
+		pred = (data[j] > cutp[i]) ? 1 : 0;
+		if(truth[d] == 1){
+		    rsum += pred;
+		    rcount++;
+		}
+		else{
+		    csum+=(1-pred);
+		    ccount++;
+		}
+	    }   /* for j (columns)*/
+	    sens[i] = (double)rsum/rcount;
+	    spec[i] = (double)csum/ccount;
+	}   /* for i (cutpoints)*/
+
+
+
+
+	/* this computes pAUC for roc curve in row k*/
+	xsum = ysum = 0;
+	for(i=k,d=0; i<ncc*nrd; i+=nrd,d++){
+	    x[d] = 1 - spec[i];
+	    y[d] = sens[i];
+	    xsum += x[d];
+	    ysum += y[d];
+	}/* for i,d */
+
+	/*rotate 180° if necessary*/
+	if(flip && xsum > ysum){
+	    for(i=k,d=0; i<ncc*nrd; i+=nrd,d++){
+		spec[i] = 1 - sens[i];
+		sens[i] = x[d];
+		x[d] = 1-spec[i];
+		y[d] = sens[i];
+	    }/* for i,d */
+	}
+	d--;
+
+	/* reverse order if necessary */
+	if(x[0] > x[d]){
+	    for(i=0, j=d; i<=(d+1)/2; i++, j--){
+		tmp=x[i]; x[i]=x[j]; x[j]=tmp;
+		tmp=y[i]; y[i]=y[j]; y[j]=tmp;
+	    }
+	}
+	x[ncc] = 1;
+	y[ncc] = y[ncc-1];
+
+	/* compute area by trapezoidal rule*/
+	lim = x[0] < (*p) ? x[0] : *p; /*right border of first segment*/
+	a = (lim*y[0])/2; /*area of 1. segement (from x1=0 to x2=lim)*/
+	i=1;
+	while(x[i] < (*p)){
+	    a += ((x[i]-x[i-1])*(y[i]-y[i-1])/2) + ((x[i]-x[i-1])*y[i-1]);
+	    i++;
+	}
+
+	if(i > 2){ /*last segment (from xn to p)*/
+	    a += (((*p)-x[i-1])*(y[i]-y[i-1])/2) + (((*p)-x[i-1])*y[i-1]);
+	}
+	ta = a;
+	/*compute full AUC and flip curve if necessary*/
+	if((*p) < 1){
+	    ta += ((x[i]-(*p))*(y[i]-y[i-1])/2) + ((x[i]-(*p))*y[i-1]);
+	    i++;
+	    while(i < ncc+1 && x[i] < 1){
+		ta += ((x[i]-x[i-1])*(y[i]-y[i-1])/2) + ((x[i]-x[i-1])*y[i-1]);
+		i++;
+	    }
+	    ta += ((1-x[i-1])*(1-y[i-1])/2) + ((1-x[i-1])*y[i-1]);
+	}
+	if(flip && (*p)==1 && ta < 0.5){ /*rotate 180° if area < 0.5*/
+	    a = (*p) - a;
+	    ta = 1-ta;
+	}
+	if(a>1)
+	    error("Internal error");
+	area[k] = a;
+	auc[k] = ta;
+    }
+}
+
+
+/*-----------------------------------------------------------------
+  interface to R with arguments:
+  data :    matrix of numerics
+  cutpts:   matrix with treshholds for ROC curve calculation
+  truth:    int with values 0 and 1, defining the real classification
+  p:        numeric in 0<p<1, limit to integrate pAUC to
+  ------------------------------------------------------------------*/
+
+SEXP ROCpAUC(SEXP _data, SEXP _cutpts, SEXP _truth, SEXP _p, SEXP _flip)
+{
+    SEXP dimData;  /* dimensions of data */
+    SEXP dimCutpts;  /* dimensions of cutpts */
+    SEXP res, namesres;      /* return value: a list */
+    SEXP spec, sens, area, auc;  /* list elements for constructing
+				    the return value */
+    SEXP dim; /* dimensions for spec and sens matrices in return value */
+
+    double *data;
+    double *cutp;
+    int *truth;
+    double *p;
+    int flip;
+    int nrd, ncd;  /* dimensions of data    */
+    int nrc, ncc;  /* dimensions of cutpts  */
+    int i;
+
+
+    /* check input argument data */
+    PROTECT(dimData = getAttrib(_data, R_DimSymbol));
+    if((!isReal(_data)) | isNull(dimData) | (LENGTH(dimData)!=2))
+	error("Invalid argument 'data': must be a real matrix.");
+    data   = REAL(_data);
+    nrd = INTEGER(dimData)[0];
+    ncd = INTEGER(dimData)[1];
+    UNPROTECT(1);
+    /* done with dimData */
+
+    PROTECT(dimCutpts = getAttrib(_cutpts, R_DimSymbol));
+    if((!isReal(_data)) | isNull(dimCutpts) | (LENGTH(dimCutpts)!=2))
+	error("Invalid argument 'cutpts': must be a real matrix.");
+    cutp   = REAL(_cutpts);
+    nrc  = INTEGER(dimCutpts)[0];
+    ncc  = INTEGER(dimCutpts)[1];
+    UNPROTECT(1);
+    if(nrc!=nrd)
+	error("nrc and nrd must be the same.");
+    /* done with dimCutpts */
+
+    /* check input argument truth */
+    if(!isInteger(_truth))
+	error("'truth' must be an integer.");
+    if(length(_truth)!=ncd) {
+	error("length(truth) and ncol(data) should be the same.");
+    }
+    truth = INTEGER(_truth);
+    for(i=0; i<ncd; i++)
+	if(! (R_IsNA(truth[i]) || ((truth[i]>=0)&&(truth[i]<=1))) )
+	    error("Elements of 'truth' must be 0 or 1.");
+    /* done with truth */
+
+    /* check input argument p */
+    if(!isReal(_p) || length(_p)!=1)
+	error("'p' must be numeric.");
+    p = REAL(_p);
+    if(((*p)<0)||((*p)>1))
+	error("'p' must be between 0 and 1.");
+    /* done with p */
+
+    /* check input argument flip */
+    if(!isInteger(_flip))
+	error("'flip' must be an integer.");
+    flip = (int)INTEGER(_flip)[0];
+    /* done with flip */
+
+    /* allocate memory for return values */
+    PROTECT(spec = allocVector(REALSXP, nrd*ncc));
+    PROTECT(sens = allocVector(REALSXP, nrd*ncc));
+    PROTECT(dim = allocVector(INTSXP, 2));
+    INTEGER(dim)[0] = nrd;
+    INTEGER(dim)[1] = ncc;
+    SET_DIM(spec, dim);
+    SET_DIM(sens, dim);
+
+    PROTECT(area = allocVector(REALSXP, nrd));
+    PROTECT(auc = allocVector(REALSXP, nrd));
+
+    /* Do it! */
+    /* note nrc is the same as nrd */
+    ROCpAUC_c(data, nrd, ncd, cutp, ncc, truth, REAL(spec), REAL(sens),
+	      REAL(area), REAL(auc), p, flip);
+
+    /* return value: a list with  elements spec sens and pAUC */
+    PROTECT(res = allocVector(VECSXP, 4));
+    SET_VECTOR_ELT(res, 0, spec);
+    SET_VECTOR_ELT(res, 1, sens);
+    SET_VECTOR_ELT(res, 2, area);
+    SET_VECTOR_ELT(res, 3, auc);
+
+
+    PROTECT(namesres = allocVector(STRSXP, 4));
+    SET_STRING_ELT(namesres, 0, mkChar("spec"));
+    SET_STRING_ELT(namesres, 1, mkChar("sens"));
+    SET_STRING_ELT(namesres, 2, mkChar("pAUC"));
+    SET_STRING_ELT(namesres, 3, mkChar("AUC"));
+    setAttrib(res, R_NamesSymbol, namesres);
+
+    UNPROTECT(7); /* done with res, namesres, spec, sens, dim, pAUC */
+    return(res);
+}
diff --git a/src/rowttests.c b/src/rowttests.c
new file mode 100644
index 0000000..8a67844
--- /dev/null
+++ b/src/rowttests.c
@@ -0,0 +1,218 @@
+/*
+ * Copyright W. Huber 2005
+ */
+ 
+#include <R.h>
+#include <Rinternals.h>
+#include <R_ext/Rdynload.h>
+#include <R_ext/Utils.h> 
+
+#include <stdlib.h>
+
+/* #define DEBUG */
+
+char errmsg[256];
+
+/*-----------------------------------------------------------------
+  which=0:  t-test by row
+  which=1:  t-test by column
+-----------------------------------------------------------------*/
+void rowcolttests_c(double *x, int *fac, int nr, int nc, int no, int nt, 
+                    int which, int nrgrp, double *statistic, double *dm, 
+                    double *df) {
+
+    int i, j, grp;
+    double z, delta, newmean, factor;
+
+    /* Currently the following provides for one- and two-sample t-tests (nrgrp=1 or 2), 
+       but it should be possible to generalize this code to more samples
+       (F-test) without too many changes */
+
+    int n[2];   
+    double* s[2];
+    double* ss[2];
+
+    if(nrgrp>2)
+	error("Please do not use 'nrgrp' >2 with 'rowcolttests'");
+
+    /* allocate and initialize storage for intermediate quantities
+       (namely first and second moments for each group) */
+    for(grp=0; grp<nrgrp; grp++) {
+	s[grp]  = (double*) R_alloc(nt, sizeof(double));
+	ss[grp] = (double*) R_alloc(nt, sizeof(double));
+	for(i=0; i<nt; i++)  
+	    s[grp][i] = ss[grp][i] = 0;
+    }
+
+    /* A numerically stable one-pass algorithm is used, see
+       http://en.wikipedia.org/wiki/Algorithms_for_calculating_variance#On-line_algorithm 
+       here: s ~ mean, ss ~ M2.
+       Work through the large matrix x in the order in which it is in memory (column-wise) -
+       in the hope that this may speed up getting it through the CPU. */
+    switch(which) {
+	case 0:  /* by row */
+	    for(i=0; i<nr; i++) {
+  	        for(grp=0; grp<nrgrp; grp++)
+		    n[grp] = 0;
+
+		for(j=0; j<nc; j++) {
+		    grp = fac[j];
+		    if(grp!=R_NaInt) {
+                        n[grp]++;
+			z = x[i+nr*j];
+                        delta   = z - s[grp][i];
+                        newmean = s[grp][i] + delta/n[grp];
+			s[grp][i]  = newmean;
+			ss[grp][i] += delta*(z-newmean);
+		    }
+		} /* for j */
+	    } /* for i */
+	    break;
+	case 1:  /* by column */
+	    for(grp=0; grp<nrgrp; grp++)
+		n[grp] = 0;
+
+	    for(i=0; i<nr; i++) {
+		grp = fac[i];
+		if(grp!=R_NaInt) { 
+                    n[grp]++;
+		    for(j=0; j<nc; j++) {
+			z = x[i+nr*j];
+                        delta   = z - s[grp][j];
+                        newmean = s[grp][j] + delta/n[grp];
+			s[grp][j]  = newmean;
+			ss[grp][j] += delta*(z-newmean);
+		    } /* for j */
+		} /* if */ 
+	    } /* for i */
+	    break;
+	default:
+	    error("Bummer!");
+    }
+
+    switch(nrgrp) {
+    case 1:
+        *df = n[0]-1;
+        factor = sqrt((*df) * n[0]);
+        for(i=0; i<nt; i++) {
+	    z            = ss[0][i];
+	    dm[i]        = s[0][i];
+	    statistic[i] =  factor * dm[i] / sqrt(z);
+        }
+        break;
+    case 2:
+	*df = n[0]+n[1]-2;
+        factor = sqrt((*df) * (double) n[0] * (double) n[1] / (n[0]+n[1]));
+        for(i=0; i<nt; i++) {
+            z            = ss[0][i] + ss[1][i];
+	    dm[i]        = s[0][i] - s[1][i];
+	    statistic[i] =  factor * dm[i] / sqrt(z);
+	}
+        break;
+    default:
+      error("Bummer!");
+    } /* switch */
+
+    return;
+} 
+
+/*-----------------------------------------------------------------
+
+   R interface 
+   x :    matrix
+   fac:   int with values 0 and 1, defining the two groups.
+   which: int. For 0, do the tests along the rows, for 1, 
+          along the columns 
+------------------------------------------------------------------*/
+SEXP rowcolttests(SEXP _x, SEXP _fac, SEXP _nrgrp, SEXP _which) 
+{
+  SEXP dimx;  /* dimensions of x */
+  SEXP res, namesres;      /* return value: a list */
+  SEXP statistic, dm, df;  /* list elements for constructing 
+                              the return value */
+
+  double *x;
+  int *fac;
+  int i, which, nrgrp;
+  int nr;  /* number of rows     */
+  int nc;  /* number of columns  */
+  int no;  /* number of objects  */
+  int nt;  /* number of tests    */
+
+  /* check input argument x */
+  PROTECT(dimx = getAttrib(_x, R_DimSymbol));
+  if((!isReal(_x)) | isNull(dimx) | (LENGTH(dimx)!=2))
+      error("Invalid argument 'x': must be a real matrix."); 
+  x   = REAL(_x);
+  nr  = INTEGER(dimx)[0];
+  nc  = INTEGER(dimx)[1];
+  UNPROTECT(1);          
+  /* done with dimx */
+
+  /* check input argument which */
+  if(!isInteger(_which) || length(_which)!=1) 
+      error("'which' must be integer of length 1.");
+  which = INTEGER(_which)[0];
+
+  /* check input argument nrgrp */
+  if(!isInteger(_nrgrp) || length(_nrgrp)!=1) 
+      error("'nrgrp' must be integer of length 1.");
+  nrgrp = INTEGER(_nrgrp)[0];
+
+  no = nt = -1; /* initialize - this is just to make some overeager compilers happy */
+
+  /* check input argument fac */
+  if(!isInteger(_fac))
+      error("'fac' must be an integer.");
+  switch(which) {
+      case 0: 
+	  if(length(_fac)!=nc) {
+	      sprintf(errmsg, "length(fac)=%d, ncol(x)=%d, should be the same.",
+		      length(_fac), nc);
+	      error(errmsg);
+	  }
+          no = nc;
+          nt = nr;
+	  break;
+      case 1:
+	  if(length(_fac)!=nr) {
+	      sprintf(errmsg, "length(fac)=%d, nrow(x)=%d, should be the same.",
+		      length(_fac), nr);
+	      error(errmsg);
+	  }
+          no = nr;
+          nt = nc;
+	  break;
+      default:
+	  error("'which' must be 0 or 1.");
+  }
+  
+  fac = INTEGER(_fac);
+  for(i=0; i<no; i++)
+      if(! ((fac[i]==R_NaInt) || ((fac[i]>=0)&&(fac[i]<nrgrp))) )
+	  error("Elements of 'fac' must be >=0 and < 'nrgrp'.");
+
+
+  PROTECT(statistic = allocVector(REALSXP, nt));
+  PROTECT(dm        = allocVector(REALSXP, nt));
+  PROTECT(df        = allocVector(REALSXP, 1));
+
+  /* Do it */
+  rowcolttests_c(x, fac, nr, nc, no, nt, which, nrgrp, REAL(statistic), REAL(dm), REAL(df));
+
+  /* return value: a list with two elements, statistic and df */
+  PROTECT(res = allocVector(VECSXP, 3));
+  SET_VECTOR_ELT(res, 0, statistic);
+  SET_VECTOR_ELT(res, 1, dm);
+  SET_VECTOR_ELT(res, 2, df);
+
+  PROTECT(namesres = allocVector(STRSXP, 3));
+  SET_STRING_ELT(namesres, 0, mkChar("statistic"));
+  SET_STRING_ELT(namesres, 1, mkChar("dm"));
+  SET_STRING_ELT(namesres, 2, mkChar("df"));
+  setAttrib(res, R_NamesSymbol, namesres);
+
+  UNPROTECT(5); /* done with res, namesres, statistic, dm, df */
+  return(res);
+}
+
diff --git a/src/ttest.f b/src/ttest.f
new file mode 100644
index 0000000..b790f4c
--- /dev/null
+++ b/src/ttest.f
@@ -0,0 +1,64 @@
+c By R Gray, March 19, 2000, DFCI
+c Copyright (C) 2000 Robert Gray
+c Distributed under the GNU public license
+c
+c t-statistics
+c first ng1 columns of d assumed to be group 1, other ng-ng1 assumed to be
+c group2.  Note: single precision stats
+c
+c  Modified by R. Gentleman, 2004, just extracted the ttest stats and 
+c  computed a ratio on demand - or fold-change
+
+      subroutine fastt(d,n,ng,ng1,z,dm,eqv,ratio)
+      real d(n,ng),z(n),dm(n)
+      integer n,ng,ng1,ng2,eqv,ratio
+c  initialize
+      ng2=ng-ng1
+      do 61 i=1,n
+         call tst2GM(d(i,1),ng1,ng2,n,z(i),dm(i), eqv, ratio)
+ 61   continue
+      return
+      end
+
+      subroutine tst2GM(d,ng1,ng2,n,tst,dm,eqv, ratio)
+c columns 1 to ng1 in group 1, ng1+1 to ng1+ng2 in group 2
+      real d(n,ng1+ng2),tst,dm
+      double precision dm1,dm2,dss1,dss2
+      integer ng1,ng2,n,i,eqv, ratio
+      dm1=0
+      dm2=0
+      dss1=0
+      dss2=0
+      do 10 i=1,ng1
+         dm1=dm1+d(1,i)
+ 10   continue
+      dm1=dm1/ng1
+      do 11 i=1,ng1
+         dss1=dss1+(d(1,i)-dm1)**2
+ 11   continue
+      do 12 i=1,ng2
+         dm2=dm2+d(1,ng1+i)
+ 12   continue
+      dm2=dm2/ng2
+      do 13 i=1,ng2
+         dss2=dss2+(d(1,ng1+i)-dm2)**2
+ 13   continue
+      if( ratio.eq.0) then
+         dm=dm1-dm2
+      endif
+      if( ratio.eq.1) then
+         dm=dm1/dm2
+      endif 
+      if (dss1.eq.0.and.dss2.eq.0) then
+         tst=0
+         return
+      endif
+c intermediate calculations in dp, so stats with many ties give same sp result
+c regardless of order of calculations
+      if( eqv .eq. 1 ) then
+         tst=(dm1-dm2)/sqrt((1.d0/ng1+1.d0/ng2)*(dss1+dss2)/(ng1+ng2-2))
+         return
+      endif
+      tst=(dm1-dm2)/sqrt(dss1/((ng1-1)*ng1)+dss2/((ng2-1)*ng2))
+      end
+
diff --git a/vignettes/howtogenefilter.Rnw b/vignettes/howtogenefilter.Rnw
new file mode 100644
index 0000000..f4b3c7d
--- /dev/null
+++ b/vignettes/howtogenefilter.Rnw
@@ -0,0 +1,212 @@
+%
+% NOTE -- ONLY EDIT howtogenefilter.Rnw!!!
+% howtogenefilter.tex file will get overwritten.
+%
+%\VignetteIndexEntry{Using the genefilter function to filter genes from a microarray dataset}
+%\VignetteDepends{Biobase, genefilter, class}
+%\VignetteKeywords{Expression Analysis}
+%\VignettePackage{genefilter}
+\documentclass{article}
+
+\usepackage{hyperref}
+
+\textwidth=6.2in
+\textheight=8.5in
+%\parskip=.3cm
+\oddsidemargin=.1in
+\evensidemargin=.1in
+\headheight=-.3in
+
+\newcommand{\classdef}[1]{%
+  {\em #1}
+}
+
+\begin{document}
+\title{Using the genefilter function to filter genes from a microarray dataset}
+
+\maketitle
+
+\section*{Introduction}
+
+The {\em genefilter} package can be used to filter (select) genes from
+a microarray dataset according to a variety of different
+filtering mechanisms.
+Here, we will consider the example dataset
+in the \verb+sample.ExpressionSet+ example from the {\em Biobase} package.
+This experiment has 26 samples, and there are 500 genes and 3
+covariates. The covariates are named \verb+sex+, \verb+type+ and
+\verb+score+. The first two have two levels and the last one is
+continuous.
+
+<<>>=
+library("Biobase")
+library("genefilter")
+data(sample.ExpressionSet)
+varLabels(sample.ExpressionSet)
+table(sample.ExpressionSet$sex)
+table(sample.ExpressionSet$type)
+@
+%$
+
+One dichotomy that can be of interest for subsequent analyses is whether the filter is
+\emph{specific} or \emph{non-specific}. Here, specific means that we are
+filtering with reference to sample metadata, for example, \texttt{type}. For example, if
+we want to select genes that are differentially expressed in the two
+groups defined by \texttt{type}, that is a specific filter.
+If on the other hand we want to select genes that are expressed in more
+than 5 samples, that is an example of a non--specific filter.
+
+First, let us see how to perform a non--specific filter.
+Suppose we want to select genes that have an expression measure above 200 in at
+least 5 samples. To do that we use the function \verb+kOverA+.
+
+There are three steps that must be performed.
+\begin{enumerate}
+\item Create function(s) implementing the filtering criteria.
+\item Assemble it (them) into a (combined) filtering function.
+\item Apply the filtering function to the expression matrix.
+\end{enumerate}
+
+<<>>=
+f1 <- kOverA(5, 200)
+ffun <- filterfun(f1)
+wh1 <- genefilter(exprs(sample.ExpressionSet), ffun)
+sum(wh1)
+@
+
+Here \verb+f1+ is a function that implies our ``expression measure above 200 in at
+least 5 samples'' criterion, the function \verb+ffun+ is the filtering
+function (which in this case consists of only one criterion), and we apply it using \verb+genefilter+.
+There were \Sexpr{sum(wh1)} genes that satisfied the criterion and passed the filter.
+
+As an example for a specific filter, let us select genes that are differentially
+expressed in the groups defined by \verb+type+.
+
+<<>>=
+f2 <- ttest(sample.ExpressionSet$type, p=0.1)
+wh2 <- genefilter(exprs(sample.ExpressionSet), filterfun(f2))
+sum(wh2)
+@
+%$
+Here, \texttt{ttest} is a function from the \texttt{genefilter}
+package which provides a suitable wrapper around \texttt{t.test} from
+package \textit{stats}. Now we see that there are \Sexpr{sum(wh2)}
+genes that satisfy the selection criterion. 
+
+Suppose that we want to combine the two filters. We want those genes
+for which at least 5 have an expression measure over 200 \emph{and} which also are differentially
+expressed between the groups defined by \verb+type+.
+
+<<>>=
+ffun_combined <- filterfun(f1, f2)
+wh3 <- genefilter(exprs(sample.ExpressionSet), ffun_combined)
+sum(wh3)
+@
+
+Now we see that there are only \Sexpr{sum(wh3)} genes  that satisfy both conditions.
+
+%%FIXME: need to replace this with something else
+%Our last example is to select genes that are
+%differentially expressed in at least one of the three groups defined
+%by \verb+cov3+.
+%To do that we use an Anova filter. This filter uses an analysis of
+%variance appraoch (via the \verb+lm+) function to test the hypothesis
+%that at least one of the three group means is different from the other
+%%two. The test is applied, then the $p$--value computed. We select
+%those genes that have a low $p$--value.
+%
+%<<>>=
+%Afilter <- Anova(eset$cov3)
+%aff <- filterfun(Afilter)
+%wh4 <- genefilter(exprs(eset), aff)
+%sum(wh4)
+%
+%@
+%%$
+%We see that there are 14 genes that pass this filter and that are
+%candidates for further exploration.
+
+
+\section*{Selecting genes that appear useful for prediction}
+
+The function \texttt{knnCV} defined below performs $k$--nearest neighbour classification
+using leave--one--out cross--validation.
+At the same time it aggregates the genes that were selected. The
+function returns the predicted classifications as its returned
+value. However, there is an additional side effect. The number of
+times that each gene was used (provided it was at least one) are
+recorded and stored in the environment of the aggregator \verb+Agg+.
+These can subsequently be retrieved and used for other purposes.
+
+<<aggregate>>=
+
+ knnCV <- function(EXPR, selectfun, cov, Agg, pselect = 0.01, Scale=FALSE) {
+   nc <- ncol(EXPR)
+   outvals <- rep(NA, nc)
+   for(i in 1:nc) {
+      v1 <- EXPR[,i]
+      expr <- EXPR[,-i]
+      glist <- selectfun(expr, cov[-i], p=pselect)
+      expr <- expr[glist,]
+      if( Scale ) {
+        expr <- scale(expr)
+        v1 <- as.vector(scale(v1[glist]))
+      }
+      else
+         v1 <- v1[glist]
+      out <- paste("iter ",i, " num genes= ", sum(glist), sep="")
+      print(out)
+      Aggregate(row.names(expr), Agg)
+      if( length(v1) == 1)
+         outvals[i] <- knn(expr, v1, cov[-i], k=5)
+      else
+          outvals[i] <- knn(t(expr), v1, cov[-i], k=5)
+    }
+    return(outvals)
+  }
+@
+%$
+
+<<aggregate>>=
+ gfun <- function(expr, cov, p=0.05) {
+    f2 <- ttest(cov, p=p)
+    ffun <- filterfun(f2)
+    which <- genefilter(expr, ffun)
+  }
+
+@
+
+Next we show how to use this function on the dataset
+\verb+geneData+.
+
+<<aggregate, results=hide>>=
+  library("class")
+
+  ##scale the genes
+  ##genescale is a slightly more flexible "scale"
+  ##work on a subset -- for speed only
+  geneData <- genescale(exprs(sample.ExpressionSet)[1:75,], 1)
+
+  Agg <- new("aggregator")
+
+  testcase <- knnCV(geneData, gfun, sample.ExpressionSet$type, 
+         Agg, pselect=0.05)
+@ 
+<<aggregate>>=
+sort(sapply(aggenv(Agg), c), decreasing=TRUE)
+@
+%$
+The environment \verb+Agg+ contains, for each gene,
+the number of times it was selected in the cross-validation.
+
+
+\section*{Session Information}
+
+The version number of R and packages loaded for generating the vignette were:
+
+<<echo=FALSE,results=tex>>=
+toLatex(sessionInfo())
+@
+
+\end{document}
+
diff --git a/vignettes/howtogenefinder.Rnw b/vignettes/howtogenefinder.Rnw
new file mode 100644
index 0000000..c09cbe0
--- /dev/null
+++ b/vignettes/howtogenefinder.Rnw
@@ -0,0 +1,111 @@
+%\VignetteIndexEntry{How to find genes whose expression profile is similar to that of specified genes}
+%\VignetteDepends{Biobase, genefilter}
+%\VignetteKeywords{Expression Analysis}
+%\VignettePackage{genefilter}
+\documentclass{article}
+\usepackage{hyperref}
+
+\textwidth=6.2in
+\textheight=8.5in
+\oddsidemargin=.1in
+\evensidemargin=.1in
+\headheight=-.3in
+
+\newcommand{\classdef}[1]{%
+  {\em #1}
+}
+
+\begin{document}
+\title{How to find genes whose expression profile is similar to that of specified genes}
+
+\maketitle
+
+\section*{Introduction}
+
+In some cases you have certain genes of interest and you would like to
+find other genes that are {\em close} to the genes of interest.
+This can be done using the \verb+genefinder+ function.
+
+You need to specify either the index position of the genes you want
+(which row of the expression array the gene is in) or the name
+(consistent with the \verb+featureNames+ of the ExpressionSet).
+
+A vector of names can be specified and matches for all will be
+computed. The number of matches and the distance measure used can all
+be specified.
+The examples will be carried out using the artificial data set,
+\verb+sample.ExpressionSet+.
+
+Two other options for \verb+genefinder+ are \verb+scale+ and \verb+method+.
+The \verb+scale+ option controls the scaling of the rows (this is
+often desirable) while the \verb+method+ option controls the distance
+measure used between genes. The possible values and their meanings are
+listed at the end of this document.
+
+<<>>=
+ library("Biobase")
+ library("genefilter")
+ data(sample.ExpressionSet)
+ igenes<- c(300,333,355,419) ##the interesting genes
+ closeg <- genefinder(sample.ExpressionSet, igenes, 10, 
+       method="euc", scale="none")
+ names(closeg)
+@
+
+The Affymetrix identifiers (since these were originally Affymetrix
+data) are \verb+31539_r_at+, \verb+31572_at+, \verb+31594_at+ and
+\verb+31658_at+.
+We can find the nearest genes (by index) for any of these by simply
+accessing the relevant component of \verb+closeg+.
+
+<<>>=
+closeg$"31539_r_at"
+Nms1 <- featureNames(sample.ExpressionSet)[closeg$"31539_r_at"$indices]
+Nms1
+@
+%$
+You could then take these names (from \verb+Nms1+) and the {\em
+  annotate} package and explore them further. See the various HOWTO's
+  in annotate to see how to further explore your data.
+Examples include finding and searching all PubMed abstracts associated
+  with these data. Finding and downloading associated sequence information.
+The data can also be visualized using the {\em geneplotter} package
+  (again there are a number of HOWTO documents there).
+
+
+\section*{Parameter Settings}
+
+The \verb+scale+ parameter can take the following values:
+\begin{description}
+\item[none] No scaling is done.
+\item[range] Scaling is done by $(x_i - x_{(1)})/(x_{(n)}- x_{(1)})$.
+\item[zscore] Scaling is done by $(x_i - \bar{x})/ s_x$. Where $s_x$
+  is the standard deviation.
+\end{description}
+
+The \verb+method+ parameter can take the following values:
+\begin{description}
+\item[euclidean] Euclidean distance is used.
+\item[maximum]  Maximum distance between any two elements of x and y
+          (supremum norm).
+\item[manhattan] Absolute distance between the two vectors (1 norm).
+
+ \item[canberra] The $\sum (|x_i - y_i| / |x_i + y_i|)$.  Terms with zero
+          numerator and denominator are omitted from the sum and
+          treated as if the values were missing.
+\item[binary] (aka asymmetric binary): The vectors are regarded as
+          binary bits, so non-zero elements are {\em on} and zero elements
+          are {\em off}.  The distance is the proportion of bits in which
+          only one is on amongst those in which at least one is on.
+\end{description}
+
+\section*{Session Information}
+
+The version number of R and packages loaded for generating the vignette were:
+
+<<echo=FALSE,results=tex>>=
+toLatex(sessionInfo())
+@
+
+\end{document}
+
diff --git a/vignettes/independent_filtering.Rnw b/vignettes/independent_filtering.Rnw
new file mode 100644
index 0000000..837094c
--- /dev/null
+++ b/vignettes/independent_filtering.Rnw
@@ -0,0 +1,468 @@
+%\VignetteIndexEntry{Diagnostics for independent filtering}
+%\VignettePackage{genefilter}
+%\VignetteEngine{knitr::knitr}
+
+% To compile this document
+% library('knitr'); rm(list=ls()); knit('independent_filtering.Rnw')
+
+\documentclass[10pt]{article}
+
+<<knitr, echo=FALSE, results="hide">>=
+library("knitr")
+opts_chunk$set(tidy=FALSE,dev="png",fig.show="hide",
+               fig.width=4,fig.height=4.5,dpi=240,
+               message=FALSE,error=FALSE,warning=FALSE)
+@ 
+
+<<style, eval=TRUE, echo=FALSE, results="asis">>=
+BiocStyle:::latex2()
+@
+
+\usepackage{xstring}
+\newcommand{\thetitle}{Diagnostics for independent filtering: choosing filter statistic and cutoff}
+
+\title{\textsf{\textbf{\thetitle}}}
+\author{Wolfgang Huber\\[1em]European Molecular Biology Laboratory (EMBL)}
+
+% The following command makes use of SVN's 'Date' keyword substitution
+% To activate this, I used: svn propset svn:keywords Date independent_filtering.Rnw
+\date{\Rpackage{genefilter} version \Sexpr{packageDescription("genefilter")$Version}  (Last revision \StrMid{$Date: 2016-03-22 18:37:15 -0400 (Tue, 22 Mar 2016) $}{8}{18})}
+
+
+\begin{document}
+
+<<options,results='hide',echo=FALSE>>=
+options(digits=3, width=100)
+library("pasilla") # make sure this is installed, since we need it in the next section
+@
+
+% Make title
+\maketitle
+\tableofcontents
+\vspace{.25in}
+
+\begin{abstract}
+\noindent This vignette illustrates diagnostics that are intended to help with
+\begin{itemize}
+\item the choice of filter criterion and
+\item the choice of filter cutoff
+\end{itemize}
+in independent filtering~\cite{Bourgon:2010:PNAS}. The package 
+\Biocpkg{genefilter} provides functions that might be convenient for this purpose.
+\end{abstract}
+
+%-----------------------------------------------------------
+\section{Introduction}
+%-----------------------------------------------------------
+Multiple testing approaches, with thousands of tests, are often used
+in analyses of genome-scale data. For instance, in analyses of
+differential gene expression based on RNA-Seq or microarray data, a
+common approach is to apply a statistical test, one by one, to each of
+thousands of genes, with the aim of identifying those genes that have
+evidence for a statistical association of their expression
+measurements with the experimental covariate(s) of interest.  Another
+instance is differential binding detection from ChIP-Seq data.  The
+idea of \emph{independent filtering} is to filter out those tests from
+the procedure that have no, or little chance of showing significant
+evidence, without even looking at their test statistic. Typically,
+this results in increased detection power at the same experiment-wide
+type I error, as measured in terms of the false discovery rate.  A
+good choice for a filtering criterion is one that
+\begin{enumerate}
+  \item\label{it:indp} is statistically independent from the test statistic
+    under the null hypothesis,
+  \item\label{it:corr} is correlated with the test statistic under the
+    alternative, and
+  \item\label{it:joint} does not notably change the dependence
+    structure --if there is any-- of the joint test statistics
+    (including those corresponding to true nulls and to true
+    alternatives).
+\end{enumerate}
+The benefit from filtering relies on property~\ref{it:corr}, and I will explore that
+further in Section~\ref{sec:qual}. The statistical validity of filtering relies on
+properties \ref{it:indp} and \ref{it:joint}.  For many practically useful combinations of
+filter criteria with test statistics, property~\ref{it:indp} is easy to prove (e.\,g., through
+Basu's theorem).  Property~\ref{it:joint} is more complicated, but rarely
+presents a problem in practice: if, for the multiple testing procedure that is being used,
+the correlation structure of the tests was acceptable without filtering, the filtering should 
+not change that. Please see~\cite{Bourgon:2010:PNAS} for further discussion on the
+mathematical and conceptual background.
+
+%-----------------------------------------------------------
+\section{Example data set}
+%-----------------------------------------------------------
+For illustration, let us use the \Robject{pasillaGenes} dataset from the
+Bioconductor package \Rpackage{pasilla}; this is an RNA-Seq dataset
+from which we extract gene-level read counts for two replicate samples
+the were measured for each of two biological conditions: normally
+growing cells and cells treated with dsRNA against the \emph{Pasilla}
+mRNA, which led to RNAi interference (RNAi) mediated knockdown of the
+Pasilla gene product.
+%
+<<libraries,results='hide'>>=
+library("pasilla")
+data("pasillaGenes")
+@
+%
+We perform a standard analysis with \Rpackage{DESeq} to look for genes
+that are differentially expressed between the normal and
+Pasilla-knockdown conditions, indicated by the factor variable
+\Robject{condition}. In the generalized linear model (GLM) analysis,
+we adjust for an additional experimental covariate \Robject{type},
+which is however not of interest for the differential expression. For
+more details, please see the vignette of the \Rpackage{DESeq} package.
+%
+<<DESeq1,results='hide'>>=
+library("DESeq")
+<<DESeq2,cache=TRUE,results='hide'>>=
+cds  = estimateSizeFactors( pasillaGenes )
+cds  = estimateDispersions( cds )
+fit1 = fitNbinomGLMs( cds, count ~ type + condition )
+fit0 = fitNbinomGLMs( cds, count ~ type  )
+<<DESeq3,cache=TRUE>>=
+res = data.frame(
+filterstat = rowMeans(counts(cds)),
+pvalue    = nbinomGLMTest( fit1, fit0 ),
+row.names = featureNames(cds) )
+@
+%
+The details of the anove analysis are not important for the purpose of
+this vignette, the essential output is contained in the columns of the
+dataframe \Robject{res}:
+\begin{itemize}
+  \item \texttt{filterstat}: the filter statistic, here the average
+    number of counts per gene across all samples, irrespective of
+    sample annoation,
+  \item \texttt{pvalue}: the test $p$-values,
+\end{itemize}
+Each row of the dataframe corresponds to one gene:
+<<headres>>=
+dim(res)
+head(res)
+@
+
+%--------------------------------------------------
+\section{Qualitative assessment of the filter statistic}\label{sec:qual}
+%--------------------------------------------------
+<<pass,echo=FALSE,cache=TRUE>>=
+theta = 0.4
+pass = with(res, filterstat > quantile(filterstat, theta))
+@
+%
+First, consider Figure~\ref{figscatterindepfilt}, which shows that
+among the approximately \Sexpr{100*theta}\% of genes with lowest overall counts, \Robject{filterstat},
+there are essentially none that achieved an (unadjusted) $p$-value less than
+\Sexpr{signif(quantile(res$pvalue[!pass], 0.0001, na.rm=TRUE), 1)}
+(this corresponds to about \Sexpr{signif(-log10(quantile(res$pvalue[!pass], 0.0001, na.rm=TRUE)), 2)} on the $-\log_{10}$-scale).
+%
+<<figscatterindepfilt>>=
+with(res,
+  plot(rank(filterstat)/length(filterstat), -log10(pvalue), pch=16, cex=0.45))
+@
+<<figecdffilt>>=
+trsf = function(n) log10(n+1)
+plot(ecdf(trsf(res$filterstat)), xlab=body(trsf), main="")
+@
+\begin{figure}[ht]
+\centering
+\includegraphics[width=.49\textwidth]{figure/figscatterindepfilt-1}
+\includegraphics[width=.49\textwidth]{figure/figecdffilt-1}
+\caption{Left: scatterplot of the rank (scaled to $[0,1]$) of the
+  filter criterion \Robject{filterstat} ($x$-axis) versus the negative
+  logarithm of the test \Robject{pvalue} ($y$-axis). Right: the
+  empirical cumulative distribution function (ECDF) shows the
+  relationships between the values of \Robject{filterstat} and its
+  quantiles.}
+\label{figscatterindepfilt}
+\end{figure}
+%
+This means that by dropping the 40\% genes with lowest \Robject{filterstat},
+we do not loose anything substantial from our subsequent
+results.
+
+For comparison, suppose you had chosen a less useful filter statistic,
+say, the gene identifiers interpreted as a decimal number. The
+analogous scatterplot to that of Figure~\ref{figscatterindepfilt} is
+shown in Figure~\ref{figbadfilter}.
+%
+<<badfilter1,cache=TRUE>>=
+badfilter = as.numeric(gsub("[+]*FBgn", "", rownames(res)))
+@
+<<badfilter2,echo=FALSE>>=
+stopifnot(!any(is.na(badfilter)))
+@
+<<figbadfilter>>=
+plot(rank(badfilter)/length(badfilter), -log10(res$pvalue), pch=16, cex=0.45)
+@
+\begin{figure}[ht]
+\centering
+\includegraphics[width=.49\textwidth]{figure/figbadfilter-1}
+\caption{Scatterplot analogous to Figure~\ref{figscatterindepfilt}, but with \Robject{badfilter}.}
+\label{figbadfilter}
+\end{figure}
+
+%--------------------------------------------------
+\section{How to choose the filter statistic and the cutoff?}\label{sec:indepfilterchoose}
+%--------------------------------------------------
+The \texttt{filtered\_p} function in the \Rpackage{genefilter} package
+calculates adjusted $p$-values over a range of possible filtering
+thresholds. Here, we call this function on our results from above and
+compute adjusted $p$-values using the method of Benjamini and Hochberg (BH)
+for a range of different filter cutoffs.
+%
+\begin{figure}[tb]
+\begin{center}
+\includegraphics[width=0.49\textwidth]{figure/figrejection-1}
+\includegraphics[width=0.49\textwidth]{figure/fignumreject-1}
+\caption{Left panel: the plot shows the number of rejections (i.\,e.\ genes detected as
+  differentially expressed) as a function of the FDR threshold
+  ($x$-axis) and the filtering cutoff $\theta$ (line colours,
+  specified as quantiles of the distribution of the
+  filter statistic). The plot is produced by the \texttt{rejection\_plot}
+  function. Note that the lines for $\theta=0\%$ and
+  $10\%$ are overplotted by the line for $\theta=20\%$, since for the
+  data shown here, these quantiles correspond all to the same set of
+  filtered genes (cf.~Figure~\ref{figscatterindepfilt}). Right panel:
+  the number of rejections at FDR=10\% as a function of
+  $\theta$.}
+\label{figrej}
+\end{center}
+\end{figure}
+%
+<<genefilter,results='hide'>>=
+library("genefilter")
+<<pBH1,cache=TRUE>>=
+theta = seq(from=0, to=0.5, by=0.1)
+pBH = filtered_p(filter=res$filterstat, test=res$pvalue, theta=theta, method="BH")
+<<pBH2>>=
+head(pBH)
+@
+%
+The rows of this matrix correspond to the genes (i.\,e., the rows of \Robject{res}) and
+the columns to the BH-adjusted $p$-values for the different possible
+choices of cutoff \Robject{theta}. A value of \Robject{NA} indicates
+that the gene was filtered out at the corresponding filter cutoff.
+The \Rfunction{rejection\_plot} function takes such a matrix and
+shows how rejection count ($R$) relates to the choice of cutoff for the
+$p$-values. For these data, over a reasonable range of FDR cutoffs, increased
+filtering corresponds to increased rejections.
+%
+<<figrejection,fig.width=5.5,fig.height=5.5>>=
+rejection_plot(pBH, at="sample",
+               xlim=c(0, 0.5), ylim=c(0, 2000),
+               xlab="FDR cutoff (Benjamini & Hochberg adjusted p-value)", main="")
+@
+The plot is shown in the left panel of Figure~\ref{figrej}.
+
+
+%------------------------------------------------------------
+\subsection{Choice of filtering cutoff}\label{choose:cutoff}
+%------------------------------------------------------------
+If we select a fixed cutoff for the adjusted $p$-values, we can also look more closely at
+the relationship between the fraction of null hypotheses filtered and the total number of
+discoveries. The \texttt{filtered\_R} function wraps \texttt{filtered\_p} and just returns
+rejection counts. It requires you to choose a particular $p$-value cutoff, specified
+through the argument \Robject{alpha}.
+%
+<<filtered_R1,cache=TRUE>>=
+theta = seq(from=0, to=0.8, by=0.02)
+rejBH = filtered_R(alpha=0.1, filter=res$filterstat, test=res$pvalue, theta=theta, method="BH")
+@
+
+Because overfiltering (or use of a filter which is inappropriate for the
+application domain) discards both false and true null hypotheses, very large
+values of $\theta$ reduce power in this example:
+
+<<fignumreject,fig.width=5.5,fig.height=5.5>>=
+plot(theta, rejBH, type="l",
+     xlab=expression(theta), ylab="number of rejections")
+@
+The plot is shown in the right panel of Figure~\ref{figrej}.
+
+%------------------------------------------------------------
+\subsection{Choice of filtering statistic}\label{choose:filterstat}
+%------------------------------------------------------------
+We can use the analysis of the previous section~\ref{choose:cutoff} also to inform
+ourselves about different possible choices of filter statistic. We construct a dataframe
+with a number of different choices.
+
+<<differentstats,cache=TRUE>>=
+filterChoices = data.frame(
+  `mean`   = res$filterstat,
+  `geneID` = badfilter,
+  `min`    = rowMin(counts(cds)),
+  `max`    = rowMax(counts(cds)),
+  `sd`     = rowSds(counts(cds))
+)
+rejChoices = sapply(filterChoices, function(f)
+  filtered_R(alpha=0.1, filter=f, test=res$pvalue, theta=theta, method="BH"))
+<<colours,results='hide'>>=
+library("RColorBrewer")
+myColours = brewer.pal(ncol(filterChoices), "Set1")
+<<figdifferentstats,fig.width=5.5,fig.height=5.5>>=
+matplot(theta, rejChoices, type="l", lty=1, col=myColours, lwd=2,
+        xlab=expression(theta), ylab="number of rejections")
+legend("bottomleft", legend=colnames(filterChoices), fill=myColours)
+@
+%
+The result is shown in Figure~\ref{figdifferentstats}. It indicates that for the data at
+hand, \Robject{mean}, \Robject{max} and \Robject{sd} provide similar performance, whereas
+the other choices are less effective.
+\begin{figure}[tb]
+\begin{center}
+\includegraphics[width=0.49\textwidth]{figure/figdifferentstats-1}
+\caption{The number of rejections at FDR=10\% as a function of
+  $\theta$ (analogous to the right panel in Figure~\ref{figrej}) for a number of different choices of the filter statistic.}
+\label{figdifferentstats}
+\end{center}
+\end{figure}
+
+%--------------------------------------------------
+\section{Some more plots pertinent to multiple testing}
+%--------------------------------------------------
+%--------------------------------------------------
+\subsection{Joint distribution of filter statistic and  $p$-values}\label{sec:pvalhist}
+%--------------------------------------------------
+The left panel of Figure~\ref{figscatterindepfilt} shows the joint distribution of filter
+statistic and $p$-values. An alternative, perhaps simpler view is provided by the
+$p$-value histograms in Figure~\ref{fighistindepfilt}.  It shows how the filtering ameliorates the multiple testing
+problem -- and thus the severity of a multiple testing adjustment -- by removing a
+background set of hypotheses whose $p$-values are distributed more or less uniformly in
+$[0,1]$.
+<<histindepfilt, fig.width=7, fig.height=5>>=
+h1 = hist(res$pvalue[!pass], breaks=50, plot=FALSE)
+h2 = hist(res$pvalue[pass], breaks=50, plot=FALSE)
+colori <- c(`do not pass`="khaki", `pass`="powderblue")
+<<fighistindepfilt, dev="pdf">>=
+barplot(height = rbind(h1$counts, h2$counts), beside = FALSE,
+        col = colori, space = 0, main = "", ylab="frequency")
+text(x = c(0, length(h1$counts)), y = 0, label = paste(c(0,1)),
+     adj = c(0.5,1.7), xpd=NA)
+legend("topright", fill=rev(colori), legend=rev(names(colori)))
+@
+\begin{figure}[ht]
+\centering
+\includegraphics[width=.5\textwidth]{figure/fighistindepfilt-1}
+\caption{Histogram of $p$-values for all tests.
+  The area shaded in blue indicates the subset of those that pass the filtering,
+  the area in khaki those that do not pass.}
+\label{fighistindepfilt}
+\end{figure}
+
+%-----------------------------------------------------
+\subsection{Illustration of the Benjamini-Hochberg method}
+%------------------------------------------------------
+The Benjamini-Hochberg multiple testing adjustment
+procedure \cite{BH:1995} has a simple graphical illustration, which is
+produced in the following code chunk. Its result is shown in the left
+panel of Figure \ref{figmulttest}.
+%
+<<sortP, cache=TRUE>>=
+resFilt = res[pass,]
+orderInPlot = order(resFilt$pvalue)
+showInPlot = (resFilt$pvalue[orderInPlot] <= 0.06)
+alpha = 0.1
+<<sortedP, fig.width=4.5, fig.height=4.5>>=
+plot(seq(along=which(showInPlot)), resFilt$pvalue[orderInPlot][showInPlot],
+     pch=".", xlab = expression(rank(p[i])), ylab=expression(p[i]))
+abline(a=0, b=alpha/length(resFilt$pvalue), col="red3", lwd=2)
+@
+<<doBH, echo=FALSE, results='hide'>>=
+whichBH = which(resFilt$pvalue[orderInPlot] <= alpha*seq(along=resFilt$pvalue)/length(resFilt$pvalue))
+## Test some assertions:
+## - whichBH is a contiguous set of integers from 1 to length(whichBH)
+## - the genes selected by this graphical method coincide with those
+##   from p.adjust (i.e. padjFilt)
+stopifnot(length(whichBH)>0,
+          identical(whichBH, seq(along=whichBH)),
+          resFilt$FDR[orderInPlot][ whichBH] <= alpha,
+          resFilt$FDR[orderInPlot][-whichBH]  > alpha)
+@
+%
+%-----------------------------------------------------
+\subsection{Schweder and Spj\o{}tvoll plot}
+%------------------------------------------------------
+Schweder and Spj\o{}tvoll \cite{SchwederSpjotvoll1982} suggested a diagnostic plot
+of the observed $p$-values which permits estimation of the fraction of true null
+hypotheses. For a series of hypothesis tests $H_1, \ldots, H_m$ with $p$-values
+$p_i$, they suggested plotting
+%
+\begin{equation}
+  \left( 1-p_i, N(p_i) \right) \mbox{ for } i \in 1, \ldots, m,
+\end{equation}
+%
+where $N(p)$ is the number of $p$-values greater than $p$. An application of
+this diagnostic plot to \Robject{resFilt\$pvalue} is shown in the right panel of
+Figure \ref{figmulttest}.
+When all null hypotheses are true, the $p$-values are each uniformly distributed
+in $[0,1]$, Consequently, the cumulative distribution function of $(p_1, \ldots,
+p_m)$ is expected to be close to the line $F(t)=t$. By symmetry, the same
+applies to $(1 - p_1, \ldots, 1 - p_m)$.
+When (without loss of generality) the first $m_0$ null hypotheses are true and
+the other $m-m_0$ are false, the cumulative distribution function of $(1-p_1,
+\ldots, 1-p_{m_0})$ is again expected to be close to the line $F_0(t)=t$. The
+cumulative distribution function of $(1-p_{m_0+1}, \ldots, 1-p_{m})$, on the
+other hand, is expected to be close to a function $F_1(t)$ which stays below
+$F_0$ but shows a steep increase towards 1 as $t$ approaches $1$.
+In practice, we do not know which of the null hypotheses are true, so we can
+only observe a mixture whose cumulative distribution function is expected to be
+close to
+%
+\begin{equation}
+  F(t) = \frac{m_0}{m} F_0(t) + \frac{m-m_0}{m} F_1(t).
+\end{equation}
+%
+Such a situation is shown in the right panel of
+Figure \ref{figmulttest}. If
+$F_1(t)/F_0(t)$ is small for small $t$, then the mixture fraction
+$\frac{m_0}{m}$ can be estimated by fitting a line to the left-hand portion of
+the plot, and then noting its height on the right. Such a fit is shown by the
+red line in the right panel of Figure \ref{figmulttest}.
+%
+<<SchwSpjot, echo=FALSE, results='hide'>>=
+j  = round(length(resFilt$pvalue)*c(1, .66))
+px = (1-resFilt$pvalue[orderInPlot[j]])
+py = ((length(resFilt$pvalue)-1):0)[j]
+slope = diff(py)/diff(px)
+@
+<<SchwederSpjotvoll, fig.width=4.5, fig.height=4.5>>=
+plot(1-resFilt$pvalue[orderInPlot],
+     (length(resFilt$pvalue)-1):0, pch=".", xaxs="i", yaxs="i",
+     xlab=expression(1-p[i]), ylab=expression(N(p[i])))
+abline(a=0, slope, col="red3", lwd=2)
+abline(h=slope)
+text(x=0, y=slope, labels=paste(round(slope)), adj=c(-0.1, 1.3))
+@
+
+\begin{figure}[ht]
+\centering
+\includegraphics[width=.49\textwidth]{figure/sortedP-1}
+\includegraphics[width=.49\textwidth]{figure/SchwederSpjotvoll-1}
+\caption{\emph{Left:} illustration of the Benjamini-Hochberg multiple testing
+  adjustment procedure \cite{BH:1995}.  The black line shows the
+  $p$-values ($y$-axis) versus their rank ($x$-axis), starting with
+  the smallest $p$-value from the left, then the second smallest, and
+  so on. Only the first \Sexpr{sum(showInPlot)} $p$-values are shown.
+  The red line is a straight line with slope $\alpha/n$, where
+  $n=\Sexpr{length(resFilt[["pvalue"]])}$ is the number of tests, and
+  $\alpha=\Sexpr{alpha}$ is a target false discovery rate (FDR).  FDR
+  is controlled at the value $\alpha$ if the genes are selected
+  that lie to the left of the rightmost intersection between the red and black
+  lines: here, this results in \Sexpr{length(whichBH)} genes.
+  \emph{Right:} Schweder and Spj\o{}tvoll plot, as described in the text.}
+\label{figmulttest}
+\end{figure}
+
+
+%--------------------------------------------------
+\section*{Session information}
+%--------------------------------------------------
+<<sessionInfo, results='asis', echo=FALSE>>=
+si = as.character( toLatex( sessionInfo() ) )
+cat( si[ -grep( "Locale", si ) ], sep = "\n" )
+@
+
+
+\bibliography{library}
+
+\end{document}
diff --git a/vignettes/independent_filtering_plots.Rnw b/vignettes/independent_filtering_plots.Rnw
new file mode 100644
index 0000000..a433218
--- /dev/null
+++ b/vignettes/independent_filtering_plots.Rnw
@@ -0,0 +1,238 @@
+%\VignetteIndexEntry{Additional plots for: Independent filtering increases power for detecting differentially expressed genes, Bourgon et al., PNAS (2010)}
+%\VignettePackage{genefilter}
+%\VignetteEngine{knitr::knitr}
+
+% To compile this document
+% library('knitr'); rm(list=ls()); knit('independent_filtering_plots.Rnw')
+
+\documentclass[10pt]{article}
+
+<<knitr, echo=FALSE, results="hide">>=
+library("knitr")
+opts_chunk$set(tidy=FALSE,dev="png",fig.show="hide",
+               fig.width=4,fig.height=4.5,dpi=240,
+               message=FALSE,error=FALSE,warning=FALSE)
+@ 
+
+<<style, eval=TRUE, echo=FALSE, results="asis">>=
+BiocStyle:::latex2()
+@
+
+\usepackage{xstring}
+\newcommand{\thetitle}{Additional plots for: Independent filtering increases power for detecting differentially expressed genes, Bourgon et al., PNAS (2010)}
+
+\title{\thetitle}
+\author{Richard Bourgon}
+
+% The following command makes use of SVN's 'Date' keyword substitution
+% To activate this, I used: svn propset svn:keywords Date independent_filtering_plots.Rnw
+\date{\Rpackage{genefilter} version \Sexpr{packageDescription("genefilter")$Version} (Last revision \StrMid{$Date: 2016-03-22 18:37:15 -0400 (Tue, 22 Mar 2016) $}{8}{18})}
+
+\begin{document}
+
+<<setup, echo=FALSE>>=
+options( width = 80 )
+@ 
+
+% Make title
+\maketitle
+\tableofcontents
+\vspace{.25in}
+
+
+%%%%%%%% Main text
+
+\section{Introduction}
+
+This vignette illustrates use of some functions in the
+\emph{genefilter} package that provide useful diagnostics 
+for independent filtering~\cite{BourgonIndependentFiltering}:
+
+\begin{itemize}
+  \item \texttt{kappa\_p} and \texttt{kappa\_t}
+  \item \texttt{filtered\_p} and \texttt{filtered\_R}
+  \item \texttt{filter\_volcano}
+  \item \texttt{rejection\_plot}
+\end{itemize}
+
+\section{Data preparation}
+
+Load the ALL data set and the \emph{genefilter} package:
+
+<<libraries>>=
+library("genefilter")
+library("ALL")
+data("ALL")
+@
+
+Reduce to just two conditions, then take a small subset of arrays from these,
+with 3 arrays per condition:
+
+<<sample_data, cache=TRUE>>=
+bcell <- grep("^B", as.character(ALL$BT))
+moltyp <- which(as.character(ALL$mol.biol) %in% 
+                c("NEG", "BCR/ABL"))
+ALL_bcrneg <- ALL[, intersect(bcell, moltyp)]
+ALL_bcrneg$mol.biol <- factor(ALL_bcrneg$mol.biol)
+n1 <- n2 <- 3
+set.seed(1969)
+use <- unlist(tapply(1:ncol(ALL_bcrneg), 
+                     ALL_bcrneg$mol.biol, sample, n1))
+subsample <- ALL_bcrneg[,use]
+@
+
+We now use functions from \emph{genefilter} to compute overall standard devation
+filter statistics as well as standard two-sample $t$ and releated statistics.
+
+<<stats, cache=TRUE>>=
+S <- rowSds( exprs( subsample ) )
+temp <- rowttests( subsample, subsample$mol.biol )
+d <- temp$dm
+p <- temp$p.value
+t <- temp$statistic
+@ 
+
+
+\section{Filtering volcano plot}
+
+Filtering on overall standard deviation and then using a standard $t$-statistic
+induces a lower bound of fold change, albeit one which varies somewhat with the
+significance of the $t$-statistic. The \texttt{filter\_volcano} function allows
+you to visualize this effect.
+
+<<filter_volcano, include=FALSE>>=
+S_cutoff <- quantile(S, .50)
+filter_volcano(d, p, S, n1, n2, alpha=.01, S_cutoff)
+@ 
+The output is shown in the left panel of Fig.~\ref{fig:volcano}.
+
+\begin{figure}[tb]
+\begin{center}
+\includegraphics[width=0.49\textwidth]{figure/filter_volcano-1}
+\includegraphics[width=0.49\textwidth]{figure/kappa-1}
+\caption{Left panel: plot produced by the \texttt{filter\_volcano} function.
+Right panel: graph of the \texttt{kappa\_t} function.}
+\label{fig:volcano}
+\end{center}
+\end{figure}
+
+The \texttt{kappa\_p} and \texttt{kappa\_t} functions, used to make the volcano
+plot, compute the fold change bound multiplier as a function of either a
+$t$-test $p$-value or the $t$-statistic itself. The actual induced bound on the
+fold change is $\kappa$ times the filter's cutoff on the overall standard
+deviation. Note that fold change bounds for values of $|T|$ which are close to 0
+are not of practical interest because we will not reject the null hypothesis
+with test statistics in this range.
+
+<<kappa, include=FALSE>>=
+t <- seq(0, 5, length=100)
+plot(t, kappa_t(t, n1, n2) * S_cutoff, 
+     xlab="|T|", ylab="Fold change bound", type="l")
+@
+The plot is shown in the right panel of Fig.~\ref{fig:volcano}.
+
+
+
+\section{Rejection count plots}
+
+\subsection{Across $p$-value cutoffs}
+
+The \texttt{filtered\_p} function permits easy simultaneous calculation of
+unadjusted or adjusted $p$-values over a range of filtering thresholds
+($\theta$). Here, we return to the full ``BCR/ABL'' versus ``NEG'' data set, and
+compute adjusted $p$-values using the method of Benjamini and Hochberg, for a
+range of different filter stringencies.
+
+\begin{figure}[tb]
+\begin{center}
+\includegraphics[width=0.49\textwidth]{figure/rejection_plot-1}
+\includegraphics[width=0.49\textwidth]{figure/filtered_R_plot-1}
+\caption{Left panel: plot produced by the \texttt{rejection\_plot} function.
+Right panel: graph of \texttt{theta}.}
+\label{fig:rej}
+\end{center}
+\end{figure}
+
+
+<<table>>=
+table(ALL_bcrneg$mol.biol)
+@
+
+<<filtered_p>>=
+S2 <- rowVars(exprs(ALL_bcrneg))
+p2 <- rowttests(ALL_bcrneg, "mol.biol")$p.value
+theta <- seq(0, .5, .1)
+p_bh <- filtered_p(S2, p2, theta, method="BH")
+@
+
+<<p_bh>>=
+head(p_bh)
+@ 
+
+The \texttt{rejection\_plot} function takes sets of $p$-values corresponding to
+different filtering choices --- in the columns of a matrix or in a list --- and
+shows how rejection count ($R$) relates to the choice of cutoff for the
+$p$-values. For these data, over a reasonable range of FDR cutoffs, increased
+filtering corresponds to increased rejections.
+
+<<rejection_plot>>=
+rejection_plot(p_bh, at="sample",
+               xlim=c(0,.3), ylim=c(0,1000),
+               main="Benjamini & Hochberg adjustment")
+@
+The plot is shown in the left panel of Fig.~\ref{fig:rej}.
+
+
+
+
+\subsection{Across filtering fractions}
+
+If we select a fixed cutoff for the adjusted $p$-values, we can also look more
+closely at the relationship between the fraction of null hypotheses filtered and
+the total number of discoveries. The \texttt{filtered\_R} function wraps
+\texttt{filtered\_p} and just returns rejection counts. It requires a $p$-value
+cutoff. 
+
+<<filtered_R>>=
+theta <- seq(0, .80, .01)
+R_BH <- filtered_R(alpha=.10, S2, p2, theta, method="BH")
+@
+
+<<R_BH>>=
+head(R_BH)
+@
+
+Because overfiltering (or use of a filter which is inappropriate for the
+application domain) discards both false and true null hypotheses, very large
+values of $\theta$ reduce power in this example:
+
+<<filtered_R_plot>>=
+plot(theta, R_BH, type="l",
+     xlab=expression(theta), ylab="Rejections",
+     main="BH cutoff = .10"
+     )
+@
+The plot is shown in the right panel of Fig.~\ref{fig:rej}.
+
+
+
+%%%%%%%% Session info
+
+\section*{Session information}
+
+<<sessionInfo, results='asis', echo=FALSE>>=
+si <- as.character( toLatex( sessionInfo() ) )
+cat( si[ -grep( "Locale", si ) ], sep = "\n" )
+@
+
+
+\begin{thebibliography}{10}
+\bibitem{BourgonIndependentFiltering}
+Richard Bourgon, Robert Gentleman and Wolfgang Huber.
+\newblock Independent filtering increases power for detecting differentially
+expressed genes.
+\end{thebibliography}
+
+
+
+\end{document}
diff --git a/vignettes/library.bib b/vignettes/library.bib
new file mode 100644
index 0000000..a7fd34f
--- /dev/null
+++ b/vignettes/library.bib
@@ -0,0 +1,172 @@
+ at Article{Anders:2010:GB,
+  url =		 {http://genomebiology.com/2010/11/10/R106},
+  author =	 {Simon Anders and Wolfgang Huber},
+  Title =	 {{D}ifferential expression analysis for sequence
+                  count data},
+  Journal =	 {Genome Biology},
+  Year =	 2010,
+  Volume =	 11,
+  Pages =	 {R106},
+}
+
+ at article{BH:1995,
+  author =	 {Y. Benjamini and Y. Hochberg},
+  title =	 {Controlling the false discovery rate: a practical
+                  and powerful approach to multiple testing},
+  journal =	 "Journal of the Royal Statistical Society B",
+  year =	 1995,
+  volume =	 57,
+  pages =	 "289--300"
+}
+
+ at Article{Bourgon:2010:PNAS,
+  ISI =		 {ISI:000278054700015},
+  URL =		 {http://www.pnas.org/content/107/21/9546.long},
+  PDF =		 {PNAS-2010-Bourgon-9546-51.pdf},
+  author =	 {Richard Bourgon and Robert Gentleman and Wolfgang
+                  Huber},
+  Title =	 {Independent filtering increases detection power for
+                  high-throughput experiments},
+  journal =	 {PNAS},
+  Year =	 2010,
+  volume =	 107,
+  number =	 21,
+  pages =	 {9546--9551},
+}
+
+ at article{Brooks2010,
+  author =	 {Brooks, A. N. and Yang, L. and Duff, M. O. and
+                  Hansen, K. D. and Park, J. W. and Dudoit, S. and
+                  Brenner, S. E. and Graveley, B. R.},
+  doi =		 {10.1101/gr.108662.110},
+  issn =	 {1088-9051},
+  journal =	 {Genome Research},
+  pages =	 {193--202},
+  title =	 {{Conservation of an RNA regulatory map between
+                  Drosophila and mammals}},
+  url =
+                  {http://genome.cshlp.org/cgi/doi/10.1101/gr.108662.110},
+  year =	 2011
+}
+
+ at Article{Tibshirani1988,
+  author =	 {Robert Tibshirani},
+  title =	 {Estimating transformations for regression via
+                  additivity and variance stabilization},
+  journal =	 {Journal of the American Statistical Association},
+  year =	 1988,
+  volume =	 83,
+  pages =	 {394--405}
+}
+
+ at misc{htseq,
+  author =	 {Simon Anders},
+  title =	 {{HTSeq: Analysing high-throughput sequencing data
+                  with Python}},
+  year =	 2011,
+  howpublished = {\url{http://www-huber.embl.de/users/anders/HTSeq/}}
+}
+
+ at article{sagmb2003,
+  title =	 {Parameter estimation for the calibration and
+                  variance stabilization of microarray data},
+  author =	 {Wolfgang Huber and Anja von Heydebreck and Holger
+                  {S\"ultmann} and Annemarie Poustka and Martin
+                  Vingron},
+  journal =	 {Statistical Applications in Genetics and Molecular
+                  Biology},
+  year =	 2003,
+  volume =	 2,
+  number =	 1,
+  pages =	 {Article 3}
+}
+
+ at misc{summarizeOverlaps,
+  author =	 {Valerie Obenchain},
+  title =	 {Counting with \texttt{summarizeOverlaps}},
+  year =	 2011,
+  howpublished = {Vignette, distributed as part of the Bioconductor
+                  package \emph{GenomicRanges}, as file
+                  \emph{summarizeOverlaps.pdf}}
+}
+
+ at article{Anders:2012:GR,
+   author = {Simon Anders and Alejandro Reyes and Wolfgang Huber},
+   title = {Detecting differential usage of exons from {RNA-seq} data },
+   year = {2012},
+   journal = {Genome Research},
+   doi = {10.1101/gr.133744.111},
+}
+   
+ at article{CR,
+author = {Cox, D. R. and Reid, N.},
+journal = {Journal of the Royal Statistical Society, Series B},
+keywords = {CML,Cox-Reid,ML,dispersion},
+mendeley-tags = {CML,Cox-Reid,ML,dispersion},
+number = {1},
+pages = {1--39},
+title = {{Parameter orthogonality and approximate conditional inference}},
+url = {http://www.jstor.org/stable/2345476},
+volume = {49},
+year = {1987}
+}
+
+ at article{edgeR_GLM,
+author = {McCarthy, Davis J and Chen, Yunshun and Smyth, Gordon K},
+doi = {10.1093/nar/gks042},
+issn = {1362-4962},
+journal = {Nucleic Acids Research},
+keywords = {edgeR},
+mendeley-tags = {edgeR},
+month = jan,
+pmid = {22287627},
+title = {{Differential expression analysis of multifactor RNA-Seq experiments with respect to biological variation}},
+url = {http://www.ncbi.nlm.nih.gov/pubmed/22287627},
+year = {2012},
+volume={40},
+pages={4288-4297} 
+}
+
+ at article{SchwederSpjotvoll1982,
+author={Schweder, T. and Spj\/{o}tvoll, E.},
+title={Plots of {P-values} to evaluate many tests simultaneously},
+journal={Biometrika},
+year={1982},
+volume=69,
+pages={493-502},
+doi={10.1093/biomet/69.3.493}
+}
+
+ at article{Haglund2012Evidence,
+    abstract = {{Context: Primary hyperparathyroidism (PHPT) is most frequently present in postmenopausal women. Although the involvement of estrogen has been suggested, current literature indicates that parathyroid tumors are estrogen receptor (ER) alpha negative.}},
+    author = {Haglund, Felix and Ma, Ran and Huss, Mikael and Sulaiman, Luqman and Lu, Ming and Nilsson, Inga-Lena and H\"{o}\"{o}g, Anders and Juhlin, Christofer C. and Hartman, Johan and Larsson, Catharina},
+    day = {28},
+    doi = {10.1210/jc.2012-2484},
+    issn = {1945-7197},
+    journal = {Journal of Clinical Endocrinology \& Metabolism},
+    month = sep,
+    pmid = {23024189},
+    posted-at = {2012-11-23 08:40:12},
+    priority = {2},
+    publisher = {Endocrine Society},
+    title = {{Evidence of a Functional Estrogen Receptor in Parathyroid Adenomas}},
+    url = {http://dx.doi.org/10.1210/jc.2012-2484},
+    year = {2012}
+}
+
+ at article{Wu2012New,
+    author = {Wu, Hao and Wang, Chi and Wu, Zhijin},
+    day = {22},
+    doi = {10.1093/biostatistics/kxs033},
+    issn = {1468-4357},
+    journal = {Biostatistics},
+    month = sep,
+    pmid = {23001152},
+    posted-at = {2013-02-26 17:09:19},
+    priority = {2},
+    publisher = {Oxford University Press},
+    title = {{A new shrinkage estimator for dispersion improves differential expression detection in RNA-seq data}},
+    url = {http://dx.doi.org/10.1093/biostatistics/kxs033},
+    year = {2012}
+}
+

-- 
Alioth's /usr/local/bin/git-commit-notice on /srv/git.debian.org/git/debian-med/r-bioc-genefilter.git



More information about the debian-med-commit mailing list