From: Justin Wagner <jmwagner@umd.edu>
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@128606 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -13,6 +13,8 @@ |
13 | 13 |
#' @param aggfun Aggregation function. |
14 | 14 |
#' @param sl scaling value, default is 1000. |
15 | 15 |
#' @param out Either 'MRexperiment' or 'matrix' |
16 |
+#' @param featureOrder Hierarchy of levels in taxonomy as fData colnames |
|
17 |
+#' @param returnFullHierarchy Boolean value to indicate return single column of fData or all columns of hierarchy |
|
16 | 18 |
#' @return An aggregated count matrix. |
17 | 19 |
#' @aliases aggTax |
18 | 20 |
#' @rdname aggregateByTaxonomy |
... | ... |
@@ -25,7 +27,7 @@ |
25 | 27 |
#' # aggregateByTaxonomy(mouseData,lvl="class",norm=TRUE,aggfun=colMedians) |
26 | 28 |
#' # aggTax(mouseData,lvl='phylum',norm=FALSE,aggfun=colSums) |
27 | 29 |
#' |
28 |
-aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfun = colSums,sl=1000,feature_order=NULL,out="MRexperiment"){ |
|
30 |
+aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfun = colSums,sl=1000,featureOrder=NULL,returnFullHierarchy=TRUE,out="MRexperiment"){ |
|
29 | 31 |
if(class(obj)=="MRexperiment"){ |
30 | 32 |
mat = MRcounts(obj,norm=norm,log=log,sl=sl) |
31 | 33 |
if(length(lvl)==1) levels = as.character(fData(obj)[,lvl]) |
... | ... |
@@ -57,13 +59,21 @@ aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfu |
57 | 59 |
colnames(newMat) = colnames(obj) |
58 | 60 |
if(out=='matrix') return(newMat) |
59 | 61 |
if(out=='MRexperiment'){ |
60 |
- if(is.null(feature_order)){ |
|
61 |
- feature_order <- colnames(fData(obj)) |
|
62 |
+ if(returnFullHierarchy){ |
|
63 |
+ |
|
64 |
+ if(is.null(featureOrder)){ |
|
65 |
+ featureOrder <- colnames(fData(obj)) |
|
66 |
+ } |
|
67 |
+ |
|
68 |
+ taxa = featureData(obj)[match(names(grps), fData(obj)[,lvl]),featureOrder[1:which(featureOrder == lvl)]] |
|
69 |
+ featureNames(taxa) = names(grps) |
|
70 |
+ } else{ |
|
71 |
+ taxa = data.frame(names(grps)) |
|
72 |
+ colnames(taxa) = "Taxa" |
|
73 |
+ rownames(taxa) = names(grps) |
|
74 |
+ taxa = as(taxa,"AnnotatedDataFrame") |
|
62 | 75 |
} |
63 |
- |
|
64 |
- taxa = featureData(obj)[match(names(grps), fData(obj)[,lvl]),feature_order[1:which(feature_order == lvl)]] |
|
65 |
- featureNames(taxa) = names(grps) |
|
66 |
- |
|
76 |
+ |
|
67 | 77 |
if(class(obj)=="MRexperiment"){ |
68 | 78 |
pd = phenoData(obj) |
69 | 79 |
newObj = newMRexperiment(newMat,featureData=taxa,phenoData=pd) |
... | ... |
@@ -75,6 +85,6 @@ aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfu |
75 | 85 |
} |
76 | 86 |
#' @rdname aggregateByTaxonomy |
77 | 87 |
#' @export |
78 |
-aggTax<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfun = colSums,sl=1000,out='MRexperiment'){ |
|
79 |
- aggregateByTaxonomy(obj,lvl,alternate=alternate,norm=norm,log=log,aggfun = aggfun,sl=sl,out=out) |
|
88 |
+aggTax<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfun = colSums,sl=1000,featureOrder=NULL,returnFullHierarchy=TRUE,out='MRexperiment'){ |
|
89 |
+ aggregateByTaxonomy(obj,lvl,alternate=alternate,norm=norm,log=log,aggfun = aggfun,sl=sl,featureOrder=featureOrder,returnFullHierarchy=returnFullHierarchy,out=out) |
|
80 | 90 |
} |
From: Justin Wagner <jmwagner@umd.edu>
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@128146 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -25,50 +25,53 @@ |
25 | 25 |
#' # aggregateByTaxonomy(mouseData,lvl="class",norm=TRUE,aggfun=colMedians) |
26 | 26 |
#' # aggTax(mouseData,lvl='phylum',norm=FALSE,aggfun=colSums) |
27 | 27 |
#' |
28 |
-aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfun = colSums,sl=1000,out="MRexperiment"){ |
|
29 |
- if(class(obj)=="MRexperiment"){ |
|
30 |
- mat = MRcounts(obj,norm=norm,log=log,sl=sl) |
|
31 |
- if(length(lvl)==1) levels = as.character(fData(obj)[,lvl]) |
|
32 |
- else levels = as.character(lvl) |
|
33 |
- } else { |
|
34 |
- mat = obj |
|
35 |
- levels = as.character(lvl) |
|
36 |
- if(length(levels)!=nrow(mat)) stop("If input is a count matrix, lvl must be a vector of length = nrow(count matrix)") |
|
37 |
- } |
|
38 |
- if(!(out%in%c("MRexperiment","matrix"))){ |
|
39 |
- stop("The variable out must either be 'MRexperiment' or 'matrix'") |
|
40 |
- } |
|
41 |
- |
|
42 |
- nafeatures = is.na(levels) |
|
43 |
- if(length(nafeatures)>0){ |
|
44 |
- if(alternate==FALSE){ |
|
45 |
- levels[nafeatures] = "no_match" |
|
46 |
- } else { |
|
47 |
- levels[nafeatures] = paste("OTU_",rownames(obj)[nafeatures],sep="") |
|
48 |
- } |
|
49 |
- } |
|
50 |
- grps = split(seq_along(levels),levels) |
|
51 |
- |
|
52 |
- newMat = array(NA,dim=c(length(grps),ncol(obj))) |
|
53 |
- for(i in seq_along(grps)){ |
|
54 |
- newMat[i,] = aggfun(mat[grps[[i]],,drop=FALSE]) |
|
55 |
- } |
|
56 |
- rownames(newMat) = names(grps) |
|
57 |
- colnames(newMat) = colnames(obj) |
|
58 |
- if(out=='matrix') return(newMat) |
|
59 |
- if(out=='MRexperiment'){ |
|
60 |
- taxa = data.frame(names(grps)) |
|
61 |
- colnames(taxa) = "Taxa" |
|
62 |
- rownames(taxa) = names(grps) |
|
63 |
- taxa = as(taxa,"AnnotatedDataFrame") |
|
64 |
- if(class(obj)=="MRexperiment"){ |
|
65 |
- pd = phenoData(obj) |
|
66 |
- newObj = newMRexperiment(newMat,featureData=taxa,phenoData=pd) |
|
67 |
- } else { |
|
68 |
- newObj = newMRexperiment(newMat,featureData=taxa) |
|
69 |
- } |
|
70 |
- return(newObj) |
|
71 |
- } |
|
28 |
+aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfun = colSums,sl=1000,feature_order=NULL,out="MRexperiment"){ |
|
29 |
+ if(class(obj)=="MRexperiment"){ |
|
30 |
+ mat = MRcounts(obj,norm=norm,log=log,sl=sl) |
|
31 |
+ if(length(lvl)==1) levels = as.character(fData(obj)[,lvl]) |
|
32 |
+ else levels = as.character(lvl) |
|
33 |
+ } else { |
|
34 |
+ mat = obj |
|
35 |
+ levels = as.character(lvl) |
|
36 |
+ if(length(levels)!=nrow(mat)) stop("If input is a count matrix, lvl must be a vector of length = nrow(count matrix)") |
|
37 |
+ } |
|
38 |
+ if(!(out%in%c("MRexperiment","matrix"))){ |
|
39 |
+ stop("The variable out must either be 'MRexperiment' or 'matrix'") |
|
40 |
+ } |
|
41 |
+ |
|
42 |
+ nafeatures = is.na(levels) |
|
43 |
+ if(length(nafeatures)>0){ |
|
44 |
+ if(alternate==FALSE){ |
|
45 |
+ levels[nafeatures] = "no_match" |
|
46 |
+ } else { |
|
47 |
+ levels[nafeatures] = paste("OTU_",rownames(obj)[nafeatures],sep="") |
|
48 |
+ } |
|
49 |
+ } |
|
50 |
+ grps = split(seq_along(levels),levels) |
|
51 |
+ |
|
52 |
+ newMat = array(NA,dim=c(length(grps),ncol(obj))) |
|
53 |
+ for(i in seq_along(grps)){ |
|
54 |
+ newMat[i,] = aggfun(mat[grps[[i]],,drop=FALSE]) |
|
55 |
+ } |
|
56 |
+ rownames(newMat) = names(grps) |
|
57 |
+ colnames(newMat) = colnames(obj) |
|
58 |
+ if(out=='matrix') return(newMat) |
|
59 |
+ if(out=='MRexperiment'){ |
|
60 |
+ if(is.null(feature_order)){ |
|
61 |
+ feature_order <- colnames(fData(obj)) |
|
62 |
+ } |
|
63 |
+ |
|
64 |
+ taxa = featureData(obj)[match(names(grps), fData(obj)[,lvl]),feature_order[1:which(feature_order == lvl)]] |
|
65 |
+ featureNames(taxa) = names(grps) |
|
66 |
+ |
|
67 |
+ if(class(obj)=="MRexperiment"){ |
|
68 |
+ pd = phenoData(obj) |
|
69 |
+ newObj = newMRexperiment(newMat,featureData=taxa,phenoData=pd) |
|
70 |
+ } else { |
|
71 |
+ newObj = newMRexperiment(newMat,featureData=taxa) |
|
72 |
+ } |
|
73 |
+ return(newObj) |
|
74 |
+ } |
|
72 | 75 |
} |
73 | 76 |
#' @rdname aggregateByTaxonomy |
74 | 77 |
#' @export |
From: jnpaulson <nosson@gmail.com>
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@116423 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,7 +1,6 @@ |
1 |
-#' @name aggregateByTaxonomy |
|
2 |
-#' @title Aggregates a MRexperiment object or counts matrix to a particular level. |
|
1 |
+#' Aggregates a MRexperiment object or counts matrix to a particular level. |
|
3 | 2 |
#' |
4 |
-#' @details Using the featureData information in the MRexperiment, calling aggregateByTaxonomy on a |
|
3 |
+#' Using the featureData information in the MRexperiment, calling aggregateByTaxonomy on a |
|
5 | 4 |
#' MRexperiment and a particular featureData column (i.e. 'genus') will aggregate counts |
6 | 5 |
#' to the desired level using the aggfun function (default colSums). Possible aggfun alternatives |
7 | 6 |
#' include colMeans and colMedians. |
Commit id: d2ab43afc28741e4da5b868a82bb26162bd55ced
many minor tweaks
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@100579 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -63,7 +63,7 @@ aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfu |
63 | 63 |
rownames(taxa) = names(grps) |
64 | 64 |
taxa = as(taxa,"AnnotatedDataFrame") |
65 | 65 |
if(class(obj)=="MRexperiment"){ |
66 |
- pd = as(pData(obj),"AnnotatedDataFrame") |
|
66 |
+ pd = phenoData(obj) |
|
67 | 67 |
newObj = newMRexperiment(newMat,featureData=taxa,phenoData=pd) |
68 | 68 |
} else { |
69 | 69 |
newObj = newMRexperiment(newMat,featureData=taxa) |
Commit information:
Commit id: 5ad5ee28cc745947cf2a79d89658082efe22a3c5
fixing hector's comments
Committed by: nosson
Author Name: nosson
Commit date: 2015-01-21 17:53:50 -0500
Author date: 2015-01-21 17:53:50 -0500
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@98565 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -51,7 +51,7 @@ aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfu |
51 | 51 |
grps = split(seq_along(levels),levels) |
52 | 52 |
|
53 | 53 |
newMat = array(NA,dim=c(length(grps),ncol(obj))) |
54 |
- for(i in 1:length(grps)){ |
|
54 |
+ for(i in seq_along(grps)){ |
|
55 | 55 |
newMat[i,] = aggfun(mat[grps[[i]],,drop=FALSE]) |
56 | 56 |
} |
57 | 57 |
rownames(newMat) = names(grps) |
... | ... |
@@ -76,69 +76,3 @@ 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 |
-} |
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
... | ... |
@@ -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 |
+} |
Commit information:
Commit id: 6aad92462d6f6957c071b5105680fb4426cab3a9
updating man pages/R functions adding modified degrees of freedom
Committed by: nosson
Author Name: nosson
Commit date: 2014-11-29 15:49:59 -0500
Author date: 2014-11-29 15:49:59 -0500
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@97223 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -20,8 +20,10 @@ |
20 | 20 |
#' @export |
21 | 21 |
#' @examples |
22 | 22 |
#' |
23 |
+#' data(mouseData) |
|
24 |
+#' aggregateByTaxonomy(mouseData[1:100,],lvl="class",norm=TRUE,aggfun=colSums) |
|
23 | 25 |
#' # not run |
24 |
-#' # aggregateByTaxonomy(mouseData,lvl="genus",norm=TRUE,aggfun=colMedians) |
|
26 |
+#' # aggregateByTaxonomy(mouseData,lvl="class",norm=TRUE,aggfun=colMedians) |
|
25 | 27 |
#' # aggTax(mouseData,lvl='phylum',norm=FALSE,aggfun=colSums) |
26 | 28 |
#' |
27 | 29 |
aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfun = colSums,sl=1000,out="MRexperiment"){ |
Commit information:
Commit id: bd56b3467846f55b07019b3365efac5dac59123b
Commit message: Merge pull request #11 from nosson/timeseries
Time series method added
Committed by: Joseph N. Paulson
Author Name: Joseph N. Paulson
Commit date: 2014-07-10 16:32:44 -0400
Author date: 2014-07-10 16:32:44 -0400
Commit id: 9ee0799a0e4c8c4d7f8dfadacbfe507495e81301
Commit message: time-series multiple methods
Committed by: Umiacs
Author Name: Umiacs
Commit date: 2014-07-10 16:30:00 -0400
Author date: 2014-07-10 16:30:00 -0400
Commit id: 03f4cc9f4aa9b187e04e154b2bc1fc2c1c138c85
Commit message: Adding plotTimeSeries in vignette
Committed by: Umiacs
Author Name: Umiacs
Commit date: 2014-07-10 13:06:56 -0400
Author date: 2014-07-10 13:06:56 -0400
Commit id: 869b6ab60e92aa21eb4337cc42d490c469b2e155
Commit message: predict on second class + no interval fix
Committed by: Umiacs
Author Name: Umiacs
Commit date: 2014-07-10 12:58:54 -0400
Author date: 2014-07-10 12:58:54 -0400
Commit id: 621f52347cbd252186fcda26783311b3d938ee02
Commit message: Fixed no interval errors
Committed by: Umiacs
Author Name: Umiacs
Commit date: 2014-07-10 12:33:32 -0400
Author date: 2014-07-10 12:33:32 -0400
Commit id: 9822bd6bad1a6492b6fe8e452bd7a42cdb41355c
Commit message: Merge branch 'timeseries' of https://github.com/nosson/metagenomeSeq into timeseries
Committed by: Umiacs
Author Name: Umiacs
Commit date: 2014-07-10 12:21:22 -0400
Author date: 2014-07-10 12:21:22 -0400
Commit id: 8ddc0a0ad6f5b2337446886a4bddfeba392abe38
Commit message: Squashed commit of the following:
commit 4854dd14140e5c4635cefddc9c7afccb1ac1fadf
Author: Umiacs <nosson@gmail.com>
Date: Thu Jul 10 12:18:51 2014 -0400
updating rd, adding plotTimeSeries and fixing fitTimeSeries abs
commit b002aeda586e2ef3dca8abe535edfbc2e0af8da0
Author: unknown <nosson@gmail.com>
Date: Wed Jul 9 10:38:48 2014 -0400
Adding vignette + seealso in
commit 6fc0766ceadc28e43032e8f4a47c08e6b6d66157
Author: nosson <nosson@gmail.com>
Date: Mon Jul 7 16:21:38 2014 -0400
Updating NEWS
commit c7542026ca588b0117effac1a577d7a0d92a29ec
Author: nosson <nosson@gmail.com>
Date: Mon Jul 7 16:19:29 2014 -0400
Updating man pages
commit 92e5e345a2eef4e9d51592c392f3270ea9c5b681
Author: nosson <nosson@gmail.com>
Date: Mon Jul 7 16:04:22 2014 -0400
Fixed build issues due to time series changes
commit 1a1c071a46239a8d7f8d1a468d633b3e4fa91528
Author: nosson <nosson@gmail.com>
Date: Mon Jul 7 15:43:32 2014 -0400
Fixing citation
commit 219a263363260d67bb153a4745d05e4cb5fe378a
Author: nosson <nosson@gmail.com>
Date: Mon Jul 7 15:41:06 2014 -0400
Adding ss-anova functions
Committed by: Umiacs
Author Name: Umiacs
Commit date: 2014-07-10 12:20:57 -0400
Author date: 2014-07-10 12:20:57 -0400
Commit id: 4854dd14140e5c4635cefddc9c7afccb1ac1fadf
Commit message: updating rd, adding plotTimeSeries and fixing fitTimeSeries abs
Committed by: Umiacs
Author Name: Umiacs
Commit date: 2014-07-10 12:18:51 -0400
Author date: 2014-07-10 12:18:51 -0400
Commit id: b002aeda586e2ef3dca8abe535edfbc2e0af8da0
Commit message: Adding vignette + seealso in
Committed by: unknown
Author Name: unknown
Commit date: 2014-07-09 10:38:48 -0400
Author date: 2014-07-09 10:38:48 -0400
Commit id: 6fc0766ceadc28e43032e8f4a47c08e6b6d66157
Commit message: Updating NEWS
Committed by: nosson
Author Name: nosson
Commit date: 2014-07-07 16:21:38 -0400
Author date: 2014-07-07 16:21:38 -0400
Commit id: c7542026ca588b0117effac1a577d7a0d92a29ec
Commit message: Updating man pages
Committed by: nosson
Author Name: nosson
Commit date: 2014-07-07 16:19:29 -0400
Author date: 2014-07-07 16:19:29 -0400
Commit id: 92e5e345a2eef4e9d51592c392f3270ea9c5b681
Commit message: Fixed build issues due to time series changes
Committed by: nosson
Author Name: nosson
Commit date: 2014-07-07 16:04:22 -0400
Author date: 2014-07-07 16:04:22 -0400
Commit id: 1a1c071a46239a8d7f8d1a468d633b3e4fa91528
Commit message: Fixing citation
Committed by: nosson
Author Name: nosson
Commit date: 2014-07-07 15:43:32 -0400
Author date: 2014-07-07 15:43:32 -0400
Commit id: 219a263363260d67bb153a4745d05e4cb5fe378a
Commit message: Adding ss-anova functions
Committed by: nosson
Author Name: nosson
Commit date: 2014-07-07 15:41:06 -0400
Author date: 2014-07-07 15:41:06 -0400
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@92401 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,7 +1,7 @@ |
1 | 1 |
#' @name aggregateByTaxonomy |
2 | 2 |
#' @title Aggregates a MRexperiment object or counts matrix to a particular level. |
3 | 3 |
#' |
4 |
-#' Using the featureData information in the MRexperiment, calling aggregateByTaxonomy on a |
|
4 |
+#' @details Using the featureData information in the MRexperiment, calling aggregateByTaxonomy on a |
|
5 | 5 |
#' MRexperiment and a particular featureData column (i.e. 'genus') will aggregate counts |
6 | 6 |
#' to the desired level using the aggfun function (default colSums). Possible aggfun alternatives |
7 | 7 |
#' include colMeans and colMedians. |
... | ... |
@@ -73,4 +73,4 @@ aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfu |
73 | 73 |
#' @export |
74 | 74 |
aggTax<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfun = colSums,sl=1000,out='MRexperiment'){ |
75 | 75 |
aggregateByTaxonomy(obj,lvl,alternate=alternate,norm=norm,log=log,aggfun = aggfun,sl=sl,out=out) |
76 |
-} |
|
77 | 76 |
\ No newline at end of file |
77 |
+} |
Commit information:
Commit id: 47218497f29051f3811d821f86b3e16ff2c1a544
Commit message: aggTax tweak
Committed by: nosson
Author Name: nosson
Commit date: 2014-07-01 01:16:40 -0400
Author date: 2014-07-01 01:16:40 -0400
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@92045 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -27,7 +27,8 @@ |
27 | 27 |
aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfun = colSums,sl=1000,out="MRexperiment"){ |
28 | 28 |
if(class(obj)=="MRexperiment"){ |
29 | 29 |
mat = MRcounts(obj,norm=norm,log=log,sl=sl) |
30 |
- levels = as.character(fData(obj)[,lvl]) |
|
30 |
+ if(length(lvl)==1) levels = as.character(fData(obj)[,lvl]) |
|
31 |
+ else levels = as.character(lvl) |
|
31 | 32 |
} else { |
32 | 33 |
mat = obj |
33 | 34 |
levels = as.character(lvl) |
... | ... |
@@ -65,8 +66,6 @@ aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfu |
65 | 66 |
} else { |
66 | 67 |
newObj = newMRexperiment(newMat,featureData=taxa) |
67 | 68 |
} |
68 |
- warning("\n\nThe output here are aggregated counts.\n |
|
69 |
- Check default parameters for all metagenomeSeq functions and consider normalization.") |
|
70 | 69 |
return(newObj) |
71 | 70 |
} |
72 | 71 |
} |
Commit information:
Commit id: eb4c389c4d932922d89f34321e58c9aa74f72e14
Commit message:
Updating aggregateByTaxonomy and defaults for the fun.
Committed by nosson <nosson at gmail.com>
Commit date: 2014-03-09T23:17:57-04:00
From: Bioconductor Git-SVN Bridge <bioc-sync@bioconductor.org>
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@87245 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,5 +1,5 @@ |
1 | 1 |
#' @name aggregateByTaxonomy |
2 |
-#' @title Aggregates a MRexperiment object by a particular taxonomic level. |
|
2 |
+#' @title Aggregates a MRexperiment object or counts matrix to a particular level. |
|
3 | 3 |
#' |
4 | 4 |
#' Using the featureData information in the MRexperiment, calling aggregateByTaxonomy on a |
5 | 5 |
#' MRexperiment and a particular featureData column (i.e. 'genus') will aggregate counts |
... | ... |
@@ -22,8 +22,9 @@ |
22 | 22 |
#' |
23 | 23 |
#' # not run |
24 | 24 |
#' # aggregateByTaxonomy(mouseData,lvl="genus",norm=TRUE,aggfun=colMedians) |
25 |
+#' # aggTax(mouseData,lvl='phylum',norm=FALSE,aggfun=colSums) |
|
25 | 26 |
#' |
26 |
-aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=TRUE,log=FALSE,aggfun = colSums,sl=1000,out="MRexperiment"){ |
|
27 |
+aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfun = colSums,sl=1000,out="MRexperiment"){ |
|
27 | 28 |
if(class(obj)=="MRexperiment"){ |
28 | 29 |
mat = MRcounts(obj,norm=norm,log=log,sl=sl) |
29 | 30 |
levels = as.character(fData(obj)[,lvl]) |
... | ... |
@@ -64,13 +65,13 @@ aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=TRUE,log=FALSE,aggfun |
64 | 65 |
} else { |
65 | 66 |
newObj = newMRexperiment(newMat,featureData=taxa) |
66 | 67 |
} |
67 |
- warning("\n\nThe output here are aggregated (normalized?) counts.\n |
|
68 |
- Check default parameters for all metagenomeSeq functions so as not to renormalize.") |
|
68 |
+ warning("\n\nThe output here are aggregated counts.\n |
|
69 |
+ Check default parameters for all metagenomeSeq functions and consider normalization.") |
|
69 | 70 |
return(newObj) |
70 | 71 |
} |
71 | 72 |
} |
72 | 73 |
#' @rdname aggregateByTaxonomy |
73 | 74 |
#' @export |
74 |
-aggTax<-function(obj,lvl,alternate=FALSE,norm=TRUE,log=FALSE,aggfun = colSums,sl=1000,out='MRexperiment'){ |
|
75 |
+aggTax<-function(obj,lvl,alternate=FALSE,norm=FALSE,log=FALSE,aggfun = colSums,sl=1000,out='MRexperiment'){ |
|
75 | 76 |
aggregateByTaxonomy(obj,lvl,alternate=alternate,norm=norm,log=log,aggfun = aggfun,sl=sl,out=out) |
76 | 77 |
} |
77 | 78 |
\ No newline at end of file |
Commit information:
Commit id: 03e4c65352e9ec7e037d948d0741e50891ea0604
Commit message:
Making aggregateByTaxonomy/aggTax more versatile
Committed by nosson <nosson at gmail.com>
Commit date: 2014-03-09T22:55:44-04:00
Commit id: f61b99590946fdcf9b7c0e7c38f9b6276a288f9a
Commit message:
Merge branch 'master' of https://github.com/nosson/metagenomeSeq
Committed by nosson <nosson at gmail.com>
Commit date: 2014-03-09T22:55:48-04:00
From: Bioconductor Git-SVN Bridge <bioc-sync@bioconductor.org>
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@87243 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -6,13 +6,14 @@ |
6 | 6 |
#' to the desired level using the aggfun function (default colSums). Possible aggfun alternatives |
7 | 7 |
#' include colMeans and colMedians. |
8 | 8 |
#' |
9 |
-#' @param obj A MRexperiment object. |
|
10 |
-#' @param lvl featureData column name from the MRexperiment object. |
|
9 |
+#' @param obj A MRexperiment object or count matrix. |
|
10 |
+#' @param lvl featureData column name from the MRexperiment object or if count matrix object a vector of labels. |
|
11 | 11 |
#' @param alternate Use the rowname for undefined OTUs instead of aggregating to "no_match". |
12 | 12 |
#' @param norm Whether to aggregate normalized counts or not. |
13 | 13 |
#' @param log Whether or not to log2 transform the counts - if MRexperiment object. |
14 | 14 |
#' @param aggfun Aggregation function. |
15 | 15 |
#' @param sl scaling value, default is 1000. |
16 |
+#' @param out Either 'MRexperiment' or 'matrix' |
|
16 | 17 |
#' @return An aggregated count matrix. |
17 | 18 |
#' @aliases aggTax |
18 | 19 |
#' @rdname aggregateByTaxonomy |
... | ... |
@@ -22,22 +23,27 @@ |
22 | 23 |
#' # not run |
23 | 24 |
#' # aggregateByTaxonomy(mouseData,lvl="genus",norm=TRUE,aggfun=colMedians) |
24 | 25 |
#' |
25 |
-aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=TRUE,log=FALSE,aggfun = colSums,sl=1000){ |
|
26 |
+aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=TRUE,log=FALSE,aggfun = colSums,sl=1000,out="MRexperiment"){ |
|
26 | 27 |
if(class(obj)=="MRexperiment"){ |
27 | 28 |
mat = MRcounts(obj,norm=norm,log=log,sl=sl) |
28 |
- } else { |
|
29 |
- stop("Object needs to be a MRexperiment object. If it's a matrix, see aggregateM.") |
|
30 |
- } |
|
31 |
- |
|
32 |
- levels = as.character(fData(obj)[,lvl]) |
|
33 |
- nafeatures = is.na(levels) |
|
34 |
- if(length(nafeatures)>0){ |
|
35 |
- if(alternate==FALSE){ |
|
36 |
- levels[nafeatures] = "no_match" |
|
37 |
- } else { |
|
38 |
- levels[nafeatures] = paste("OTU_",rownames(obj)[nafeatures],sep="") |
|
39 |
- } |
|
40 |
- } |
|
29 |
+ levels = as.character(fData(obj)[,lvl]) |
|
30 |
+ } else { |
|
31 |
+ mat = obj |
|
32 |
+ levels = as.character(lvl) |
|
33 |
+ if(length(levels)!=nrow(mat)) stop("If input is a count matrix, lvl must be a vector of length = nrow(count matrix)") |
|
34 |
+ } |
|
35 |
+ if(!(out%in%c("MRexperiment","matrix"))){ |
|
36 |
+ stop("The variable out must either be 'MRexperiment' or 'matrix'") |
|
37 |
+ } |
|
38 |
+ |
|
39 |
+ nafeatures = is.na(levels) |
|
40 |
+ if(length(nafeatures)>0){ |
|
41 |
+ if(alternate==FALSE){ |
|
42 |
+ levels[nafeatures] = "no_match" |
|
43 |
+ } else { |
|
44 |
+ levels[nafeatures] = paste("OTU_",rownames(obj)[nafeatures],sep="") |
|
45 |
+ } |
|
46 |
+ } |
|
41 | 47 |
grps = split(seq_along(levels),levels) |
42 | 48 |
|
43 | 49 |
newMat = array(NA,dim=c(length(grps),ncol(obj))) |
... | ... |
@@ -45,11 +51,26 @@ aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=TRUE,log=FALSE,aggfun |
45 | 51 |
newMat[i,] = aggfun(mat[grps[[i]],,drop=FALSE]) |
46 | 52 |
} |
47 | 53 |
rownames(newMat) = names(grps) |
48 |
- colnames(newMat) = sampleNames(obj) |
|
49 |
- newMat |
|
54 |
+ colnames(newMat) = colnames(obj) |
|
55 |
+ if(out=='matrix') return(newMat) |
|
56 |
+ if(out=='MRexperiment'){ |
|
57 |
+ taxa = data.frame(names(grps)) |
|
58 |
+ colnames(taxa) = "Taxa" |
|
59 |
+ rownames(taxa) = names(grps) |
|
60 |
+ taxa = as(taxa,"AnnotatedDataFrame") |
|
61 |
+ if(class(obj)=="MRexperiment"){ |
|
62 |
+ pd = as(pData(obj),"AnnotatedDataFrame") |
|
63 |
+ newObj = newMRexperiment(newMat,featureData=taxa,phenoData=pd) |
|
64 |
+ } else { |
|
65 |
+ newObj = newMRexperiment(newMat,featureData=taxa) |
|
66 |
+ } |
|
67 |
+ warning("\n\nThe output here are aggregated (normalized?) counts.\n |
|
68 |
+ Check default parameters for all metagenomeSeq functions so as not to renormalize.") |
|
69 |
+ return(newObj) |
|
70 |
+ } |
|
50 | 71 |
} |
51 | 72 |
#' @rdname aggregateByTaxonomy |
52 | 73 |
#' @export |
53 |
-aggTax<-function(obj,lvl,alternate=FALSE,norm=TRUE,log=FALSE,aggfun = colSums,sl=1000){ |
|
54 |
- aggregateByTaxonomy(obj,lvl,alternate=alternate,norm=norm,log=log,aggfun = aggfun,sl=sl) |
|
74 |
+aggTax<-function(obj,lvl,alternate=FALSE,norm=TRUE,log=FALSE,aggfun = colSums,sl=1000,out='MRexperiment'){ |
|
75 |
+ aggregateByTaxonomy(obj,lvl,alternate=alternate,norm=norm,log=log,aggfun = aggfun,sl=sl,out=out) |
|
55 | 76 |
} |
56 | 77 |
\ No newline at end of file |
Commit information:
Commit id: 13226f5c172a2e5e54a61e521a57d13b5ef50863
Commit message:
Added sl param to aggTax
Committed by nosson <nosson at gmail.com>
Commit date: 2014-02-28T12:16:03-08:00
From: Bioconductor Git-SVN Bridge <bioc-sync@bioconductor.org>
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@86937 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -12,6 +12,7 @@ |
12 | 12 |
#' @param norm Whether to aggregate normalized counts or not. |
13 | 13 |
#' @param log Whether or not to log2 transform the counts - if MRexperiment object. |
14 | 14 |
#' @param aggfun Aggregation function. |
15 |
+#' @param sl scaling value, default is 1000. |
|
15 | 16 |
#' @return An aggregated count matrix. |
16 | 17 |
#' @aliases aggTax |
17 | 18 |
#' @rdname aggregateByTaxonomy |
... | ... |
@@ -21,9 +22,9 @@ |
21 | 22 |
#' # not run |
22 | 23 |
#' # aggregateByTaxonomy(mouseData,lvl="genus",norm=TRUE,aggfun=colMedians) |
23 | 24 |
#' |
24 |
-aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=TRUE,log=FALSE,aggfun = colSums){ |
|
25 |
+aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=TRUE,log=FALSE,aggfun = colSums,sl=1000){ |
|
25 | 26 |
if(class(obj)=="MRexperiment"){ |
26 |
- mat = MRcounts(obj,norm=norm,log=log) |
|
27 |
+ mat = MRcounts(obj,norm=norm,log=log,sl=sl) |
|
27 | 28 |
} else { |
28 | 29 |
stop("Object needs to be a MRexperiment object. If it's a matrix, see aggregateM.") |
29 | 30 |
} |
... | ... |
@@ -49,6 +50,6 @@ aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=TRUE,log=FALSE,aggfun |
49 | 50 |
} |
50 | 51 |
#' @rdname aggregateByTaxonomy |
51 | 52 |
#' @export |
52 |
-aggTax<-function(obj,lvl,alternate=FALSE,norm=TRUE,log=FALSE,aggfun = colSums){ |
|
53 |
- aggregateByTaxonomy(obj,lvl,alternate=alternate,norm=norm,log=log,aggfun = aggfun) |
|
53 |
+aggTax<-function(obj,lvl,alternate=FALSE,norm=TRUE,log=FALSE,aggfun = colSums,sl=1000){ |
|
54 |
+ aggregateByTaxonomy(obj,lvl,alternate=alternate,norm=norm,log=log,aggfun = aggfun,sl=sl) |
|
54 | 55 |
} |
55 | 56 |
\ No newline at end of file |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@85736 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -10,6 +10,7 @@ |
10 | 10 |
#' @param lvl featureData column name from the MRexperiment object. |
11 | 11 |
#' @param alternate Use the rowname for undefined OTUs instead of aggregating to "no_match". |
12 | 12 |
#' @param norm Whether to aggregate normalized counts or not. |
13 |
+#' @param log Whether or not to log2 transform the counts - if MRexperiment object. |
|
13 | 14 |
#' @param aggfun Aggregation function. |
14 | 15 |
#' @return An aggregated count matrix. |
15 | 16 |
#' @aliases aggTax |
... | ... |
@@ -20,9 +21,9 @@ |
20 | 21 |
#' # not run |
21 | 22 |
#' # aggregateByTaxonomy(mouseData,lvl="genus",norm=TRUE,aggfun=colMedians) |
22 | 23 |
#' |
23 |
-aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=TRUE,aggfun = colSums){ |
|
24 |
+aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=TRUE,log=FALSE,aggfun = colSums){ |
|
24 | 25 |
if(class(obj)=="MRexperiment"){ |
25 |
- mat = MRcounts(obj,norm=norm,log=FALSE) |
|
26 |
+ mat = MRcounts(obj,norm=norm,log=log) |
|
26 | 27 |
} else { |
27 | 28 |
stop("Object needs to be a MRexperiment object. If it's a matrix, see aggregateM.") |
28 | 29 |
} |
... | ... |
@@ -48,6 +49,6 @@ aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=TRUE,aggfun = colSums |
48 | 49 |
} |
49 | 50 |
#' @rdname aggregateByTaxonomy |
50 | 51 |
#' @export |
51 |
-aggTax<-function(obj,lvl,alternate=FALSE,norm=TRUE,aggfun = colSums){ |
|
52 |
- aggregateByTaxonomy(obj,lvl,alternate=alternate,norm=norm,aggfun = aggfun) |
|
52 |
+aggTax<-function(obj,lvl,alternate=FALSE,norm=TRUE,log=FALSE,aggfun = colSums){ |
|
53 |
+ aggregateByTaxonomy(obj,lvl,alternate=alternate,norm=norm,log=log,aggfun = aggfun) |
|
53 | 54 |
} |
54 | 55 |
\ No newline at end of file |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@84540 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -3,12 +3,12 @@ |
3 | 3 |
#' |
4 | 4 |
#' Using the featureData information in the MRexperiment, calling aggregateByTaxonomy on a |
5 | 5 |
#' MRexperiment and a particular featureData column (i.e. 'genus') will aggregate counts |
6 |
-#' to the desired level by with the aggfun function (default colSums). Possible aggfun alternatives |
|
6 |
+#' to the desired level using the aggfun function (default colSums). Possible aggfun alternatives |
|
7 | 7 |
#' include colMeans and colMedians. |
8 | 8 |
#' |
9 | 9 |
#' @param obj A MRexperiment object. |
10 | 10 |
#' @param lvl featureData column name from the MRexperiment object. |
11 |
-#' @param alternatelabel Use the rowname for undefined OTUs instead of aggregating to others. |
|
11 |
+#' @param alternate Use the rowname for undefined OTUs instead of aggregating to "no_match". |
|
12 | 12 |
#' @param norm Whether to aggregate normalized counts or not. |
13 | 13 |
#' @param aggfun Aggregation function. |
14 | 14 |
#' @return An aggregated count matrix. |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@84391 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -8,6 +8,7 @@ |
8 | 8 |
#' |
9 | 9 |
#' @param obj A MRexperiment object. |
10 | 10 |
#' @param lvl featureData column name from the MRexperiment object. |
11 |
+#' @param alternatelabel Use the rowname for undefined OTUs instead of aggregating to others. |
|
11 | 12 |
#' @param norm Whether to aggregate normalized counts or not. |
12 | 13 |
#' @param aggfun Aggregation function. |
13 | 14 |
#' @return An aggregated count matrix. |
... | ... |
@@ -19,14 +20,22 @@ |
19 | 20 |
#' # not run |
20 | 21 |
#' # aggregateByTaxonomy(mouseData,lvl="genus",norm=TRUE,aggfun=colMedians) |
21 | 22 |
#' |
22 |
-aggregateByTaxonomy<-function(obj,lvl,norm=TRUE,aggfun = colSums){ |
|
23 |
+aggregateByTaxonomy<-function(obj,lvl,alternate=FALSE,norm=TRUE,aggfun = colSums){ |
|
23 | 24 |
if(class(obj)=="MRexperiment"){ |
24 | 25 |
mat = MRcounts(obj,norm=norm,log=FALSE) |
25 | 26 |
} else { |
26 | 27 |
stop("Object needs to be a MRexperiment object. If it's a matrix, see aggregateM.") |
27 | 28 |
} |
28 | 29 |
|
29 |
- levels = fData(obj)[,lvl] |
|
30 |
+ levels = as.character(fData(obj)[,lvl]) |
|
31 |
+ nafeatures = is.na(levels) |
|
32 |
+ if(length(nafeatures)>0){ |
|
33 |
+ if(alternate==FALSE){ |
|
34 |
+ levels[nafeatures] = "no_match" |
|
35 |
+ } else { |
|
36 |
+ levels[nafeatures] = paste("OTU_",rownames(obj)[nafeatures],sep="") |
|
37 |
+ } |
|
38 |
+ } |
|
30 | 39 |
grps = split(seq_along(levels),levels) |
31 | 40 |
|
32 | 41 |
newMat = array(NA,dim=c(length(grps),ncol(obj))) |
... | ... |
@@ -39,6 +48,6 @@ aggregateByTaxonomy<-function(obj,lvl,norm=TRUE,aggfun = colSums){ |
39 | 48 |
} |
40 | 49 |
#' @rdname aggregateByTaxonomy |
41 | 50 |
#' @export |
42 |
-aggTax<-function(obj,lvl,norm=TRUE,aggfun = colSums){ |
|
43 |
- aggregateByTaxonomy(obj,lvl,norm=TRUE,aggfun = colSums) |
|
51 |
+aggTax<-function(obj,lvl,alternate=FALSE,norm=TRUE,aggfun = colSums){ |
|
52 |
+ aggregateByTaxonomy(obj,lvl,alternate=alternate,norm=norm,aggfun = aggfun) |
|
44 | 53 |
} |
45 | 54 |
\ No newline at end of file |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@84100 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -20,10 +20,10 @@ |
20 | 20 |
#' # aggregateByTaxonomy(mouseData,lvl="genus",norm=TRUE,aggfun=colMedians) |
21 | 21 |
#' |
22 | 22 |
aggregateByTaxonomy<-function(obj,lvl,norm=TRUE,aggfun = colSums){ |
23 |
- if(class(obj)=="MRexperiment"){ |
|
24 |
- mat = MRcounts(obj,norm=norm,log=FALSE) |
|
23 |
+ if(class(obj)=="MRexperiment"){ |
|
24 |
+ mat = MRcounts(obj,norm=norm,log=FALSE) |
|
25 | 25 |
} else { |
26 |
- stop("Object needs to be a MRexperiment object. If it's a matrix, see aggregateM.") |
|
26 |
+ stop("Object needs to be a MRexperiment object. If it's a matrix, see aggregateM.") |
|
27 | 27 |
} |
28 | 28 |
|
29 | 29 |
levels = fData(obj)[,lvl] |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@84095 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,4 +1,5 @@ |
1 |
-#' Aggregates a MRexperiment object by a particular taxonomic level. |
|
1 |
+#' @name aggregateByTaxonomy |
|
2 |
+#' @title Aggregates a MRexperiment object by a particular taxonomic level. |
|
2 | 3 |
#' |
3 | 4 |
#' Using the featureData information in the MRexperiment, calling aggregateByTaxonomy on a |
4 | 5 |
#' MRexperiment and a particular featureData column (i.e. 'genus') will aggregate counts |
... | ... |
@@ -10,7 +11,8 @@ |
10 | 11 |
#' @param norm Whether to aggregate normalized counts or not. |
11 | 12 |
#' @param aggfun Aggregation function. |
12 | 13 |
#' @return An aggregated count matrix. |
13 |
-#' @aliases aggregateTax, aggTax |
|
14 |
+#' @aliases aggTax |
|
15 |
+#' @rdname aggregateByTaxonomy |
|
14 | 16 |
#' @export |
15 | 17 |
#' @examples |
16 | 18 |
#' |
... | ... |
@@ -34,4 +36,9 @@ aggregateByTaxonomy<-function(obj,lvl,norm=TRUE,aggfun = colSums){ |
34 | 36 |
rownames(newMat) = names(grps) |
35 | 37 |
colnames(newMat) = sampleNames(obj) |
36 | 38 |
newMat |
39 |
+} |
|
40 |
+#' @rdname aggregateByTaxonomy |
|
41 |
+#' @export |
|
42 |
+aggTax<-function(obj,lvl,norm=TRUE,aggfun = colSums){ |
|
43 |
+ aggregateByTaxonomy(obj,lvl,norm=TRUE,aggfun = colSums) |
|
37 | 44 |
} |
38 | 45 |
\ No newline at end of file |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@84090 bc3139a8-67e5-0310-9ffc-ced21a209358
1 | 1 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,37 @@ |
1 |
+#' Aggregates a MRexperiment object by a particular taxonomic level. |
|
2 |
+#' |
|
3 |
+#' Using the featureData information in the MRexperiment, calling aggregateByTaxonomy on a |
|
4 |
+#' MRexperiment and a particular featureData column (i.e. 'genus') will aggregate counts |
|
5 |
+#' to the desired level by with the aggfun function (default colSums). Possible aggfun alternatives |
|
6 |
+#' include colMeans and colMedians. |
|
7 |
+#' |
|
8 |
+#' @param obj A MRexperiment object. |
|
9 |
+#' @param lvl featureData column name from the MRexperiment object. |
|
10 |
+#' @param norm Whether to aggregate normalized counts or not. |
|
11 |
+#' @param aggfun Aggregation function. |
|
12 |
+#' @return An aggregated count matrix. |
|
13 |
+#' @aliases aggregateTax, aggTax |
|
14 |
+#' @export |
|
15 |
+#' @examples |
|
16 |
+#' |
|
17 |
+#' # not run |
|
18 |
+#' # aggregateByTaxonomy(mouseData,lvl="genus",norm=TRUE,aggfun=colMedians) |
|
19 |
+#' |
|
20 |
+aggregateByTaxonomy<-function(obj,lvl,norm=TRUE,aggfun = colSums){ |
|
21 |
+ if(class(obj)=="MRexperiment"){ |
|
22 |
+ mat = MRcounts(obj,norm=norm,log=FALSE) |
|
23 |
+ } else { |
|
24 |
+ stop("Object needs to be a MRexperiment object. If it's a matrix, see aggregateM.") |
|
25 |
+ } |
|
26 |
+ |
|
27 |
+ levels = fData(obj)[,lvl] |
|
28 |
+ grps = split(seq_along(levels),levels) |
|
29 |
+ |
|
30 |
+ newMat = array(NA,dim=c(length(grps),ncol(obj))) |
|
31 |
+ for(i in 1:length(grps)){ |
|
32 |
+ newMat[i,] = aggfun(mat[grps[[i]],,drop=FALSE]) |
|
33 |
+ } |
|
34 |
+ rownames(newMat) = names(grps) |
|
35 |
+ colnames(newMat) = sampleNames(obj) |
|
36 |
+ newMat |
|
37 |
+} |
|
0 | 38 |
\ No newline at end of file |