Browse code

Commit made by the Bioconductor Git-SVN bridge. Consists of 1 commit.

Commit information:

Commit id: 384d1491ac0ebcb21e634d8274ab1974244270bd

adding aggregateBySample

Committed by: nosson
Author Name: nosson
Commit date: 2015-01-21 01:15:42 -0500
Author date: 2015-01-21 01:15:42 -0500


git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@98545 bc3139a8-67e5-0310-9ffc-ced21a209358

Joseph Paulson authored on 21/01/2015 06:15:51
Showing 4 changed files

... ...
@@ -1,6 +1,6 @@
1 1
 Package: metagenomeSeq
2 2
 Title: Statistical analysis for sparse high-throughput sequencing
3
-Version: 1.9.17
3
+Version: 1.9.18
4 4
 Date: 2014-12-20
5 5
 Author: Joseph Nathaniel Paulson, Hisham Talukder, Mihai Pop, Hector Corrada
6 6
     Bravo
... ...
@@ -33,5 +33,6 @@ Imports:
33 33
     matrixStats,
34 34
     gplots
35 35
 VignetteBuilder: knitr
36
-URL: http://cbcb.umd.edu/software/metagenomeSeq
36
+URL: https://github.com/nosson/metagenomeSeq/
37
+BugReports: https://github.com/nosson/metagenomeSeq/issues
37 38
 biocViews: Classification, Clustering, GeneticVariability, DifferentialExpression, Microbiome, Metagenomics, Visualization, MultipleComparison, Sequencing, Software
... ...
@@ -22,6 +22,8 @@ exportMethods(
22 22
 export(
23 23
 aggregateByTaxonomy,
24 24
 aggTax,
25
+aggregateBySample,
26
+aggSamp,
25 27
 biom2MRexperiment,
26 28
 calculateEffectiveSamples,
27 29
 calcNormFactors,
... ...
@@ -76,3 +76,69 @@ aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfu
76 76
 aggTax<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfun = colSums,sl=1000,out='MRexperiment'){
77 77
 	aggregateByTaxonomy(obj,lvl,alternate=alternate,norm=norm,log=log,aggfun = aggfun,sl=sl,out=out)
78 78
 }
79
+
80
+#' @name aggregateBySample
81
+#' @title Aggregates a MRexperiment object or counts matrix to by a factor.
82
+#' 
83
+#' @details Using the phenoData information in the MRexperiment, calling aggregateBySample on a
84
+#' MRexperiment and a particular phenoData column (i.e. 'diet') will aggregate counts
85
+#' using the aggfun function (default rowMeans). Possible aggfun alternatives
86
+#' include rowMeans and rowMedians.
87
+#' 
88
+#' @param obj A MRexperiment object or count matrix.
89
+#' @param fct phenoData column name from the MRexperiment object or if count matrix object a vector of labels.
90
+#' @param aggfun Aggregation function.
91
+#' @param out Either 'MRexperiment' or 'matrix'
92
+#' @return An aggregated count matrix or MRexperiment object.
93
+#' @aliases aggSamp
94
+#' @rdname aggregateBySample
95
+#' @export
96
+#' @examples
97
+#' 
98
+#' data(mouseData)
99
+#' aggregateBySample(mouseData[1:100,],fct="diet",aggfun=rowSums)
100
+#' # not run
101
+#' # aggregateBySample(mouseData,fct="diet",aggfun=rowMedians)
102
+#' # aggSamp(mouseData,fct='diet',aggfun=rowMaxs)
103
+#' 
104
+aggregateBySample<-function(obj,fct,aggfun=rowMeans,out="MRexperiment"){
105
+	if(class(obj)=="MRexperiment"){
106
+		mat = MRcounts(obj)
107
+		if(length(fct)==1) factors = as.character(pData(obj)[,fct])
108
+		else factors = as.character(fct)
109
+	} else {
110
+		mat = obj
111
+		factors = as.character(fct)
112
+		if(length(factors)!=ncol(mat)) stop("If input is a count matrix, fct must be a vector of length = ncol(count matrix)")
113
+	}
114
+	if(!(out%in%c("MRexperiment","matrix"))){
115
+		stop("The variable out must either be 'MRexperiment' or 'matrix'")
116
+	}
117
+	grps = split(seq_along(factors),factors)
118
+	
119
+	newMat = array(NA,dim=c(nrow(obj),length(grps)))
120
+	for(i in 1:length(grps)){
121
+		newMat[,i] = aggfun(mat[,grps[[i]],drop=FALSE])
122
+	}
123
+	colnames(newMat) = names(grps)
124
+	rownames(newMat) = rownames(obj)
125
+	if(out=='matrix') return(newMat)
126
+	if(out=='MRexperiment'){
127
+		pd = data.frame(names(grps))
128
+		colnames(pd) = "pd"
129
+		rownames(pd) = names(grps)
130
+		pd = as(pd,"AnnotatedDataFrame")
131
+		if(class(obj)=="MRexperiment"){
132
+			fd = as(fData(obj),"AnnotatedDataFrame")
133
+			newObj = newMRexperiment(newMat,featureData=fd,phenoData=pd)
134
+		} else {
135
+			newObj = newMRexperiment(newMat,phenoData=pd)
136
+		}
137
+		return(newObj)
138
+	}
139
+}
140
+#' @rdname aggregateBySample
141
+#' @export
142
+aggSamp<-function(obj,fct,aggfun=rowMeans,out='MRexperiment'){
143
+	aggregateBySample(obj,fct,aggfun=aggfun,out=out)
144
+}
79 145
new file mode 100644
... ...
@@ -0,0 +1,40 @@
1
+% Generated by roxygen2 (4.1.0): do not edit by hand
2
+% Please edit documentation in R/aggregateByTaxonomy.R
3
+\name{aggregateBySample}
4
+\alias{aggSamp}
5
+\alias{aggregateBySample}
6
+\title{Aggregates a MRexperiment object or counts matrix to by a factor.}
7
+\usage{
8
+aggregateBySample(obj, fct, aggfun = rowMeans, out = "MRexperiment")
9
+
10
+aggSamp(obj, fct, aggfun = rowMeans, out = "MRexperiment")
11
+}
12
+\arguments{
13
+\item{obj}{A MRexperiment object or count matrix.}
14
+
15
+\item{fct}{phenoData column name from the MRexperiment object or if count matrix object a vector of labels.}
16
+
17
+\item{aggfun}{Aggregation function.}
18
+
19
+\item{out}{Either 'MRexperiment' or 'matrix'}
20
+}
21
+\value{
22
+An aggregated count matrix or MRexperiment object.
23
+}
24
+\description{
25
+Aggregates a MRexperiment object or counts matrix to by a factor.
26
+}
27
+\details{
28
+Using the phenoData information in the MRexperiment, calling aggregateBySample on a
29
+MRexperiment and a particular phenoData column (i.e. 'diet') will aggregate counts
30
+using the aggfun function (default rowMeans). Possible aggfun alternatives
31
+include rowMeans and rowMedians.
32
+}
33
+\examples{
34
+data(mouseData)
35
+aggregateBySample(mouseData[1:100,],fct="diet",aggfun=rowSums)
36
+# not run
37
+# aggregateBySample(mouseData,fct="diet",aggfun=rowMedians)
38
+# aggSamp(mouseData,fct='diet',aggfun=rowMaxs)
39
+}
40
+