... | ... |
@@ -1,5 +1,5 @@ |
1 | 1 |
Package: DEsubs |
2 |
-Version: 1.7.1 |
|
2 |
+Version: 1.7.2 |
|
3 | 3 |
Date: 2017-07-23 |
4 | 4 |
Title: DEsubs: an R package for flexible identification of |
5 | 5 |
differentially expressed subpathways using RNA-seq expression |
... | ... |
@@ -25,7 +25,7 @@ Repository: Bioconductor |
25 | 25 |
Date/Publication: |
26 | 26 |
NeedsCompilation: no |
27 | 27 |
LazyLoad: yes |
28 |
-Imports: graph, igraph, RBGL, circlize, limma, edgeR, samr, EBSeq, |
|
28 |
+Imports: graph, igraph, RBGL, circlize, limma, edgeR, EBSeq, |
|
29 | 29 |
NBPSeq, DESeq, stats, grDevices, graphics, pheatmap, utils, |
30 | 30 |
ggplot2, Matrix, jsonlite, tools, DESeq2, methods |
31 | 31 |
Suggests: RUnit, BiocGenerics, knitr |
... | ... |
@@ -60,7 +60,7 @@ DEsubs <- function( org, mRNAexpr, mRNAnomenclature, pathways, |
60 | 60 |
if ( missing(classes) ) { message('Please supply the classes.') } |
61 | 61 |
if ( missing(DEGchoice) ) { message('Please supply a type.') } |
62 | 62 |
|
63 |
- supportedMethods <- c('edgeR', 'DESeq', 'EBSeq', 'samr', 'NBPSeq', |
|
63 |
+ supportedMethods <- c('edgeR', 'DESeq', 'EBSeq', 'NBPSeq', |
|
64 | 64 |
'voom+limma', 'vst+limma', 'TSPM') |
65 | 65 |
|
66 | 66 |
if ( DEGchoice == 'edgeR' ) |
... | ... |
@@ -116,34 +116,34 @@ DEsubs <- function( org, mRNAexpr, mRNAnomenclature, pathways, |
116 | 116 |
|
117 | 117 |
return(adjpvalues) |
118 | 118 |
} |
119 |
- if ( DEGchoice == 'samr' ) |
|
120 |
- { |
|
121 |
- # samr |
|
122 |
- sink( tempfile() ) |
|
123 |
- SAMseq.test <- suppressMessages(SAMseq(count.matrix, classes, |
|
124 |
- resp.type="Two class unpaired", |
|
125 |
- geneid = rownames(count.matrix), |
|
126 |
- genenames = rownames(count.matrix), |
|
127 |
- nperms = 100, nresamp = 20, fdr.output = 1)) |
|
128 |
- SAMseq.result.table <- rbind( |
|
129 |
- SAMseq.test[['siggenes.table']][['genes.up']], |
|
130 |
- SAMseq.test[['siggenes.table']][['genes.lo']]) |
|
131 |
- SAMseq.score <- rep(0, nrow(count.matrix)) |
|
132 |
- idx <- match(SAMseq.result.table[,1], |
|
133 |
- rownames(count.matrix)) |
|
134 |
- SAMseq.score[idx] <- as.numeric(SAMseq.result.table[,3]) |
|
135 |
- SAMseq.FDR <- rep(1, nrow(count.matrix)) |
|
136 |
- idx <- match(SAMseq.result.table[,1], |
|
137 |
- rownames(count.matrix)) |
|
138 |
- SAMseq.FDR[idx] <- as.numeric(SAMseq.result.table[,5])/100 |
|
139 |
- adjpvalues <- SAMseq.FDR |
|
140 |
- genes <- SAMseq.result.table[, 'Gene ID'] |
|
141 |
- names(adjpvalues) <- genes |
|
119 |
+ # if ( DEGchoice == 'samr' ) |
|
120 |
+ # { |
|
121 |
+ # # samr |
|
122 |
+ # sink( tempfile() ) |
|
123 |
+ # SAMseq.test <- suppressMessages(SAMseq(count.matrix, classes, |
|
124 |
+ # resp.type="Two class unpaired", |
|
125 |
+ # geneid = rownames(count.matrix), |
|
126 |
+ # genenames = rownames(count.matrix), |
|
127 |
+ # nperms = 100, nresamp = 20, fdr.output = 1)) |
|
128 |
+ # SAMseq.result.table <- rbind( |
|
129 |
+ # SAMseq.test[['siggenes.table']][['genes.up']], |
|
130 |
+ # SAMseq.test[['siggenes.table']][['genes.lo']]) |
|
131 |
+ # SAMseq.score <- rep(0, nrow(count.matrix)) |
|
132 |
+ # idx <- match(SAMseq.result.table[,1], |
|
133 |
+ # rownames(count.matrix)) |
|
134 |
+ # SAMseq.score[idx] <- as.numeric(SAMseq.result.table[,3]) |
|
135 |
+ # SAMseq.FDR <- rep(1, nrow(count.matrix)) |
|
136 |
+ # idx <- match(SAMseq.result.table[,1], |
|
137 |
+ # rownames(count.matrix)) |
|
138 |
+ # SAMseq.FDR[idx] <- as.numeric(SAMseq.result.table[,5])/100 |
|
139 |
+ # adjpvalues <- SAMseq.FDR |
|
140 |
+ # genes <- SAMseq.result.table[, 'Gene ID'] |
|
141 |
+ # names(adjpvalues) <- genes |
|
142 | 142 |
|
143 |
- sink() |
|
143 |
+ # sink() |
|
144 | 144 |
|
145 |
- return(adjpvalues) |
|
146 |
- } |
|
145 |
+ # return(adjpvalues) |
|
146 |
+ # } |
|
147 | 147 |
if ( DEGchoice == 'EBSeq' ) |
148 | 148 |
{ |
149 | 149 |
# run EBSeq |
... | ... |
@@ -1,3 +1,6 @@ |
1 |
+1.7.2 - Removed 'Significance Analysis of Microarrays' (SAM) from |
|
2 |
+ available differential expression analysis options due to the |
|
3 |
+ removal of its package from the ecosystem. |
|
1 | 4 |
1.3.4: - Fixing (persistent) inconsistencies between vignette output within |
2 | 5 |
the package and the output in the landing page. |
3 | 6 |
|
... | ... |
@@ -17,7 +17,7 @@ or a filename of a text file stored in the 'User' directory.} |
17 | 17 |
'hgnc_transcript_name', 'refseq_mrna', 'refseq_peptide')} |
18 | 18 |
\item{pathways}{Pathway type ('All', 'Non-Metabolic', 'Metabolic')} |
19 | 19 |
\item{DEtool}{DEG analysis tool selection for NodeRule ('edgeR', 'DESeq', |
20 |
- 'EBSeq', 'samr', 'NBPSeq', 'voom+limma', 'vst+limma', 'TSPM')} |
|
20 |
+ 'EBSeq', 'NBPSeq', 'voom+limma', 'vst+limma', 'TSPM')} |
|
21 | 21 |
\item{DEpar}{DE analysis tools Q-value threshold of NodeRule |
22 | 22 |
(default: DEGpar = 0.05)} |
23 | 23 |
\item{CORtool}{ Correlation measure selection for EdgeRule |
... | ... |
@@ -203,12 +203,12 @@ Supported Labels R command |
203 | 203 |
[@leng2013ebseq] 'EBSeq' |
204 | 204 |
[@smyth2004linear] 'vst+limma' |
205 | 205 |
[@anders2010differential]; [@smyth2004linear] 'voom+limma' |
206 |
-[@li2013finding] 'samr' |
|
207 | 206 |
[@di2011nbp] 'NBPSeq' |
208 | 207 |
[@auer2011two] 'TSPM' |
209 | 208 |
-------------- ---------------- |
210 | 209 |
Table: Node Rule options |
211 | 210 |
|
211 |
+\newpage |
|
212 | 212 |
|
213 | 213 |
## 5. Subpathway Extraction |
214 | 214 |
|