git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/branches/RELEASE_3_4/madman/Rpacks/DEsubs@123321 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -371,9 +371,10 @@ subpathwayVisualization <- function( DEsubs.out, |
371 | 371 |
} |
372 | 372 |
if ( '' %in% outfiles ) { outfiles <- rep('', length(references) ) } |
373 | 373 |
|
374 |
+ out <- vector(mode='list', length=length(references)) |
|
374 | 375 |
for ( i in seq_len(length(references)) ) |
375 | 376 |
{ |
376 |
- .subpathwayVisualization(DEsubs.out=DEsubs.out, |
|
377 |
+ out[[i]] <- .subpathwayVisualization(DEsubs.out=DEsubs.out, |
|
377 | 378 |
reference=references[i], |
378 | 379 |
submethod=submethod, |
379 | 380 |
subname=subname, |
... | ... |
@@ -385,6 +386,9 @@ subpathwayVisualization <- function( DEsubs.out, |
385 | 386 |
verbose=verbose |
386 | 387 |
) |
387 | 388 |
} |
389 |
+ names(out) <- references |
|
390 |
+ |
|
391 |
+ return( out ) |
|
388 | 392 |
} |
389 | 393 |
|
390 | 394 |
.subpathwayVisualization <- function( DEsubs.out, reference, submethod, |
... | ... |
@@ -503,9 +507,15 @@ subpathwayVisualization <- function( DEsubs.out, |
503 | 507 |
adjmat <- matrix(0, nrow=length(rowTerms), ncol=length(colTerms)) |
504 | 508 |
rownames(adjmat) <- rowTerms |
505 | 509 |
colnames(adjmat) <- colTerms |
510 |
+ adjmat.pval <- matrix(NA, nrow=length(rowTerms), ncol=length(colTerms)) |
|
511 |
+ rownames(adjmat.pval) <- rowTerms |
|
512 |
+ colnames(adjmat.pval) <- colTerms |
|
506 | 513 |
for ( i in seq_len(nrow(edgeList)) ) |
507 | 514 |
{ |
515 |
+ # For visualization purposes |
|
508 | 516 |
adjmat[ edgeList[i,1], edgeList[i,2] ] <- 1 |
517 |
+ # For output |
|
518 |
+ adjmat.pval[edgeList[i,1], edgeList[i,2]] <- as.numeric(edgeList[i,3]) |
|
509 | 519 |
} |
510 | 520 |
|
511 | 521 |
if ( shuffleColors ) |
... | ... |
@@ -538,6 +548,8 @@ subpathwayVisualization <- function( DEsubs.out, |
538 | 548 |
export=export) |
539 | 549 |
|
540 | 550 |
if (verbose) { message('done.') } |
551 |
+ |
|
552 |
+ return( adjmat.pval ) |
|
541 | 553 |
} |
542 | 554 |
|
543 | 555 |
|
... | ... |
@@ -571,9 +583,10 @@ organismVisualization <- function( DEsubs.out, |
571 | 583 |
} |
572 | 584 |
if ( '' %in% outfiles ) { outfiles <- rep('', length(references) ) } |
573 | 585 |
|
586 |
+ out <- vector(mode='list', length=length(references)) |
|
574 | 587 |
for ( i in seq_len(length(references)) ) |
575 | 588 |
{ |
576 |
- res <- .organismVisualization(DEsubs.out=DEsubs.out, |
|
589 |
+ out[[i]] <- .organismVisualization(DEsubs.out=DEsubs.out, |
|
577 | 590 |
references=references[i], |
578 | 591 |
topSubs=topSubs, |
579 | 592 |
topTerms=topTerms, |
... | ... |
@@ -584,9 +597,9 @@ organismVisualization <- function( DEsubs.out, |
584 | 597 |
outfile=outfiles[i], |
585 | 598 |
verbose=verbose) |
586 | 599 |
} |
600 |
+ names(out) <- references |
|
587 | 601 |
|
588 |
- |
|
589 |
- return(invisible()) |
|
602 |
+ return( out ) |
|
590 | 603 |
} |
591 | 604 |
|
592 | 605 |
.organismVisualization <- function( DEsubs.out, references, topSubs, topTerms, |
... | ... |
@@ -712,7 +725,7 @@ organismVisualization <- function( DEsubs.out, |
712 | 725 |
{ message('done', appendLF = TRUE) } |
713 | 726 |
|
714 | 727 |
|
715 |
- return(termsPerSub.edgeList) |
|
728 |
+ return( termsPerSub.df ) |
|
716 | 729 |
} |
717 | 730 |
|
718 | 731 |
|
... | ... |
@@ -31,7 +31,8 @@ not specified, default filenames are used ('DEsubs/Output').} |
31 | 31 |
\item{verbose}{ TRUE to display informative messages, FALSE to hide. } |
32 | 32 |
} |
33 | 33 |
\value{ |
34 |
-No value is returned. |
|
34 |
+A list of matrices, containing Subpathway/Term/P-Value results for each |
|
35 |
+reference. |
|
35 | 36 |
} |
36 | 37 |
\description{ |
37 | 38 |
Organism level measures |
... | ... |
@@ -38,7 +38,9 @@ not specified, default filenames are used ('DEsubs/Output').} |
38 | 38 |
\item{verbose}{ TRUE to display informative messages, FALSE to hide. } |
39 | 39 |
} |
40 | 40 |
\value{ |
41 |
-No value is returned. |
|
41 |
+A list of matrices, each containing the P-Value of enrichment between the |
|
42 |
+terms for a specific reference (rows) and each of the subpathway genes |
|
43 |
+(columns). If there is no enrichment, the value is NA. |
|
42 | 44 |
} |
43 | 45 |
\description{ |
44 | 46 |
Circular diagrams containing subpathways enrichment in potential key |
... | ... |
@@ -88,9 +88,9 @@ load(system.file('extdata', 'data.RData', package='DEsubs')) |
88 | 88 |
\newpage |
89 | 89 |
|
90 | 90 |
## 2. User Input |
91 |
-DEsubs accepts RNA-seq expression control-case profile data. The following |
|
92 |
-example in Table 1 shows the right structure for RNA-seq expression data input. |
|
93 |
- |
|
91 |
+DEsubs accepts RNA-seq expression paired case-control profile data. The |
|
92 |
+following example in Table 1 shows the right structure for RNA-seq expression |
|
93 |
+data input. |
|
94 | 94 |
|
95 | 95 |
```{r, eval=TRUE, echo=FALSE, results = 'asis'} |
96 | 96 |
|
... | ... |
@@ -103,7 +103,7 @@ data <- c( 1879, 2734, 2369, 2636, 2188, 9743, 9932, 10099, |
103 | 103 |
data <- matrix(data, nrow=6, ncol=8, byrow=TRUE) |
104 | 104 |
|
105 | 105 |
rownames(data) <- c(paste0('Gene ', 1:3), '...', 'Gene N-1', 'Gene N') |
106 |
-colnames(data) <- paste0('Sample ', 1:8) |
|
106 |
+colnames(data) <- c(paste0('Case ', 1:4), paste0('Control ', 1:4)) |
|
107 | 107 |
|
108 | 108 |
kable( data, |
109 | 109 |
caption = 'Example of user input format' ) |