git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/ROntoTools@80800 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,7 +1,7 @@ |
1 | 1 |
Package: ROntoTools |
2 | 2 |
Type: Package |
3 | 3 |
Title: R Onto-Tools suite |
4 |
-Version: 1.1.0 |
|
4 |
+Version: 1.1.2 |
|
5 | 5 |
Author: Calin Voichita <calin@wayne.edu> and Sorin Draghici <sorin@wayne.edu> |
6 | 6 |
Maintainer: Calin Voichita <calin@wayne.edu> |
7 | 7 |
Description: Suite of tools for functional analysis |
... | ... |
@@ -1,6 +1,6 @@ |
1 | 1 |
export(alpha1MR) |
2 | 2 |
export(alphaMLG) |
3 |
-export(compute.fischer) |
|
3 |
+export(compute.fisher) |
|
4 | 4 |
export(compute.normalInv) |
5 | 5 |
export(keggPathwayGraphs) |
6 | 6 |
export(keggPathwayNames) |
... | ... |
@@ -16,7 +16,7 @@ exportMethods(plot) |
16 | 16 |
exportMethods(Summary) |
17 | 17 |
import(boot) |
18 | 18 |
import(graph) |
19 |
-import(KEGGgraph) |
|
20 | 19 |
import(KEGGREST) |
20 |
+import(KEGGgraph) |
|
21 | 21 |
import(parallel) |
22 | 22 |
importMethodsFrom(KEGGgraph) |
... | ... |
@@ -3,7 +3,7 @@ |
3 | 3 |
#' |
4 | 4 |
#' @usage Summary(x, pathNames = NULL, totalAcc = TRUE, totalPert = TRUE, normalize = TRUE, |
5 | 5 |
#' pPert = TRUE, pAcc = TRUE, pORA = TRUE, |
6 |
-#' comb.pv = c("pPert", "pORA"), comb.pv.func = compute.fischer, |
|
6 |
+#' comb.pv = c("pPert", "pORA"), comb.pv.func = compute.fisher, |
|
7 | 7 |
#' order.by = "pComb", adjust.method = "fdr") |
8 | 8 |
#' |
9 | 9 |
#' @param x Pathways-Express result object obtained using \code{\link{pe}} |
... | ... |
@@ -55,7 +55,7 @@ |
55 | 55 |
setMethod("Summary", c("x" = "peRes"), |
56 | 56 |
function(x, pathNames = NULL, totalAcc = TRUE, totalPert = TRUE, normalize = TRUE, |
57 | 57 |
pPert = TRUE, pAcc = TRUE, pORA = TRUE, |
58 |
- comb.pv = c("pPert", "pORA"), comb.pv.func = compute.fischer, |
|
58 |
+ comb.pv = c("pPert", "pORA"), comb.pv.func = compute.fisher, |
|
59 | 59 |
order.by = "pComb", adjust.method = "fdr") |
60 | 60 |
{ |
61 | 61 |
ifelse <- function(test, trueCase, falseCase){ |
... | ... |
@@ -67,19 +67,19 @@ setMethod("Summary", c("x" = "peRes"), |
67 | 67 |
{ |
68 | 68 |
pStats <- NULL |
69 | 69 |
|
70 |
- pStats$totalAcc <- ifelse(totalAcc, get.totalAcc(pePath), NULL) |
|
71 |
- pStats$totalPert <- ifelse(totalPert, get.totalPert(pePath), NULL) |
|
70 |
+ pStats$totalAcc <- ifelse(totalAcc, ifelse(!pePath@asGS, get.totalAcc(pePath), NA), NULL) |
|
71 |
+ pStats$totalPert <- ifelse(totalPert, ifelse(!pePath@asGS, get.totalPert(pePath), NA), NULL) |
|
72 | 72 |
|
73 |
- pStats$totalAccNorm <- ifelse(totalAcc & normalize, get.totalAccNorm(pePath), NULL) |
|
74 |
- pStats$totalPertNorm <- ifelse(totalPert & normalize, get.totalPertNorm(pePath), NULL) |
|
73 |
+ pStats$totalAccNorm <- ifelse(totalAcc & normalize, ifelse(!pePath@asGS, get.totalAccNorm(pePath), NA), NULL) |
|
74 |
+ pStats$totalPertNorm <- ifelse(totalPert & normalize, ifelse(!pePath@asGS, get.totalPertNorm(pePath), NA), NULL) |
|
75 | 75 |
|
76 |
- pStats$pPert <- ifelse(pPert, compute.pPert(pePath), NULL) |
|
77 |
- pStats$pAcc <- ifelse(pAcc, compute.pAcc(pePath), NULL) |
|
76 |
+ pStats$pPert <- ifelse(pPert, ifelse(!pePath@asGS, compute.pPert(pePath), NA), NULL) |
|
77 |
+ pStats$pAcc <- ifelse(pAcc, ifelse(!pePath@asGS, compute.pAcc(pePath), NA), NULL) |
|
78 | 78 |
|
79 | 79 |
pStats$pORA <- ifelse(pORA & !x@cutOffFree, compute.pORA(pePath, length(x@input), length(x@ref)), NULL) |
80 | 80 |
|
81 | 81 |
pStats$pComb <- ifelse(!is.null(comb.pv) & !any(is.null(pStats[comb.pv])), |
82 |
- as.numeric(comb.pv.func(unlist(pStats[comb.pv]))), NULL) |
|
82 |
+ ifelse(!any(is.na(pStats[comb.pv])), as.numeric(comb.pv.func(unlist(pStats[comb.pv]))), NA), NULL) |
|
83 | 83 |
|
84 | 84 |
return(unlist(pStats)) |
85 | 85 |
} |
... | ... |
@@ -167,7 +167,7 @@ keggPathwayGraphs <- function(organism = "hsa", |
167 | 167 |
pathwayGraphs <- pathwayGraphs[!sapply(pathwayGraphs, is.null)] |
168 | 168 |
|
169 | 169 |
if (defaultParameters) |
170 |
- save(pathwayGraphs, paste(system.file("extdata",package="ROntoTools"), "/kpgDefault.RData", sep = "")) |
|
170 |
+ save(pathwayGraphs, file = paste(system.file("extdata",package="ROntoTools"), "/kpgDefault.RData", sep = "")) |
|
171 | 171 |
|
172 | 172 |
return(pathwayGraphs) |
173 | 173 |
} |
... | ... |
@@ -194,9 +194,15 @@ pe.boot <- function(g, x, ref, nboot, all.genes = F) |
194 | 194 |
input = x[names(x) %in% nodes(g)], |
195 | 195 |
ref = ref[ref %in% nodes(g)]) |
196 | 196 |
|
197 |
- if (is.null(inv) | (length(pePath@input) == 0)) |
|
197 |
+ if (length(pePath@input) == 0) |
|
198 | 198 |
return(NULL) |
199 | 199 |
|
200 |
+ if (is.null(inv)) |
|
201 |
+ { |
|
202 |
+ pePath@asGS <- TRUE |
|
203 |
+ return(pePath) |
|
204 |
+ } |
|
205 |
+ |
|
200 | 206 |
# same number of DE genes at any position in the pathway |
201 | 207 |
# (given by the gene from the pathway in the reference) |
202 | 208 |
ran.gen.de <- function(x, l) { |
... | ... |
@@ -226,7 +232,8 @@ pe.boot <- function(g, x, ref, nboot, all.genes = F) |
226 | 232 |
xx[names(pePath@input)] <- pePath@input |
227 | 233 |
pePath@Pert = (inv %*% xx)[,1]; |
228 | 234 |
pePath@Acc = pePath@Pert - xx |
229 |
- |
|
235 |
+ pePath@asGS <- FALSE |
|
236 |
+ |
|
230 | 237 |
return(pePath) |
231 | 238 |
} |
232 | 239 |
|
... | ... |
@@ -92,7 +92,9 @@ setMethod("plot", signature(x="pePathway", y="character"), |
92 | 92 |
tB <- (tB - mean(allB)) / sd(allB) |
93 | 93 |
allB <- (allB - mean(allB)) / sd(allB) |
94 | 94 |
|
95 |
- plot(density(allB), xlab = y, main = main, ...) |
|
95 |
+ xlim <- c(min(allB, tB), max(allB, tB)) * 1.10 |
|
96 |
+ |
|
97 |
+ plot(density(allB, from = xlim[1], to = xlim[2]), xlab = y, main = main, ...) |
|
96 | 98 |
abline(v=0, lwd = .5) |
97 | 99 |
abline(v=tB, lwd = 1, col = "red") |
98 | 100 |
|
... | ... |
@@ -112,7 +114,7 @@ setMethod("plot", signature(x="pePathway", y="character"), |
112 | 114 |
#' @param y vector of two p-values names to be combined using \code{comb.pv.func} (default: \code{c("pAcc", "pORA")}). |
113 | 115 |
#' @param ... Arguments to be passed to methods, such as \code{\link{par}}. |
114 | 116 |
#' @param comb.pv.func the function to combine the p-values - takes as input a vector of p-values |
115 |
-#' and returns the combined p-value (default: \code{\link{compute.fischer}}). |
|
117 |
+#' and returns the combined p-value (default: \code{\link{compute.fisher}}). |
|
116 | 118 |
#' @param adjust.method the name of the method to adjust the p-value (see \code{\link{p.adjust}}) |
117 | 119 |
#' @param threshold corrected p-value threshold |
118 | 120 |
#' @param eps any value smaller than this will be considered as \code{eps} (default: \code{1e-6}). |
... | ... |
@@ -148,7 +150,7 @@ setMethod("plot", signature(x="pePathway", y="character"), |
148 | 150 |
#' @aliases plot,peRes,missing-method |
149 | 151 |
#' @export |
150 | 152 |
setMethod("plot", signature(x="peRes", y="missing"), |
151 |
- function(x, y, ... , comb.pv.func = compute.fischer, adjust.method = "fdr", threshold = .05, eps = 1e-6) |
|
153 |
+ function(x, y, ... , comb.pv.func = compute.fisher, adjust.method = "fdr", threshold = .05, eps = 1e-6) |
|
152 | 154 |
{ |
153 | 155 |
plot(x, y = c("pAcc", "pORA"), ... , comb.pv.func = comb.pv.func, adjust.method = adjust.method, |
154 | 156 |
threshold = threshold, eps = eps) |
... | ... |
@@ -161,7 +163,7 @@ setMethod("plot", signature(x="peRes", y="missing"), |
161 | 163 |
#' @aliases plot,peRes,character-method |
162 | 164 |
#' @export |
163 | 165 |
setMethod("plot", signature(x="peRes", y="character"), |
164 |
- function(x, y, ... , comb.pv.func = compute.fischer, adjust.method = "fdr", threshold = .05, eps = 1e-6) |
|
166 |
+ function(x, y, ... , comb.pv.func = compute.fisher, adjust.method = "fdr", threshold = .05, eps = 1e-6) |
|
165 | 167 |
{ |
166 | 168 |
|
167 | 169 |
st <- Summary(x, comb.pv = y, comb.pv.func = comb.pv.func, adjust.method = adjust.method) |
... | ... |
@@ -140,7 +140,10 @@ peNodeRenderInfo <- function(x, y = "Pert", |
140 | 140 |
|
141 | 141 |
nFillColor <- rep(zero.col, length(nodes(x@map))) |
142 | 142 |
names(nFillColor) <- nodes(x@map) |
143 |
- pf <- slot(x, y) |
|
143 |
+ pfi <- slot(x, y) |
|
144 |
+ pf <- rep(0, length(nodes(x@map))) |
|
145 |
+ names(pf) <- nodes(x@map) |
|
146 |
+ pf[names(pfi)] <- pfi |
|
144 | 147 |
nFillColor[pf <= 0] <- colorRampPalette(c(zero.col,neg.col))(256)[as.numeric(cut(abs(pf[pf<=0]), 256))] |
145 | 148 |
nFillColor[pf >= 0] <- colorRampPalette(c(zero.col,pos.col))(256)[as.numeric(cut(abs(pf[pf>=0]), 256))] |
146 | 149 |
|
... | ... |
@@ -14,7 +14,7 @@ addNames <- function(x, nms) |
14 | 14 |
compute.bootPV <- function(real, dist) |
15 | 15 |
( sum(abs(dist - mean(dist)) > abs(real - mean(dist))) + 1 ) / (1 + length(dist)) |
16 | 16 |
|
17 |
-#' Combine independent p-values using the Fischer method |
|
17 |
+#' Combine independent p-values using the Fisher method |
|
18 | 18 |
#' |
19 | 19 |
#' @param p a vector of independent p-values |
20 | 20 |
#' @param eps the minimal p-value considered (all p-values smaller will be set to this value) |
... | ... |
@@ -23,15 +23,19 @@ compute.bootPV <- function(real, dist) |
23 | 23 |
#' |
24 | 24 |
#' @author Calin Voichita and Sorin Draghici |
25 | 25 |
#' |
26 |
+#' @references |
|
27 |
+#' |
|
28 |
+#' Tarca AL., Draghici S., Khatri P., Hassan SS., Kim J., Kim CJ., Kusanovic JP., Romero R.: "A Signaling Pathway Impact Analysis for Microarray Experiments", 2008, Bioinformatics, 2009, 25(1):75-82. |
|
29 |
+#' |
|
26 | 30 |
#' @seealso \code{\link{pe}},\code{\link{compute.normalInv}} |
27 | 31 |
#' |
28 | 32 |
#' @examples |
29 | 33 |
#' |
30 | 34 |
#' p <- c(.1, .01) |
31 |
-#' compute.fischer(p) |
|
35 |
+#' compute.fisher(p) |
|
32 | 36 |
#' |
33 | 37 |
#' @export |
34 |
-compute.fischer <- function(p, eps = 1e-6) |
|
38 |
+compute.fisher <- function(p, eps = 1e-6) |
|
35 | 39 |
{ |
36 | 40 |
stopifnot(any(p >= 0 & p<=1)) |
37 | 41 |
p[p < eps] <- eps |
... | ... |
@@ -49,7 +53,11 @@ compute.fischer <- function(p, eps = 1e-6) |
49 | 53 |
#' |
50 | 54 |
#' @author Calin Voichita and Sorin Draghici |
51 | 55 |
#' |
52 |
-#' @seealso \code{\link{pe}},\code{\link{compute.fischer}} |
|
56 |
+#' @references |
|
57 |
+#' |
|
58 |
+#' Tarca AL., Draghici S., Romero R.: "A Mmore Specific Method To Combine Perturbation and Over-representation Evidence in Pathway Analysis", PSB 2010 poster. |
|
59 |
+#' |
|
60 |
+#' @seealso \code{\link{pe}},\code{\link{compute.fisher}} |
|
53 | 61 |
#' |
54 | 62 |
#' @examples |
55 | 63 |
#' |
56 | 64 |
deleted file mode 100644 |
... | ... |
@@ -1,26 +0,0 @@ |
1 |
-\name{compute.fischer} |
|
2 |
-\alias{compute.fischer} |
|
3 |
-\title{Combine independent p-values using the Fischer method} |
|
4 |
-\usage{ |
|
5 |
- compute.fischer(p, eps = 1e-06) |
|
6 |
-} |
|
7 |
-\arguments{ |
|
8 |
- \item{p}{a vector of independent p-values} |
|
9 |
- |
|
10 |
- \item{eps}{the minimal p-value considered (all p-values |
|
11 |
- smaller will be set to this value)} |
|
12 |
-} |
|
13 |
-\description{ |
|
14 |
- Combine independent p-values using the Fischer method |
|
15 |
-} |
|
16 |
-\examples{ |
|
17 |
-p <- c(.1, .01) |
|
18 |
-compute.fischer(p) |
|
19 |
-} |
|
20 |
-\author{ |
|
21 |
- Calin Voichita and Sorin Draghici |
|
22 |
-} |
|
23 |
-\seealso{ |
|
24 |
- \code{\link{pe}},\code{\link{compute.normalInv}} |
|
25 |
-} |
|
26 |
- |
27 | 0 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,32 @@ |
1 |
+\name{compute.fisher} |
|
2 |
+\alias{compute.fisher} |
|
3 |
+\title{Combine independent p-values using the Fisher method} |
|
4 |
+\usage{ |
|
5 |
+ compute.fisher(p, eps = 1e-06) |
|
6 |
+} |
|
7 |
+\arguments{ |
|
8 |
+ \item{p}{a vector of independent p-values} |
|
9 |
+ |
|
10 |
+ \item{eps}{the minimal p-value considered (all p-values |
|
11 |
+ smaller will be set to this value)} |
|
12 |
+} |
|
13 |
+\description{ |
|
14 |
+ Combine independent p-values using the Fisher method |
|
15 |
+} |
|
16 |
+\examples{ |
|
17 |
+p <- c(.1, .01) |
|
18 |
+compute.fisher(p) |
|
19 |
+} |
|
20 |
+\author{ |
|
21 |
+ Calin Voichita and Sorin Draghici |
|
22 |
+} |
|
23 |
+\references{ |
|
24 |
+ Tarca AL., Draghici S., Khatri P., Hassan SS., Kim J., |
|
25 |
+ Kim CJ., Kusanovic JP., Romero R.: "A Signaling Pathway |
|
26 |
+ Impact Analysis for Microarray Experiments", 2008, |
|
27 |
+ Bioinformatics, 2009, 25(1):75-82. |
|
28 |
+} |
|
29 |
+\seealso{ |
|
30 |
+ \code{\link{pe}},\code{\link{compute.normalInv}} |
|
31 |
+} |
|
32 |
+ |
... | ... |
@@ -21,7 +21,12 @@ compute.normalInv(p) |
21 | 21 |
\author{ |
22 | 22 |
Calin Voichita and Sorin Draghici |
23 | 23 |
} |
24 |
+\references{ |
|
25 |
+ Tarca AL., Draghici S., Romero R.: "A Mmore Specific |
|
26 |
+ Method To Combine Perturbation and Over-representation |
|
27 |
+ Evidence in Pathway Analysis", PSB 2010 poster. |
|
28 |
+} |
|
24 | 29 |
\seealso{ |
25 |
- \code{\link{pe}},\code{\link{compute.fischer}} |
|
30 |
+ \code{\link{pe}},\code{\link{compute.fisher}} |
|
26 | 31 |
} |
27 | 32 |
|
... | ... |
@@ -16,7 +16,7 @@ |
16 | 16 |
\item{comb.pv.func}{the function to combine the p-values |
17 | 17 |
- takes as input a vector of p-values and returns the |
18 | 18 |
combined p-value (default: |
19 |
- \code{\link{compute.fischer}}).} |
|
19 |
+ \code{\link{compute.fisher}}).} |
|
20 | 20 |
|
21 | 21 |
\item{adjust.method}{the name of the method to adjust the |
22 | 22 |
p-value (see \code{\link{p.adjust}})} |