also created fitFeatureModelResults and fitZigResults classes
... | ... |
@@ -46,21 +46,21 @@ |
46 | 46 |
#' fit = fitFeatureModel(obj = lungTrim,mod=mod) |
47 | 47 |
#' head(MRtable(fit)) |
48 | 48 |
#' |
49 |
-MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa, |
|
49 |
+MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj@taxa, |
|
50 | 50 |
uniqueNames=FALSE,adjustMethod="fdr",group=0,eff=0,numberEff=FALSE,ncounts=0,file=NULL){ |
51 | 51 |
|
52 |
- if(length(grep("fitFeatureModel",obj$call))){ |
|
53 |
- groups = factor(obj$design[,by]) |
|
52 |
+ if(length(grep("fitFeatureModel",obj@call))){ |
|
53 |
+ groups = factor(obj@design[,by]) |
|
54 | 54 |
by = "logFC"; coef = 1:2; |
55 |
- tb = data.frame(logFC=obj$fitZeroLogNormal$logFC,se=obj$fitZeroLogNormal$se) |
|
56 |
- p = obj$pvalues |
|
55 |
+ tb = data.frame(logFC=obj@fitZeroLogNormal$logFC,se=obj@fitZeroLogNormal$se) |
|
56 |
+ p = obj@pvalues |
|
57 | 57 |
} else { |
58 |
- tb = obj$fit$coefficients |
|
58 |
+ tb = obj@fit$coefficients |
|
59 | 59 |
if(is.null(coef)){ |
60 | 60 |
coef = 1:ncol(tb) |
61 | 61 |
} |
62 |
- p=obj$eb$p.value[,by] |
|
63 |
- groups = factor(obj$fit$design[,by]) |
|
62 |
+ p=obj@eb$p.value[,by] |
|
63 |
+ groups = factor(obj@fit$design[,by]) |
|
64 | 64 |
if(eff>0){ |
65 | 65 |
effectiveSamples = calculateEffectiveSamples(obj) |
66 | 66 |
if(numberEff == FALSE){ |
... | ... |
@@ -79,7 +79,7 @@ MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa, |
79 | 79 |
} |
80 | 80 |
} |
81 | 81 |
padj = p.adjust(p,method=adjustMethod) |
82 |
- cnts = obj$counts |
|
82 |
+ cnts = obj@counts |
|
83 | 83 |
posIndices = cnts>0 |
84 | 84 |
|
85 | 85 |
np0 = rowSums(posIndices[,groups==0]) |
tweak table functions (removed invisible call)
From: hcorrada <hcorrada@gmail.com>
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@121794 bc3139a8-67e5-0310-9ffc-ced21a209358
From: jnpaulson <nosson@gmail.com>
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@111515 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -105,7 +105,7 @@ MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa, |
105 | 105 |
np=rowSums(cbind(np0,np1)) |
106 | 106 |
valid = intersect(valid,which(np>=ncounts)) |
107 | 107 |
} |
108 |
- srt = srt[which(srt%in%valid)][1:number] |
|
108 |
+ srt = srt[which(srt%in%valid)][1:min(number,nrow(tb))] |
|
109 | 109 |
|
110 | 110 |
mat = cbind(np0,np1) |
111 | 111 |
mat = cbind(mat,nc0) |
Commit id: e8c7750ff220036cb51ace6dc52af1ecc7dc3d47
speeding up examples
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@103678 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -30,24 +30,22 @@ |
30 | 30 |
#' @param file Name of file, including location, to save the table. |
31 | 31 |
#' @return Table of the top-ranked features determined by the linear fit's |
32 | 32 |
#' coefficient. |
33 |
-#' @seealso \code{\link{fitZig}} \code{\link{fitFeatureModel}} \code{\link{MRcoefs}} |
|
33 |
+#' @seealso \code{\link{fitZig}} \code{\link{fitFeatureModel}} \code{\link{MRcoefs}} \code{\link{MRfulltable}} |
|
34 | 34 |
#' @examples |
35 | 35 |
#' |
36 | 36 |
#' data(lungData) |
37 | 37 |
#' k = grep("Extraction.Control",pData(lungData)$SampleType) |
38 | 38 |
#' lungTrim = lungData[,-k] |
39 |
-#' k = which(rowSums(MRcounts(lungTrim)>0)<10) |
|
40 |
-#' lungTrim = lungTrim[-k,] |
|
41 |
-#' cumNorm(lungTrim) |
|
39 |
+#' lungTrim=filterData(lungTrim,present=30) |
|
40 |
+#' lungTrim=cumNorm(lungTrim,p=0.5) |
|
42 | 41 |
#' smokingStatus = pData(lungTrim)$SmokingStatus |
43 | 42 |
#' mod = model.matrix(~smokingStatus) |
44 |
-#' settings = zigControl(maxit=1,verbose=FALSE) |
|
45 |
-#' fit = fitZig(obj = lungTrim,mod=mod,control=settings) |
|
43 |
+#' fit = fitZig(obj = lungTrim,mod=mod) |
|
46 | 44 |
#' head(MRtable(fit)) |
47 | 45 |
#' #### |
48 | 46 |
#' fit = fitFeatureModel(obj = lungTrim,mod=mod) |
49 | 47 |
#' head(MRtable(fit)) |
50 |
-#' |
|
48 |
+#' |
|
51 | 49 |
MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa, |
52 | 50 |
uniqueNames=FALSE,adjustMethod="fdr",group=0,eff=0,numberEff=FALSE,ncounts=0,file=NULL){ |
53 | 51 |
|
Commit id: f228152638ce533024128de813d8b2855f26f34b
modifying MRfulltable/table/coefs to accept fitFeatureModel as well
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@103677 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -8,8 +8,7 @@ |
8 | 8 |
#' ensure significant features called are moderately present. |
9 | 9 |
#' |
10 | 10 |
#' |
11 |
-#' @param obj A list containing the linear model fit produced by lmFit through |
|
12 |
-#' fitZig. |
|
11 |
+#' @param obj Output of fitFeatureModel or fitZig. |
|
13 | 12 |
#' @param by Column number or column name specifying which coefficient or |
14 | 13 |
#' contrast of the linear model is of interest. |
15 | 14 |
#' @param coef Column number(s) or column name(s) specifying which coefficient |
... | ... |
@@ -17,7 +16,7 @@ |
17 | 16 |
#' @param number The number of bacterial features to pick out. |
18 | 17 |
#' @param taxa Taxa list. |
19 | 18 |
#' @param uniqueNames Number the various taxa. |
20 |
-#' @param adjust.method Method to adjust p-values by. Default is "FDR". Options |
|
19 |
+#' @param adjustMethod Method to adjust p-values by. Default is "FDR". Options |
|
21 | 20 |
#' include "holm", "hochberg", "hommel", "bonferroni", "BH", "BY", "fdr", |
22 | 21 |
#' "none". See \code{\link{p.adjust}} for more details. |
23 | 22 |
#' @param group One of five choices, 0,1,2,3,4. 0: the sort is ordered by a |
... | ... |
@@ -27,11 +26,11 @@ |
27 | 26 |
#' of the coefficient fit in increasing order. 4: no sorting. |
28 | 27 |
#' @param eff Filter features to have at least a "eff" quantile or number of effective samples. |
29 | 28 |
#' @param numberEff Boolean, whether eff should represent quantile (default/FALSE) or number. |
30 |
-#' @param counts Filter features to have at least 'counts' of counts. |
|
29 |
+#' @param ncounts Filter features to have at least 'counts' of counts. |
|
31 | 30 |
#' @param file Name of file, including location, to save the table. |
32 | 31 |
#' @return Table of the top-ranked features determined by the linear fit's |
33 | 32 |
#' coefficient. |
34 |
-#' @seealso \code{\link{fitZig}} \code{\link{MRcoefs}} |
|
33 |
+#' @seealso \code{\link{fitZig}} \code{\link{fitFeatureModel}} \code{\link{MRcoefs}} |
|
35 | 34 |
#' @examples |
36 | 35 |
#' |
37 | 36 |
#' data(lungData) |
... | ... |
@@ -45,32 +44,51 @@ |
45 | 44 |
#' settings = zigControl(maxit=1,verbose=FALSE) |
46 | 45 |
#' fit = fitZig(obj = lungTrim,mod=mod,control=settings) |
47 | 46 |
#' head(MRtable(fit)) |
47 |
+#' #### |
|
48 |
+#' fit = fitFeatureModel(obj = lungTrim,mod=mod) |
|
49 |
+#' head(MRtable(fit)) |
|
48 | 50 |
#' |
49 |
-MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,adjust.method="fdr",group=0,eff=0,numberEff=FALSE,counts=0,file=NULL){ |
|
50 |
- tb = obj$fit$coefficients |
|
51 |
- tx = as.character(taxa); |
|
51 |
+MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa, |
|
52 |
+ uniqueNames=FALSE,adjustMethod="fdr",group=0,eff=0,numberEff=FALSE,ncounts=0,file=NULL){ |
|
53 |
+ |
|
54 |
+ if(length(grep("fitFeatureModel",obj$call))){ |
|
55 |
+ groups = factor(obj$design[,by]) |
|
56 |
+ by = "logFC"; coef = 1:2; |
|
57 |
+ tb = data.frame(logFC=obj$fitZeroLogNormal$logFC,se=obj$fitZeroLogNormal$se) |
|
58 |
+ p = obj$pvalues |
|
59 |
+ } else { |
|
60 |
+ tb = obj$fit$coefficients |
|
61 |
+ if(is.null(coef)){ |
|
62 |
+ coef = 1:ncol(tb) |
|
63 |
+ } |
|
64 |
+ p=obj$eb$p.value[,by] |
|
65 |
+ groups = factor(obj$fit$design[,by]) |
|
66 |
+ if(eff>0){ |
|
67 |
+ effectiveSamples = calculateEffectiveSamples(obj) |
|
68 |
+ if(numberEff == FALSE){ |
|
69 |
+ valid = which(effectiveSamples>=quantile(effectiveSamples,p=eff,na.rm=TRUE)) |
|
70 |
+ } else { |
|
71 |
+ valid = which(effectiveSamples>=eff) |
|
72 |
+ } |
|
73 |
+ } |
|
74 |
+ } |
|
52 | 75 |
|
76 |
+ tx = as.character(taxa) |
|
53 | 77 |
if(uniqueNames==TRUE){ |
54 | 78 |
for (nm in unique(tx)) { |
55 | 79 |
ii=which(tx==nm) |
56 |
- tx[ii]=paste(tx[ii],seq_along(ii),sep=":") |
|
80 |
+ tx[ii]=paste(tx[ii],seq_along(ii),sep=":") |
|
57 | 81 |
} |
58 | 82 |
} |
59 |
- |
|
60 |
- if(is.null(coef)){coef = 1:ncol(tb);} |
|
61 |
- |
|
62 |
- p=obj$eb$p.value[,by]; |
|
63 |
- padj = p.adjust(p,method=adjust.method); |
|
64 |
- |
|
65 |
- groups = factor(obj$fit$design[,by]) |
|
66 |
- cnts = obj$counts; |
|
67 |
- yy = cnts>0; |
|
83 |
+ padj = p.adjust(p,method=adjustMethod) |
|
84 |
+ cnts = obj$counts |
|
85 |
+ posIndices = cnts>0 |
|
68 | 86 |
|
69 |
- np0 = rowSums(yy[,groups==0]); |
|
70 |
- np1 = rowSums(yy[,groups==1]); |
|
87 |
+ np0 = rowSums(posIndices[,groups==0]) |
|
88 |
+ np1 = rowSums(posIndices[,groups==1]) |
|
71 | 89 |
|
72 |
- nc0 = rowSums(cnts[,groups==0]); |
|
73 |
- nc1 = rowSums(cnts[,groups==1]); |
|
90 |
+ nc0 = rowSums(cnts[,groups==0]) |
|
91 |
+ nc1 = rowSums(cnts[,groups==1]) |
|
74 | 92 |
|
75 | 93 |
if(group==0){ |
76 | 94 |
srt = order(abs(tb[,by]),decreasing=TRUE) |
... | ... |
@@ -81,37 +99,28 @@ MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,a |
81 | 99 |
} else if(group==3){ |
82 | 100 |
srt = order(p,decreasing=FALSE) |
83 | 101 |
} else { |
84 |
- srt = 1:length(padj); |
|
102 |
+ srt = 1:length(padj) |
|
85 | 103 |
} |
86 | 104 |
|
87 |
- valid = 1:length(padj); |
|
88 |
- if(eff>0){ |
|
89 |
- effectiveSamples = calculateEffectiveSamples(obj); |
|
90 |
- if(numberEff == FALSE){ |
|
91 |
- valid = which(effectiveSamples>=quantile(effectiveSamples,p=eff,na.rm=TRUE)); |
|
92 |
- } else { |
|
93 |
- valid = which(effectiveSamples>=eff); |
|
94 |
- } |
|
105 |
+ valid = 1:length(padj) |
|
106 |
+ if(ncounts>0){ |
|
107 |
+ np=rowSums(cbind(np0,np1)) |
|
108 |
+ valid = intersect(valid,which(np>=ncounts)) |
|
95 | 109 |
} |
96 |
- if(counts>0){ |
|
97 |
- np=rowSums(cbind(np0,np1)); |
|
98 |
- valid = intersect(valid,which(np>=counts)); |
|
99 |
- } |
|
100 |
- |
|
101 |
- srt = srt[which(srt%in%valid)][1:number]; |
|
110 |
+ srt = srt[which(srt%in%valid)][1:number] |
|
102 | 111 |
|
103 |
- mat = cbind(np0,np1); |
|
104 |
- mat = cbind(mat,nc0); |
|
105 |
- mat = cbind(mat,nc1); |
|
106 |
- mat = cbind(mat,tb[,coef]); |
|
107 |
- mat = cbind(mat,p); |
|
108 |
- mat = cbind(mat,padj); |
|
109 |
- rownames(mat) = tx; |
|
110 |
- mat = mat[srt,]; |
|
112 |
+ mat = cbind(np0,np1) |
|
113 |
+ mat = cbind(mat,nc0) |
|
114 |
+ mat = cbind(mat,nc1) |
|
115 |
+ mat = cbind(mat,tb[,coef]) |
|
116 |
+ mat = cbind(mat,p) |
|
117 |
+ mat = cbind(mat,padj) |
|
118 |
+ rownames(mat) = tx |
|
119 |
+ mat = mat[srt,] |
|
111 | 120 |
|
112 | 121 |
nm = c("+samples in group 0","+samples in group 1","counts in group 0", |
113 |
- "counts in group 1",colnames(tb)[coef],"pvalues","adjPvalues"); |
|
114 |
- colnames(mat) = nm; |
|
122 |
+ "counts in group 1",colnames(tb)[coef],"pvalues","adjPvalues") |
|
123 |
+ colnames(mat) = nm |
|
115 | 124 |
|
116 | 125 |
if(!is.null(file)){ |
117 | 126 |
nm = c("Taxa",nm) |
Commit information:
Commit id: fc42468cd9915cc54e61fbbf71ac93f854f42f6a
cleaning up a bit of code for fun
Committed by: nosson
Author Name: nosson
Commit date: 2015-02-11 20:17:21 -0500
Author date: 2015-02-11 20:17:21 -0500
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@99387 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -118,7 +118,6 @@ MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,a |
118 | 118 |
mat2 = cbind(rownames(mat),mat) |
119 | 119 |
mat2 = rbind(nm,mat2) |
120 | 120 |
write(t(mat2),ncolumns=ncol(mat2),file=file,sep="\t") |
121 |
- } else{ |
|
122 |
- return(as.data.frame(mat)) |
|
123 | 121 |
} |
122 |
+ invisible(as.data.frame(mat)) |
|
124 | 123 |
} |
Commit information:
Commit id: 4bc5c8251031ecfd6ffdff3177a46dcbedc8c3a2
same time points bug
Committed by: nosson
Author Name: nosson
Commit date: 2014-11-12 22:10:29 -0500
Author date: 2014-11-12 22:10:29 -0500
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@96709 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -66,11 +66,11 @@ MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,a |
66 | 66 |
cnts = obj$counts; |
67 | 67 |
yy = cnts>0; |
68 | 68 |
|
69 |
- np0 = rowSums(yy[,groups==unique(groups)[1]]); |
|
70 |
- np1 = rowSums(yy[,groups==unique(groups)[2]]); |
|
69 |
+ np0 = rowSums(yy[,groups==0]); |
|
70 |
+ np1 = rowSums(yy[,groups==1]); |
|
71 | 71 |
|
72 |
- nc0 = rowSums(cnts[,groups==unique(groups)[1]]); |
|
73 |
- nc1 = rowSums(cnts[,groups==unique(groups)[2]]); |
|
72 |
+ nc0 = rowSums(cnts[,groups==0]); |
|
73 |
+ nc1 = rowSums(cnts[,groups==1]); |
|
74 | 74 |
|
75 | 75 |
if(group==0){ |
76 | 76 |
srt = order(abs(tb[,by]),decreasing=TRUE) |
... | ... |
@@ -109,9 +109,8 @@ MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,a |
109 | 109 |
rownames(mat) = tx; |
110 | 110 |
mat = mat[srt,]; |
111 | 111 |
|
112 |
- nm = c(paste("+samples in group",unique(groups)[1]),paste("+samples in group",unique(groups)[2]), |
|
113 |
- paste("counts in group",unique(groups)[1]),paste("counts in group",unique(groups)[2]), |
|
114 |
- colnames(tb)[coef],"pvalues","adjPvalues"); |
|
112 |
+ nm = c("+samples in group 0","+samples in group 1","counts in group 0", |
|
113 |
+ "counts in group 1",colnames(tb)[coef],"pvalues","adjPvalues"); |
|
115 | 114 |
colnames(mat) = nm; |
116 | 115 |
|
117 | 116 |
if(!is.null(file)){ |
Commit information:
Commit id: 683b5c4d606482d43bc1e1cd2159df5423a34c01
Commit message: fixed request bug causing error (calling non-existent column) resulting in no output
Committed by: nosson
Author Name: nosson
Commit date: 2014-07-28 17:54:13 -0400
Author date: 2014-07-28 17:54:13 -0400
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@92951 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -81,10 +81,10 @@ MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,a |
81 | 81 |
} else if(group==3){ |
82 | 82 |
srt = order(p,decreasing=FALSE) |
83 | 83 |
} else { |
84 |
- srt = 1:length(np0); |
|
84 |
+ srt = 1:length(padj); |
|
85 | 85 |
} |
86 | 86 |
|
87 |
- valid = 1:length(np0); |
|
87 |
+ valid = 1:length(padj); |
|
88 | 88 |
if(eff>0){ |
89 | 89 |
effectiveSamples = calculateEffectiveSamples(obj); |
90 | 90 |
if(numberEff == FALSE){ |
... | ... |
@@ -111,7 +111,7 @@ MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,a |
111 | 111 |
|
112 | 112 |
nm = c(paste("+samples in group",unique(groups)[1]),paste("+samples in group",unique(groups)[2]), |
113 | 113 |
paste("counts in group",unique(groups)[1]),paste("counts in group",unique(groups)[2]), |
114 |
- colnames(tb)[coef],"pValue","adjPvalue"); |
|
114 |
+ colnames(tb)[coef],"pvalues","adjPvalues"); |
|
115 | 115 |
colnames(mat) = nm; |
116 | 116 |
|
117 | 117 |
if(!is.null(file)){ |
Commit information:
Commit id: d34dd4aec0fb3b2fe12cfa5e81414dc4de4fb191
Commit message: Merge pull request #12 from nosson/request
Request 7.28.14
Committed by: Joseph N. Paulson
Author Name: Joseph N. Paulson
Commit date: 2014-07-28 10:10:28 -0400
Author date: 2014-07-28 10:10:28 -0400
Commit id: c5ffc1eb429498a84d14e703a3c397f3513777e8
Commit message: adding recent request
Committed by: Joseph Nathaniel Paulson
Author Name: Joseph Nathaniel Paulson
Commit date: 2014-07-28 09:55:00 -0400
Author date: 2014-07-28 09:55:00 -0400
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@92916 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -20,13 +20,14 @@ |
20 | 20 |
#' @param adjust.method Method to adjust p-values by. Default is "FDR". Options |
21 | 21 |
#' include "holm", "hochberg", "hommel", "bonferroni", "BH", "BY", "fdr", |
22 | 22 |
#' "none". See \code{\link{p.adjust}} for more details. |
23 |
-#' @param group One of three choices, 0,1,2,3,4. 0: the sort is ordered by a |
|
23 |
+#' @param group One of five choices, 0,1,2,3,4. 0: the sort is ordered by a |
|
24 | 24 |
#' decreasing absolute value coefficient fit. 1: the sort is ordered by the raw |
25 | 25 |
#' coefficient fit in decreasing order. 2: the sort is ordered by the raw |
26 | 26 |
#' coefficient fit in increasing order. 3: the sort is ordered by the p-value |
27 | 27 |
#' of the coefficient fit in increasing order. 4: no sorting. |
28 |
-#' @param eff Restrict samples to have at least a "eff" quantile or number of effective samples. |
|
28 |
+#' @param eff Filter features to have at least a "eff" quantile or number of effective samples. |
|
29 | 29 |
#' @param numberEff Boolean, whether eff should represent quantile (default/FALSE) or number. |
30 |
+#' @param counts Filter features to have at least 'counts' of counts. |
|
30 | 31 |
#' @param file Name of file, including location, to save the table. |
31 | 32 |
#' @return Table of the top-ranked features determined by the linear fit's |
32 | 33 |
#' coefficient. |
... | ... |
@@ -45,7 +46,7 @@ |
45 | 46 |
#' fit = fitZig(obj = lungTrim,mod=mod,control=settings) |
46 | 47 |
#' head(MRtable(fit)) |
47 | 48 |
#' |
48 |
-MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,adjust.method="fdr",group=0,eff=0,numberEff=FALSE,file=NULL){ |
|
49 |
+MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,adjust.method="fdr",group=0,eff=0,numberEff=FALSE,counts=0,file=NULL){ |
|
49 | 50 |
tb = obj$fit$coefficients |
50 | 51 |
tx = as.character(taxa); |
51 | 52 |
|
... | ... |
@@ -83,12 +84,20 @@ MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,a |
83 | 84 |
srt = 1:length(np0); |
84 | 85 |
} |
85 | 86 |
|
86 |
- effectiveSamples = calculateEffectiveSamples(obj); |
|
87 |
- if(numberEff == FALSE){ |
|
88 |
- valid = which(effectiveSamples>=quantile(effectiveSamples,p=eff,na.rm=TRUE)); |
|
89 |
- } else { |
|
90 |
- valid = which(effectiveSamples>=eff); |
|
87 |
+ valid = 1:length(np0); |
|
88 |
+ if(eff>0){ |
|
89 |
+ effectiveSamples = calculateEffectiveSamples(obj); |
|
90 |
+ if(numberEff == FALSE){ |
|
91 |
+ valid = which(effectiveSamples>=quantile(effectiveSamples,p=eff,na.rm=TRUE)); |
|
92 |
+ } else { |
|
93 |
+ valid = which(effectiveSamples>=eff); |
|
94 |
+ } |
|
91 | 95 |
} |
96 |
+ if(counts>0){ |
|
97 |
+ np=rowSums(cbind(np0,np1)); |
|
98 |
+ valid = intersect(valid,which(np>=counts)); |
|
99 |
+ } |
|
100 |
+ |
|
92 | 101 |
srt = srt[which(srt%in%valid)][1:number]; |
93 | 102 |
|
94 | 103 |
mat = cbind(np0,np1); |
Commit information:
Commit id: adce455f6c326b6ef1d6420cf61102597e6e8cb2
Commit message: Output of fitZig (eb) is now a result of limma::eBayes instead of limma::ebayes
Committed by: nosson
Author Name: nosson
Commit date: 2014-06-13 11:35:33 -0400
Author date: 2014-06-13 11:35:33 -0400
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@91372 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -58,7 +58,7 @@ MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,a |
58 | 58 |
|
59 | 59 |
if(is.null(coef)){coef = 1:ncol(tb);} |
60 | 60 |
|
61 |
- p=obj$eb$p[,by]; |
|
61 |
+ p=obj$eb$p.value[,by]; |
|
62 | 62 |
padj = p.adjust(p,method=adjust.method); |
63 | 63 |
|
64 | 64 |
groups = factor(obj$fit$design[,by]) |
Commit information:
Commit id: 58e266e0f4cb1efcb583fc0a1ed9c0f37e85a2e3
Commit message:
added numberEff to tables, and plots to vignette, renamed output to file for exporting datasets in a number of functions.
Committed by nosson <nosson at gmail.com>
Commit date: 2014-04-01T16:35:31-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@88271 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -20,13 +20,14 @@ |
20 | 20 |
#' @param adjust.method Method to adjust p-values by. Default is "FDR". Options |
21 | 21 |
#' include "holm", "hochberg", "hommel", "bonferroni", "BH", "BY", "fdr", |
22 | 22 |
#' "none". See \code{\link{p.adjust}} for more details. |
23 |
-#' @param group One of three choices, 0,1,2. 0: the sort is ordered by a |
|
23 |
+#' @param group One of three choices, 0,1,2,3,4. 0: the sort is ordered by a |
|
24 | 24 |
#' decreasing absolute value coefficient fit. 1: the sort is ordered by the raw |
25 | 25 |
#' coefficient fit in decreasing order. 2: the sort is ordered by the raw |
26 | 26 |
#' coefficient fit in increasing order. 3: the sort is ordered by the p-value |
27 |
-#' of the coefficient fit in increasing order. |
|
28 |
-#' @param eff Restrict samples to have at least a "eff" quantile effective samples. |
|
29 |
-#' @param output Name of output file, including location, to save the table. |
|
27 |
+#' of the coefficient fit in increasing order. 4: no sorting. |
|
28 |
+#' @param eff Restrict samples to have at least a "eff" quantile or number of effective samples. |
|
29 |
+#' @param numberEff Boolean, whether eff should represent quantile (default/FALSE) or number. |
|
30 |
+#' @param file Name of file, including location, to save the table. |
|
30 | 31 |
#' @return Table of the top-ranked features determined by the linear fit's |
31 | 32 |
#' coefficient. |
32 | 33 |
#' @seealso \code{\link{fitZig}} \code{\link{MRcoefs}} |
... | ... |
@@ -44,7 +45,7 @@ |
44 | 45 |
#' fit = fitZig(obj = lungTrim,mod=mod,control=settings) |
45 | 46 |
#' head(MRtable(fit)) |
46 | 47 |
#' |
47 |
-MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,adjust.method="fdr",group=0,eff=0,output=NULL){ |
|
48 |
+MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,adjust.method="fdr",group=0,eff=0,numberEff=FALSE,file=NULL){ |
|
48 | 49 |
tb = obj$fit$coefficients |
49 | 50 |
tx = as.character(taxa); |
50 | 51 |
|
... | ... |
@@ -78,10 +79,16 @@ MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,a |
78 | 79 |
srt = order((tb[,by]),decreasing=FALSE) |
79 | 80 |
} else if(group==3){ |
80 | 81 |
srt = order(p,decreasing=FALSE) |
82 |
+ } else { |
|
83 |
+ srt = 1:length(np0); |
|
81 | 84 |
} |
82 | 85 |
|
83 | 86 |
effectiveSamples = calculateEffectiveSamples(obj); |
84 |
- valid = which(effectiveSamples>=quantile(effectiveSamples,p=eff,na.rm=TRUE)); |
|
87 |
+ if(numberEff == FALSE){ |
|
88 |
+ valid = which(effectiveSamples>=quantile(effectiveSamples,p=eff,na.rm=TRUE)); |
|
89 |
+ } else { |
|
90 |
+ valid = which(effectiveSamples>=eff); |
|
91 |
+ } |
|
85 | 92 |
srt = srt[which(srt%in%valid)][1:number]; |
86 | 93 |
|
87 | 94 |
mat = cbind(np0,np1); |
... | ... |
@@ -98,11 +105,11 @@ MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,a |
98 | 105 |
colnames(tb)[coef],"pValue","adjPvalue"); |
99 | 106 |
colnames(mat) = nm; |
100 | 107 |
|
101 |
- if(!is.null(output)){ |
|
108 |
+ if(!is.null(file)){ |
|
102 | 109 |
nm = c("Taxa",nm) |
103 | 110 |
mat2 = cbind(rownames(mat),mat) |
104 | 111 |
mat2 = rbind(nm,mat2) |
105 |
- write(t(mat2),ncolumns=ncol(mat2),file=output,sep="\t") |
|
112 |
+ write(t(mat2),ncolumns=ncol(mat2),file=file,sep="\t") |
|
106 | 113 |
} else{ |
107 | 114 |
return(as.data.frame(mat)) |
108 | 115 |
} |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@84391 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -25,6 +25,7 @@ |
25 | 25 |
#' coefficient fit in decreasing order. 2: the sort is ordered by the raw |
26 | 26 |
#' coefficient fit in increasing order. 3: the sort is ordered by the p-value |
27 | 27 |
#' of the coefficient fit in increasing order. |
28 |
+#' @param eff Restrict samples to have at least a "eff" quantile effective samples. |
|
28 | 29 |
#' @param output Name of output file, including location, to save the table. |
29 | 30 |
#' @return Table of the top-ranked features determined by the linear fit's |
30 | 31 |
#' coefficient. |
... | ... |
@@ -43,14 +44,14 @@ |
43 | 44 |
#' fit = fitZig(obj = lungTrim,mod=mod,control=settings) |
44 | 45 |
#' head(MRtable(fit)) |
45 | 46 |
#' |
46 |
-MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,adjust.method="fdr",group=0,output=NULL){ |
|
47 |
+MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,adjust.method="fdr",group=0,eff=0,output=NULL){ |
|
47 | 48 |
tb = obj$fit$coefficients |
48 | 49 |
tx = as.character(taxa); |
49 | 50 |
|
50 | 51 |
if(uniqueNames==TRUE){ |
51 | 52 |
for (nm in unique(tx)) { |
52 | 53 |
ii=which(tx==nm) |
53 |
- tx[ii]=paste(tx[ii],seq_along(ii),sep=":") |
|
54 |
+ tx[ii]=paste(tx[ii],seq_along(ii),sep=":") |
|
54 | 55 |
} |
55 | 56 |
} |
56 | 57 |
|
... | ... |
@@ -70,28 +71,32 @@ MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,a |
70 | 71 |
nc1 = rowSums(cnts[,groups==unique(groups)[2]]); |
71 | 72 |
|
72 | 73 |
if(group==0){ |
73 |
- srt = order(abs(tb[,by]),decreasing=TRUE)[1:number] |
|
74 |
+ srt = order(abs(tb[,by]),decreasing=TRUE) |
|
74 | 75 |
} else if(group==1){ |
75 |
- srt = order((tb[,by]),decreasing=TRUE)[1:number] |
|
76 |
+ srt = order((tb[,by]),decreasing=TRUE) |
|
76 | 77 |
} else if(group==2){ |
77 |
- srt = order((tb[,by]),decreasing=FALSE)[1:number] |
|
78 |
+ srt = order((tb[,by]),decreasing=FALSE) |
|
78 | 79 |
} else if(group==3){ |
79 |
- srt = order(p,decreasing=FALSE)[1:number] |
|
80 |
+ srt = order(p,decreasing=FALSE) |
|
80 | 81 |
} |
81 | 82 |
|
82 |
- mat = cbind(np0,np1) |
|
83 |
- mat = cbind(mat,nc0) |
|
84 |
- mat = cbind(mat,nc1) |
|
85 |
- mat = cbind(mat,tb[,coef]) |
|
86 |
- mat = cbind(mat,p) |
|
87 |
- mat = cbind(mat,padj) |
|
83 |
+ effectiveSamples = calculateEffectiveSamples(obj); |
|
84 |
+ valid = which(effectiveSamples>=quantile(effectiveSamples,p=eff,na.rm=TRUE)); |
|
85 |
+ srt = srt[which(srt%in%valid)][1:number]; |
|
86 |
+ |
|
87 |
+ mat = cbind(np0,np1); |
|
88 |
+ mat = cbind(mat,nc0); |
|
89 |
+ mat = cbind(mat,nc1); |
|
90 |
+ mat = cbind(mat,tb[,coef]); |
|
91 |
+ mat = cbind(mat,p); |
|
92 |
+ mat = cbind(mat,padj); |
|
88 | 93 |
rownames(mat) = tx; |
89 |
- mat = mat[srt,] |
|
94 |
+ mat = mat[srt,]; |
|
90 | 95 |
|
91 | 96 |
nm = c(paste("+samples in group",unique(groups)[1]),paste("+samples in group",unique(groups)[2]), |
92 | 97 |
paste("counts in group",unique(groups)[1]),paste("counts in group",unique(groups)[2]), |
93 |
- colnames(tb)[coef],"pValue","adjPvalue") |
|
94 |
- colnames(mat) = nm |
|
98 |
+ colnames(tb)[coef],"pValue","adjPvalue"); |
|
99 |
+ colnames(mat) = nm; |
|
95 | 100 |
|
96 | 101 |
if(!is.null(output)){ |
97 | 102 |
nm = c("Taxa",nm) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@79408 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,3 +1,48 @@ |
1 |
+#' Table of top microbial marker gene from linear model fit including sequence |
|
2 |
+#' information |
|
3 |
+#' |
|
4 |
+#' Extract a table of the top-ranked features from a linear model fit. This |
|
5 |
+#' function will be updated soon to provide better flexibility similar to |
|
6 |
+#' limma's topTable. This function differs from \code{link{MRcoefs}} in that it |
|
7 |
+#' provides other information about the presence or absence of features to help |
|
8 |
+#' ensure significant features called are moderately present. |
|
9 |
+#' |
|
10 |
+#' |
|
11 |
+#' @param obj A list containing the linear model fit produced by lmFit through |
|
12 |
+#' fitZig. |
|
13 |
+#' @param by Column number or column name specifying which coefficient or |
|
14 |
+#' contrast of the linear model is of interest. |
|
15 |
+#' @param coef Column number(s) or column name(s) specifying which coefficient |
|
16 |
+#' or contrast of the linear model to display. |
|
17 |
+#' @param number The number of bacterial features to pick out. |
|
18 |
+#' @param taxa Taxa list. |
|
19 |
+#' @param uniqueNames Number the various taxa. |
|
20 |
+#' @param adjust.method Method to adjust p-values by. Default is "FDR". Options |
|
21 |
+#' include "holm", "hochberg", "hommel", "bonferroni", "BH", "BY", "fdr", |
|
22 |
+#' "none". See \code{\link{p.adjust}} for more details. |
|
23 |
+#' @param group One of three choices, 0,1,2. 0: the sort is ordered by a |
|
24 |
+#' decreasing absolute value coefficient fit. 1: the sort is ordered by the raw |
|
25 |
+#' coefficient fit in decreasing order. 2: the sort is ordered by the raw |
|
26 |
+#' coefficient fit in increasing order. 3: the sort is ordered by the p-value |
|
27 |
+#' of the coefficient fit in increasing order. |
|
28 |
+#' @param output Name of output file, including location, to save the table. |
|
29 |
+#' @return Table of the top-ranked features determined by the linear fit's |
|
30 |
+#' coefficient. |
|
31 |
+#' @seealso \code{\link{fitZig}} \code{\link{MRcoefs}} |
|
32 |
+#' @examples |
|
33 |
+#' |
|
34 |
+#' data(lungData) |
|
35 |
+#' k = grep("Extraction.Control",pData(lungData)$SampleType) |
|
36 |
+#' lungTrim = lungData[,-k] |
|
37 |
+#' k = which(rowSums(MRcounts(lungTrim)>0)<10) |
|
38 |
+#' lungTrim = lungTrim[-k,] |
|
39 |
+#' cumNorm(lungTrim) |
|
40 |
+#' smokingStatus = pData(lungTrim)$SmokingStatus |
|
41 |
+#' mod = model.matrix(~smokingStatus) |
|
42 |
+#' settings = zigControl(maxit=1,verbose=FALSE) |
|
43 |
+#' fit = fitZig(obj = lungTrim,mod=mod,control=settings) |
|
44 |
+#' head(MRtable(fit)) |
|
45 |
+#' |
|
1 | 46 |
MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,adjust.method="fdr",group=0,output=NULL){ |
2 | 47 |
tb = obj$fit$coefficients |
3 | 48 |
tx = as.character(taxa); |
... | ... |
@@ -56,4 +101,4 @@ MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,a |
56 | 101 |
} else{ |
57 | 102 |
return(as.data.frame(mat)) |
58 | 103 |
} |
59 |
-} |
|
60 | 104 |
\ No newline at end of file |
105 |
+} |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@77421 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -2,7 +2,7 @@ MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,a |
2 | 2 |
tb = obj$fit$coefficients |
3 | 3 |
tx = as.character(taxa); |
4 | 4 |
|
5 |
- if(uniqueNames=TRUE){ |
|
5 |
+ if(uniqueNames==TRUE){ |
|
6 | 6 |
for (nm in unique(tx)) { |
7 | 7 |
ii=which(tx==nm) |
8 | 8 |
tx[ii]=paste(tx[ii],seq_along(ii),sep=":") |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@77398 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,10 +1,12 @@ |
1 |
-MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,adjust.method="fdr",group=0,output=NULL){ |
|
1 |
+MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,uniqueNames=FALSE,adjust.method="fdr",group=0,output=NULL){ |
|
2 | 2 |
tb = obj$fit$coefficients |
3 | 3 |
tx = as.character(taxa); |
4 | 4 |
|
5 |
- for (nm in unique(tx)) { |
|
6 |
- ii=which(tx==nm) |
|
7 |
- tx[ii]=paste(tx[ii],seq_along(ii),sep=":") |
|
5 |
+ if(uniqueNames=TRUE){ |
|
6 |
+ for (nm in unique(tx)) { |
|
7 |
+ ii=which(tx==nm) |
|
8 |
+ tx[ii]=paste(tx[ii],seq_along(ii),sep=":") |
|
9 |
+ } |
|
8 | 10 |
} |
9 | 11 |
|
10 | 12 |
if(is.null(coef)){coef = 1:ncol(tb);} |
... | ... |
@@ -28,6 +30,8 @@ MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,adjust.method="fdr" |
28 | 30 |
srt = order((tb[,by]),decreasing=TRUE)[1:number] |
29 | 31 |
} else if(group==2){ |
30 | 32 |
srt = order((tb[,by]),decreasing=FALSE)[1:number] |
33 |
+ } else if(group==3){ |
|
34 |
+ srt = order(p,decreasing=FALSE)[1:number] |
|
31 | 35 |
} |
32 | 36 |
|
33 | 37 |
mat = cbind(np0,np1) |
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/metagenomeSeq@74804 bc3139a8-67e5-0310-9ffc-ced21a209358
1 | 1 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,55 @@ |
1 |
+MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,adjust.method="fdr",group=0,output=NULL){ |
|
2 |
+ tb = obj$fit$coefficients |
|
3 |
+ tx = as.character(taxa); |
|
4 |
+ |
|
5 |
+ for (nm in unique(tx)) { |
|
6 |
+ ii=which(tx==nm) |
|
7 |
+ tx[ii]=paste(tx[ii],seq_along(ii),sep=":") |
|
8 |
+ } |
|
9 |
+ |
|
10 |
+ if(is.null(coef)){coef = 1:ncol(tb);} |
|
11 |
+ |
|
12 |
+ p=obj$eb$p[,by]; |
|
13 |
+ padj = p.adjust(p,method=adjust.method); |
|
14 |
+ |
|
15 |
+ groups = factor(obj$fit$design[,by]) |
|
16 |
+ cnts = obj$counts; |
|
17 |
+ yy = cnts>0; |
|
18 |
+ |
|
19 |
+ np0 = rowSums(yy[,groups==unique(groups)[1]]); |
|
20 |
+ np1 = rowSums(yy[,groups==unique(groups)[2]]); |
|
21 |
+ |
|
22 |
+ nc0 = rowSums(cnts[,groups==unique(groups)[1]]); |
|
23 |
+ nc1 = rowSums(cnts[,groups==unique(groups)[2]]); |
|
24 |
+ |
|
25 |
+ if(group==0){ |
|
26 |
+ srt = order(abs(tb[,by]),decreasing=TRUE)[1:number] |
|
27 |
+ } else if(group==1){ |
|
28 |
+ srt = order((tb[,by]),decreasing=TRUE)[1:number] |
|
29 |
+ } else if(group==2){ |
|
30 |
+ srt = order((tb[,by]),decreasing=FALSE)[1:number] |
|
31 |
+ } |
|
32 |
+ |
|
33 |
+ mat = cbind(np0,np1) |
|
34 |
+ mat = cbind(mat,nc0) |
|
35 |
+ mat = cbind(mat,nc1) |
|
36 |
+ mat = cbind(mat,tb[,coef]) |
|
37 |
+ mat = cbind(mat,p) |
|
38 |
+ mat = cbind(mat,padj) |
|
39 |
+ rownames(mat) = tx; |
|
40 |
+ mat = mat[srt,] |
|
41 |
+ |
|
42 |
+ nm = c(paste("+samples in group",unique(groups)[1]),paste("+samples in group",unique(groups)[2]), |
|
43 |
+ paste("counts in group",unique(groups)[1]),paste("counts in group",unique(groups)[2]), |
|
44 |
+ colnames(tb)[coef],"pValue","adjPvalue") |
|
45 |
+ colnames(mat) = nm |
|
46 |
+ |
|
47 |
+ if(!is.null(output)){ |
|
48 |
+ nm = c("Taxa",nm) |
|
49 |
+ mat2 = cbind(rownames(mat),mat) |
|
50 |
+ mat2 = rbind(nm,mat2) |
|
51 |
+ write(t(mat2),ncolumns=ncol(mat2),file=output,sep="\t") |
|
52 |
+ } else{ |
|
53 |
+ return(as.data.frame(mat)) |
|
54 |
+ } |
|
55 |
+} |
|
0 | 56 |
\ No newline at end of file |