Browse code

added plot functionalities; updated documentation; removed 3.0.0 dependency; fixed bugs

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/ROntoTools@75116 bc3139a8-67e5-0310-9ffc-ced21a209358

Calin Voichita authored on 31/03/2013 19:14:34
Showing 24 changed files

... ...
@@ -1,14 +1,31 @@
1 1
 Package: ROntoTools
2 2
 Type: Package
3 3
 Title: R Onto-Tools suite
4
-Version: 0.99.2
4
+Version: 0.99.3
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
8 8
 biocViews: NetworkAnalysis, Microarray, GraphsAndNetworks
9 9
 License: GPL (>= 3)
10
-Depends: R (>= 3.0.0), methods, graph, boot, KEGGREST, KEGGgraph
11
-Suggests: RUnit, BiocGenerics, Rgraphviz
12
-Collate: 'pathwayExpress.R' 'utils.R' 'graphWeights.R' 'keggDataREST.R'
13
-        'AllClasses.R' 'AllGenerics.R' 'nodeWeights-methods.R'
14
-        'pePathway-utils.R' 'Summary-methods.R'
10
+Depends:
11
+    methods,
12
+    graph,
13
+    boot,
14
+    KEGGREST,
15
+    KEGGgraph,
16
+    Rgraphviz
17
+Suggests:
18
+    RUnit,
19
+    BiocGenerics
20
+Collate:
21
+    'pathwayExpress.R'
22
+    'utils.R'
23
+    'graphWeights.R'
24
+    'keggDataREST.R'
25
+    'AllClasses.R'
26
+    'AllGenerics.R'
27
+    'nodeWeights-methods.R'
28
+    'pePathway-utils.R'
29
+    'Summary-methods.R'
30
+    'plot-methods.R'
31
+    'renderInfo-methods.R'
... ...
@@ -1,13 +1,18 @@
1 1
 export(alpha1MR)
2 2
 export(alphaMLG)
3
+export(compute.fischer)
4
+export(compute.normalInv)
3 5
 export(keggPathwayGraphs)
4 6
 export(keggPathwayNames)
5 7
 export(pe)
8
+export(peEdgeRenderInfo)
9
+export(peNodeRenderInfo)
6 10
 export(setEdgeWeights)
7 11
 export(setNodeWeights)
8 12
 exportClasses(pePathway)
9 13
 exportClasses(peRes)
10 14
 exportMethods(nodeWeights)
15
+exportMethods(plot)
11 16
 exportMethods(Summary)
12 17
 import(boot)
13 18
 import(graph)
... ...
@@ -21,7 +21,7 @@
21 21
 #' 
22 22
 #' Calin Voichita and Sorin Draghici
23 23
 #'
24
-#' @seealso \code{\link{pe}} \code{\link{pePathway}}
24
+#' @seealso \code{\link{pe}}, \code{\link{pePathway}}
25 25
 #'
26 26
 #' @aliases peRes-class
27 27
 #' @exportClass peRes
... ...
@@ -39,12 +39,12 @@ setClass("peRes",
39 39
 #' @section Slots:
40 40
 #' 
41 41
 #' \describe{
42
-#'    \item{map}{an object of type graph (e.g., \code{\link{graphNEL}}).}
43
-#'    \item{input}{named vector of fold changes for genes on this pathway. The names of the genes are the orignal IDS used in the analysis}
44
-#'    \item{ref}{vector of reference IDs on this pathway}
45
-#'    \item{boot}{an object of class \code{boot} encoding the bootstrap information.}
46
-#'    \item{PF}{the gene perturbation factors for all genes on the pathway, as computed by Pathway-Express.}
47
-#'    \item{Acc}{the gene accumulations for all genes on the pathway, as computed by Pathway-Express.}
42
+#'    \item{\code{map}:}{an object of type graph (e.g., \code{\link{graphNEL}}).}
43
+#'    \item{\code{input}:}{named vector of fold changes for genes on this pathway. The names of the genes are the orignal IDS used in the analysis}
44
+#'    \item{\code{ref}:}{vector of reference IDs on this pathway}
45
+#'    \item{\code{boot}:}{an object of class \code{boot} encoding the bootstrap information.}
46
+#'    \item{\code{Pert}:}{the gene perturbation factors for all genes on the pathway, as computed by Pathway-Express.}
47
+#'    \item{\code{Acc}:}{the gene accumulations for all genes on the pathway, as computed by Pathway-Express.}
48 48
 #' }
49 49
 #' 
50 50
 #' @author
... ...
@@ -52,7 +52,7 @@ setClass("peRes",
52 52
 #' Calin Voichita and Sorin Draghici
53 53
 #'
54 54
 #'             
55
-#' @seealso \code{\link{pe}} \code{\link{peRes}}
55
+#' @seealso \code{\link{pe}}, \code{\link{peRes}}
56 56
 #' 
57 57
 #' @aliases pePathway-class
58 58
 #' @import graph
... ...
@@ -62,7 +62,7 @@ setClass("pePathway",
62 62
                         input = "numeric",
63 63
                         ref = "character",
64 64
                         boot = "ANY",
65
-                        PF = "numeric",
65
+                        Pert = "numeric",
66 66
                         Acc = "numeric"
67 67
          ), 
68 68
          prototype(map = new("graphNEL")
... ...
@@ -32,7 +32,7 @@
32 32
 #' 
33 33
 #' @seealso
34 34
 #' 
35
-#' \link{nodes} \link{nodeData}
35
+#' \link{nodes}, \link{nodeData}
36 36
 #' 
37 37
 #' @examples
38 38
 #' 
... ...
@@ -43,7 +43,6 @@
43 43
 #' nodeWeights(g, "B")
44 44
 #' nodeWeights(g, attr = "WT", default = 3)
45 45
 #' 
46
-#' @docType methods
47 46
 #' @rdname nodeWeights
48 47
 #' 
49 48
 #' @export
... ...
@@ -47,7 +47,9 @@
47 47
 #' head(Summary(peRes, pathNames = kpn, totalAcc = FALSE, totalPert = FALSE, 
48 48
 #'              pAcc = FALSE, pORA = FALSE, comb.pv = NULL, order.by = "pPert"))
49 49
 #' 
50
+#' @rdname Summary-methods
50 51
 #' 
52
+#' @aliases Summary.peRes
51 53
 #' @aliases Summary,peRes-method
52 54
 #' @export
53 55
 setMethod("Summary", c("x" = "peRes"),
... ...
@@ -74,9 +76,7 @@ setMethod("Summary", c("x" = "peRes"),
74 76
               pStats$pPert <- ifelse(pPert, compute.pPert(pePath), NULL)
75 77
               pStats$pAcc <- ifelse(pAcc, compute.pAcc(pePath), NULL)
76 78
               
77
-              if (pORA & peRes@cutOffFree)
78
-                warning("The over-representaion p-value is not defined for cut-off free analysis and will not be computed!")  
79
-              pStats$pORA <- ifelse(pORA & !peRes@cutOffFree, compute.pORA(pePath, length(peRes@input), length(peRes@ref)), NULL)
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 82
                                      as.numeric(comb.pv.func(unlist(pStats[comb.pv]))), NULL)
... ...
@@ -84,6 +84,17 @@ setMethod("Summary", c("x" = "peRes"),
84 84
               return(unlist(pStats))
85 85
             }
86 86
             
87
+            if (pORA & x@cutOffFree)
88
+            {
89
+              pORA <- FALSE
90
+              if ("pORA" %in% comb.pv)
91
+              {
92
+                order.by <- setdiff(comb.pv, "pORA")[1]
93
+                comb.pv <- NULL
94
+              }
95
+              message("The over-representaion p-value is not defined for cut-off free analysis and will not be computed!")  
96
+            }
97
+            
87 98
             if(!is.null(comb.pv))
88 99
             {
89 100
               if(!all(comb.pv %in% c("pPert","pAcc","pORA")))
... ...
@@ -98,7 +109,7 @@ setMethod("Summary", c("x" = "peRes"),
98 109
               }
99 110
             }
100 111
             
101
-            topStats <- data.frame(do.call(rbind, lapply(peRes@pathways, pathStats)))
112
+            topStats <- data.frame(do.call(rbind, lapply(x@pathways, pathStats)))
102 113
             
103 114
             if(!is.null(pathNames))
104 115
             {
... ...
@@ -58,7 +58,7 @@ loadKEGGpathwayDataREST <- function(organism = "hsa",
58 58
 #' @param targRelTypes target relation types
59 59
 #' @param relPercThresh percentage of the number of relation types over all possible realtions in the pathway
60 60
 #' @param nodeOnlyGraphs allow graphs with no edges
61
-#' @param updateCache re-downlaod KEGG data
61
+#' @param updateCache re-download KEGG data
62 62
 #' @param verbose show progress of downloading and parsing
63 63
 #' 
64 64
 #' @return
... ...
@@ -194,7 +194,7 @@ keggPathwayGraphs <- function(organism = "hsa",
194 194
 #' 
195 195
 #' # to update the pathway cache for human run:
196 196
 #' # kpn <- keggPathwayNames("hsa", updateCache = TRUE)
197
-#' # this is time consuming and depends on the available bandwith.
197
+#' # this is time consuming and depends on the available bandwidth.
198 198
 #' 
199 199
 #' head(kpn)
200 200
 #' 
... ...
@@ -2,7 +2,7 @@
2 2
 #' 
3 3
 #' 
4 4
 #' @param x named vector of log fold changes for the differentially expressed genes; \code{names(x)} must use the same id's as \code{ref} and the nodes of the \code{graphs}
5
-#' @param graphs list of pathway graphs as objects of type \code{graph} (e.g., \code{\link{graphNEL}}); the graphs must be weighted graphs (i.e., have an atrribute \code{weight} for both nodes and edges)
5
+#' @param graphs list of pathway graphs as objects of type \code{graph} (e.g., \code{\link{graphNEL}}); the graphs must be weighted graphs (i.e., have an attribute \code{weight} for both nodes and edges)
6 6
 #' @param ref the reference vector for all genes in the analysis; if the reference is not provided or it is identical to \code{names(x)} a cut-off free analysis is performed
7 7
 #' @param nboot number of bootstrap iterations
8 8
 #' @param verbose print progress output
... ...
@@ -31,7 +31,8 @@
31 31
 #' 
32 32
 #' Draghici S., Khatri P., Tarca A.L., Amin K., Done A., Voichita C., Georgescu C., Romero R.: "A systems biology approach for pathway level analysis". Genome Research, 17, 2007. 
33 33
 #' 
34
-#' @seealso \code{\link{Summary}} \code{\link{keggPathwayGraphs}} \code{\link{setNodeWeights}} \code{\link{setEdgeWeights}}
34
+#' @seealso \code{\link{Summary}}, \code{\link{plot.peRes}}, 
35
+#' \code{\link{keggPathwayGraphs}}, \code{\link{setNodeWeights}}, \code{\link{setEdgeWeights}}
35 36
 #' 
36 37
 #' @examples
37 38
 #' 
... ...
@@ -223,8 +224,8 @@ pe.boot <- function(g, x, ref, nboot, all.genes = F)
223 224
   xx <- rep(0, nrow(inv))
224 225
   names(xx) <- rownames(inv)
225 226
   xx[names(pePath@input)] <- pePath@input  
226
-  pePath@PF = (inv %*% xx)[,1];
227
-  pePath@Acc = pePath@PF - xx
227
+  pePath@Pert = (inv %*% xx)[,1];
228
+  pePath@Acc = pePath@Pert - xx
228 229
     
229 230
   return(pePath) 
230 231
 }
231 232
new file mode 100644
... ...
@@ -0,0 +1,221 @@
1
+#' Plot pathway level statistics
2
+#' 
3
+#' @description Display graphical representation of pathway level statistic like:
4
+#' i) two way comparison between the measured expression change and one of the 
5
+#' factors computed by Pathway-Express (\code{\link{pe}}) or ii) the boostrap 
6
+#' statistics of the same factors.
7
+#' 
8
+#' 
9
+#' @param x an object of type \code{\link{pePathway}}
10
+#' @param y if provided, the factor to be ploted (either \code{Acc} (default) or \code{Pert}; see \code{\link{pePathway}})
11
+#' @param ... Arguments to be passed to methods, such as \code{\link{par}}
12
+#' @param type type of plot (either \code{two.way} (default) or \code{boot})
13
+#' @param eps any value smaller than this will be ploted as 0
14
+#' 
15
+#' @author Calin Voichita and Sorin Draghici
16
+#' 
17
+#' @seealso \code{\link{pe}}, \code{\link{plot.peRes}}, \code{\link{peNodeRenderInfo}}, \code{\link{peEdgeRenderInfo}}
18
+#' 
19
+#' @examples
20
+#' 
21
+#' # load experiment
22
+#' load(system.file("extdata/E-GEOD-21942.topTable.RData", package = "ROntoTools"))
23
+#' fc <- top$logFC[top$adj.P.Val <= .01]
24
+#' names(fc) <- top$entrez[top$adj.P.Val <= .01]
25
+#' ref <- top$entrez
26
+#' 
27
+#' # load the set of pathways
28
+#' kpg <- keggPathwayGraphs("hsa")
29
+#' kpg <- setEdgeWeights(kpg)
30
+#' kpg <- setNodeWeights(kpg, defaultWeight = 1)
31
+#' 
32
+#' # perform the pathway analysis (for more accurate results use nboot = 2000)
33
+#' peRes <- pe(fc, graphs = kpg, ref = ref, nboot = 100, verbose = TRUE)
34
+#' 
35
+#' plot(peRes@@pathways[[50]])
36
+#' 
37
+#' plot(peRes@@pathways[[50]], "Pert", main = "Perturbation factor")
38
+#' 
39
+#' plot(peRes@@pathways[[50]], type = "boot")
40
+#' 
41
+#' plot(peRes@@pathways[[50]], "Pert", type = "boot", main = "Perturbation factor")
42
+#' 
43
+#' @rdname plot.pePathway-methods
44
+#' @name plot.pePathway
45
+#' 
46
+#' @aliases plot.pePathway
47
+#' @aliases plot,pePathway,missing-method
48
+#' @export
49
+setMethod("plot", signature(x="pePathway", y="missing"),
50
+          function(x, y, ..., type = "two.way", eps = 1e-6)
51
+          {
52
+            plot(x, y = "Acc", ..., type = type, eps = eps)           
53
+          }
54
+)
55
+
56
+#' @rdname plot.pePathway-methods
57
+#' 
58
+#' @aliases plot.pePathway
59
+#' @aliases plot,pePathway,character-method
60
+#' @export
61
+setMethod("plot", signature(x="pePathway", y="character"),
62
+          function(x, y, main = "", ... , type = "two.way", eps = 1e-6)
63
+          {
64
+            if (!(y %in% c("Acc", "Pert")))
65
+              stop("Undefined slot selected: ", y,".")
66
+                        
67
+            switch(type,
68
+                   two.way={        
69
+                     iy <- y
70
+                     
71
+                     extInput <- rep(0, length(slot(x, iy)))
72
+                     names(extInput) <- names(slot(x, iy))
73
+                     extInput[names(x@input)] <- x@input
74
+                     
75
+                     cl <- rep("black", length(slot(x, iy)))
76
+                     cl[abs(slot(x, iy)) >= eps] <- "green"
77
+                     cl[abs(extInput) >= eps] <- "blue"
78
+                     cl[abs(slot(x, iy)) >= eps & abs(extInput) >= eps] <- "red"
79
+                     
80
+                     plot(slot(x, iy), extInput, pch = 16, xlab = y, ylab = "Log2 FC", main = main, ...)
81
+                     abline(v=0,h=0, lwd = .5)
82
+                     points(slot(x, iy), extInput, pch = 16, col = cl)
83
+                     
84
+                     return(invisible())
85
+                   },
86
+                   boot={
87
+                     iy <- paste("t", y, sep = "")
88
+                     
89
+                     tB <- x@boot$t0[iy]
90
+                     allB <- x@boot$t[,iy]
91
+                     
92
+                     tB <- (tB - mean(allB)) / sd(allB)
93
+                     allB <- (allB - mean(allB)) / sd(allB)
94
+                     
95
+                     plot(density(allB), xlab = y, main = main, ...)
96
+                     abline(v=0, lwd = .5)
97
+                     abline(v=tB, lwd = 1, col = "red")
98
+                     
99
+                     return(invisible())
100
+                   }
101
+            )
102
+            stop(type, " is not a valid plot type.")
103
+            
104
+          }
105
+)
106
+
107
+#' Plot Pathway-Express result
108
+#' 
109
+#' @description Display a two-way plot using two of the p-values from the Pathway-Express analysis.
110
+#' 
111
+#' @param x an object of type \code{\link{peRes}}
112
+#' @param y vector of two p-values names to be combined using \code{comb.pv.func} (default: \code{c("pAcc", "pORA")}).
113
+#' @param ... Arguments to be passed to methods, such as \code{\link{par}}.
114
+#' @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}}).
116
+#' @param adjust.method the name of the method to adjust the p-value (see \code{\link{p.adjust}})
117
+#' @param threshold corrected p-value threshold
118
+#' @param eps any value smaller than this will be considered as \code{eps} (default: \code{1e-6}).
119
+#' 
120
+#' @author Calin Voichita and Sorin Draghici
121
+#' 
122
+#' @seealso \code{\link{pe}}, \code{\link{Summary.peRes}}, \code{\link{plot.pePathway}}
123
+#' 
124
+#' @examples
125
+#' 
126
+#' # load experiment
127
+#' load(system.file("extdata/E-GEOD-21942.topTable.RData", package = "ROntoTools"))
128
+#' fc <- top$logFC[top$adj.P.Val <= .01]
129
+#' names(fc) <- top$entrez[top$adj.P.Val <= .01]
130
+#' ref <- top$entrez
131
+#' 
132
+#' # load the set of pathways
133
+#' kpg <- keggPathwayGraphs("hsa")
134
+#' kpg <- setEdgeWeights(kpg)
135
+#' kpg <- setNodeWeights(kpg, defaultWeight = 1)
136
+#' 
137
+#' # perform the pathway analysis (for more accurate results use nboot = 2000)
138
+#' peRes <- pe(fc, graphs = kpg, ref = ref, nboot = 100, verbose = TRUE)
139
+#' 
140
+#' plot(peRes)
141
+#' 
142
+#' plot(peRes, c("pPert","pORA"), comb.pv.func = compute.normalInv, threshold = .01)
143
+#' 
144
+#' @rdname plot.peRes-methods
145
+#' @name plot.peRes
146
+#' 
147
+#' @aliases plot.peRes
148
+#' @aliases plot,peRes,missing-method
149
+#' @export
150
+setMethod("plot", signature(x="peRes", y="missing"),
151
+          function(x, y, ... , comb.pv.func = compute.fischer, adjust.method = "fdr", threshold = .05, eps = 1e-6)
152
+          {
153
+            plot(x, y = c("pAcc", "pORA"), ... , comb.pv.func = comb.pv.func, adjust.method = adjust.method,
154
+                 threshold = threshold, eps = eps)
155
+          }
156
+)
157
+
158
+#' @rdname plot.peRes-methods
159
+#' 
160
+#' @aliases plot.peRes
161
+#' @aliases plot,peRes,character-method
162
+#' @export
163
+setMethod("plot", signature(x="peRes", y="character"),
164
+          function(x, y, ... , comb.pv.func = compute.fischer, adjust.method = "fdr", threshold = .05, eps = 1e-6)
165
+          {
166
+            
167
+            st <- Summary(x, comb.pv = y, comb.pv.func = comb.pv.func, adjust.method = adjust.method)
168
+            st <- st[!is.na(st[, paste("pComb", adjust.method, sep = ".")]),]
169
+            
170
+            st[,y[1]][st[,y[1]] <= eps] <- eps
171
+            st[,y[2]][st[,y[2]] <= eps] <- eps
172
+            
173
+            i <- st[, paste("pComb", adjust.method, sep = ".")] <= threshold
174
+            thr.comb <- mean(min(st[!i,"pComb"]),max(st[i,"pComb"]))
175
+            
176
+            xrange <- c(min(-log(st[,y[1]])), max(-log(st[,y[1]])))
177
+            xrange[2] <- xrange[2] + (xrange[2]-xrange[1]) * .1
178
+            yrange <- c(min(-log(st[,y[2]])), max(-log(st[,y[2]]))) 
179
+            yrange[2] <- yrange[2] + (yrange[2]-yrange[1]) * .1
180
+            
181
+            i <- seq(xrange[1], xrange[2], length.out=200)
182
+            j <- seq(yrange[1], yrange[2], length.out=200)
183
+            expGrid <- expand.grid(i,j)
184
+            z <- apply(1/exp(expGrid), 1, comb.pv.func) <= thr.comb
185
+            
186
+            plot(c(min(-log(st[,y[1]])),min(-log(st[,y[2]]))), 
187
+                 xlab = y[1], ylab = y[2], 
188
+                 xlim = xrange,
189
+                 ylim = yrange,
190
+                 col = "white", ...)
191
+            nonSig <- expGrid[!z,][chull(expGrid[!z,]),]
192
+            sig <- expGrid[z,][chull(expGrid[z,]),]
193
+            
194
+            polygon(nonSig, col="gray90")
195
+            polygon(sig, col="lightcyan")
196
+            
197
+            i <- st[, paste("pComb", adjust.method, sep = ".")] <= threshold
198
+            
199
+            points(-log(st[,y[1]]), -log(st[,y[2]]),  xlab = y[1], ylab = y[2], pch = 19)
200
+            if (any(i))
201
+            {
202
+              points(-log(st[,y[1]])[i], -log(st[,y[2]])[i], pch = 21, bg = "red")
203
+              text(-log(st[,y[1]])[i], -log(st[,y[2]])[i] - .5, labels = rownames(st)[i], 
204
+                   cex = .75)
205
+            }
206
+            
207
+            i <- st[, paste(y[1], adjust.method, sep = ".")] <= threshold
208
+            if (any(i))
209
+            {              
210
+              thr1 <- mean(min(st[!i,y[1]]),max(st[i,y[1]]))            
211
+              abline(v = -log(thr1), col = "red", lwd = 2, lty = 2)
212
+            }
213
+            
214
+            i <- st[, paste(y[2], adjust.method, sep = ".")] <= threshold
215
+            if (any(i))
216
+            {
217
+              thr2 <- mean(min(st[!i,y[2]]),max(st[i,y[2]]))                        
218
+              abline(h = -log(thr2), col = "red", lwd = 2, lty = 2)
219
+            }
220
+          }
221
+)
0 222
new file mode 100644
... ...
@@ -0,0 +1,151 @@
1
+#' Extract edge render information from a \code{pePathway} object
2
+#' 
3
+#' @param x an object of class \code{\link{pePathway}}
4
+#' @param pos.col color of the edges with possitive weight
5
+#' @param pos.lty line type of the edges with possitive weight
6
+#' @param pos.ah arrow head of the edges with possitive weight 
7
+#' @param neg.col color of the edges with negative weight
8
+#' @param neg.lty line type of the edges with negative weight 
9
+#' @param neg.ah arrow head of the edges with negative weight 
10
+#' @param zero.col color of the edges with zero weight 
11
+#' @param zero.lty color of the edges with zero weight
12
+#' @param zero.ah color of the edges with zero weight
13
+#' 
14
+#' @value a named list as expected by \code{\link{edgeRenderInfo}}
15
+#' 
16
+#' @author Calin Voichita and Sorin Draghici
17
+#' 
18
+#' @seealso \code{\link{edgeRenderInfo}},\code{\link{par}}
19
+#' 
20
+#' @examples
21
+#' 
22
+#' # load experiment
23
+#' load(system.file("extdata/E-GEOD-21942.topTable.RData", package = "ROntoTools"))
24
+#' fc <- top$logFC[top$adj.P.Val <= .01]
25
+#' names(fc) <- top$entrez[top$adj.P.Val <= .01]
26
+#' ref <- top$entrez
27
+#' 
28
+#' # load the set of pathways
29
+#' kpg <- keggPathwayGraphs("hsa")
30
+#' kpg <- setEdgeWeights(kpg)
31
+#' kpg <- setNodeWeights(kpg, defaultWeight = 1)
32
+#' 
33
+#' # perform the pathway analysis
34
+#' peRes <- pe(fc, graphs = kpg, ref = ref, nboot = 100, verbose = TRUE)
35
+#' 
36
+#' p <- peRes@@pathways[[50]]
37
+#' g <- layoutGraph(p@@map, layoutType = "dot")
38
+#' graphRenderInfo(g) <- list(fixedsize = FALSE)
39
+#' edgeRenderInfo(g) <- peEdgeRenderInfo(p)
40
+#' nodeRenderInfo(g) <- peNodeRenderInfo(p)
41
+#' # notice the different type of edges in the graph (solid/dashed/dotted) 
42
+#' renderGraph(g)
43
+#' 
44
+#' @export
45
+peEdgeRenderInfo <- function(x,
46
+                             pos.col = "black", pos.lty = "solid", pos.ah = "vee",
47
+                             neg.col = "black", neg.lty = "dashed", neg.ah = "tee",
48
+                             zero.col = "lightgray", zero.lty = "dotted", zero.ah = "none")
49
+{
50
+  stopifnot(class(x) == "pePathway")
51
+  
52
+  ew <- unlist(edgeWeights(x@map))
53
+  
54
+  aHead <- rep(zero.ah, length(edgeNames(x@map)))
55
+  names(aHead) <- edgeNames(x@map)
56
+  aHead[ew > 0] <- pos.ah
57
+  aHead[ew < 0] <- neg.ah
58
+  aHead <- aHead[setdiff(seq(along=ew), removedEdges(x@map))]
59
+  
60
+  eCol <- rep(zero.col, length(edgeNames(x@map)))
61
+  names(eCol) <- edgeNames(x@map)
62
+  eCol[ew > 0] <- pos.col
63
+  eCol[ew < 0] <- neg.col
64
+  eCol <- eCol[setdiff(seq(along=ew), removedEdges(x@map))]
65
+  
66
+  eStyle <- rep(zero.lty, length(edgeNames(x@map)))
67
+  names(eStyle) <- edgeNames(x@map)  
68
+  eStyle[ew > 0] <- pos.lty
69
+  eStyle[ew < 0] <- neg.lty
70
+  eStyle <- eStyle[setdiff(seq(along=ew), removedEdges(x@map))]
71
+  
72
+  return(list(
73
+    arrowhead = aHead,
74
+    col = eCol,
75
+    lty = eStyle
76
+  ))
77
+}
78
+
79
+#' Extract node render information from a \code{pePathway} object
80
+#' 
81
+#' @param x an object of class \code{\link{pePathway}}
82
+#' @param y a string representing the factor to be represented (\code{Pert, Acc} or \code{input}; see \code{\link{pePathway}})
83
+#' @param input.shape shape of nodes that have measured expression change
84
+#' @param default.shape shape of all other nodes
85
+#' @param pos.col color of nodes with a positive \code{y} factor
86
+#' @param neg.col color of nodes with a negative \code{y} factor
87
+#' @param zero.col color of nodes with the \code{y} factor equal to zero
88
+#' 
89
+#' @value a named list as expected by \code{\link{nodeRenderInfo}}
90
+#' 
91
+#' @author Calin Voichita and Sorin Draghici
92
+#' 
93
+#' @seealso \code{\link{nodeRenderInfo}},\code{\link{par}}
94
+#' 
95
+#' @examples
96
+#' 
97
+#' # load experiment
98
+#' load(system.file("extdata/E-GEOD-21942.topTable.RData", package = "ROntoTools"))
99
+#' fc <- top$logFC[top$adj.P.Val <= .01]
100
+#' names(fc) <- top$entrez[top$adj.P.Val <= .01]
101
+#' ref <- top$entrez
102
+#' 
103
+#' # load the set of pathways
104
+#' kpg <- keggPathwayGraphs("hsa")
105
+#' kpg <- setEdgeWeights(kpg)
106
+#' kpg <- setNodeWeights(kpg, defaultWeight = 1)
107
+#' 
108
+#' # perform the pathway analysis
109
+#' peRes <- pe(fc, graphs = kpg, ref = ref, nboot = 100, verbose = TRUE)
110
+#' 
111
+#' p <- peRes@@pathways[[50]]
112
+#' g <- layoutGraph(p@@map, layoutType = "dot")
113
+#' graphRenderInfo(g) <- list(fixedsize = FALSE)
114
+#' edgeRenderInfo(g) <- peEdgeRenderInfo(p)
115
+#' nodeRenderInfo(g) <- peNodeRenderInfo(p)
116
+#' # notice the different type of nodes in the graph (box/circle)
117
+#' # the color of each node represents the perturbation (red = positive, blue = negative)
118
+#' # the shade represents the stregth of the perturbation 
119
+#' renderGraph(g)
120
+#' 
121
+#' nodeRenderInfo(g) <- peNodeRenderInfo(p, "Acc")
122
+#' # now, the color of each node represents the accumulation (red = positive, blue = negative)
123
+#' # notice that square nodes with no parents have no accumulation
124
+#' renderGraph(g)
125
+#' 
126
+#' @export
127
+peNodeRenderInfo <- function(x, y = "Pert",
128
+                             input.shape = "box",
129
+                             default.shape = "ellipse",
130
+                             pos.col = "red",
131
+                             neg.col = "blue",
132
+                             zero.col = "white")
133
+{
134
+  stopifnot(class(x) == "pePathway")
135
+  stopifnot(y %in%  c("input", "Pert", "Acc"))
136
+  
137
+  nShape <- rep(default.shape, length(nodes(x@map)))
138
+  names(nShape) <- nodes(x@map)
139
+  nShape[names(x@input)] <- input.shape
140
+  
141
+  nFillColor <- rep(zero.col, length(nodes(x@map)))
142
+  names(nFillColor) <- nodes(x@map)
143
+  pf <- slot(x, y)
144
+  nFillColor[pf <= 0] <- colorRampPalette(c(zero.col,neg.col))(256)[as.numeric(cut(abs(pf[pf<=0]), 256))]                                  
145
+  nFillColor[pf >= 0] <- colorRampPalette(c(zero.col,pos.col))(256)[as.numeric(cut(abs(pf[pf>=0]), 256))]
146
+  
147
+  return(list(
148
+    shape = nShape,
149
+    fill = nFillColor
150
+  ))
151
+}
0 152
\ No newline at end of file
... ...
@@ -1,22 +1,3 @@
1
-
2
-#' @keywords internal
3
-pf2col <- function(pf)
4
-{
5
-  retcol <- rep("white", length(pf))
6
-  
7
-  ### possitive
8
-  i <- pf > 0
9
-  #retcol[i] <- rainbow(256, start = 1/6, end = 2/6)[ceiling(pf[i] / max(pf[i]) * 256)]  
10
-  retcol[i] <- colorRampPalette(c("white", "red"))(256)[ceiling(pf[i] / max(pf[i]) * 256)]
11
-  
12
-  i <- pf < 0
13
-  #retcol[i] <- rainbow(256, start = 1, end = 1/6)[256:1][ceiling(abs(pf[i]) / max(abs(pf[i])) * 256)]
14
-  retcol[i] <- colorRampPalette(c("white", "blue"))(256)[ceiling(abs(pf[i]) / max(abs(pf[i])) * 256)]
15
-  
16
-  names(retcol) <- names(pf)
17
-  return(retcol)
18
-}
19
-
20 1
 #' @keywords internal
21 2
 addNames <- function(x, nms)
22 3
 {
... ...
@@ -33,13 +14,55 @@ addNames <- function(x, nms)
33 14
 compute.bootPV <- function(real, dist)
34 15
   ( sum(abs(dist - mean(dist)) > abs(real - mean(dist))) + 1 ) / (1 + length(dist))
35 16
 
36
-#' @keywords internal
37
-compute.fischer <- function(p)
38
-  {k <- p[1] * p[2]; return(k-k*log(k))}
17
+#' Combine independent p-values using the Fischer method
18
+#' 
19
+#' @param p a vector of independent p-values
20
+#' @param eps the minimal p-value considered (all p-values smaller will be set to this value)
21
+#' 
22
+#' @value the combined p-value
23
+#' 
24
+#' @author Calin Voichita and Sorin Draghici
25
+#' 
26
+#' @seealso \code{\link{pe}},\code{\link{compute.normalInv}}
27
+#' 
28
+#' @examples
29
+#' 
30
+#' p <- c(.1, .01)
31
+#' compute.fischer(p)
32
+#' 
33
+#' @export
34
+compute.fischer <- function(p, eps = 1e-6)
35
+{
36
+  stopifnot(any(p >= 0 & p<=1))  
37
+  p[p < eps] <- eps
38
+  
39
+  k <- prod(p); 
40
+  return(k-k*log(k))
41
+}
39 42
 
40
-#' @keywords internal
41
-compute.normalInv <- function(p)
42
-  pnorm( (qnorm(p[1]) + qnorm(p[2])) / sqrt(2) )
43
+#' Combine independent p-values using the normal inversion method
44
+#' 
45
+#' @param p a vector of independent p-values
46
+#' @param eps the minimal p-value considered (all p-values smaller will be set to this value)
47
+#' 
48
+#' @value the combined p-value
49
+#' 
50
+#' @author Calin Voichita and Sorin Draghici
51
+#' 
52
+#' @seealso \code{\link{pe}},\code{\link{compute.fischer}}
53
+#' 
54
+#' @examples
55
+#' 
56
+#' p <- c(.1, .01)
57
+#' compute.normalInv(p)
58
+#' 
59
+#' @export
60
+compute.normalInv <- function(p, eps = 1e-6)
61
+{
62
+  stopifnot(any(p >= 0 & p<=1))  
63
+  p[p < eps] <- eps
64
+  return(pnorm(sum(sapply(p, qnorm)) / sqrt(length(p))))
65
+}
43 66
 
44 67
 #` @keywords internal
45 68
 graph2ftM <- function(g)
46 69
similarity index 99%
47 70
rename from man/Summary.Rd
48 71
rename to man/Summary-methods.Rd
... ...
@@ -1,6 +1,6 @@
1 1
 \name{Summary}
2
-\alias{Summary}
3 2
 \alias{Summary,peRes-method}
3
+\alias{Summary.peRes}
4 4
 \title{Summarize the results of a Pathway-Express analysis}
5 5
 \arguments{
6 6
   \item{x}{Pathways-Express result object obtained using
7 7
new file mode 100644
... ...
@@ -0,0 +1,26 @@
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
+
0 27
new file mode 100644
... ...
@@ -0,0 +1,27 @@
1
+\name{compute.normalInv}
2
+\alias{compute.normalInv}
3
+\title{Combine independent p-values using the normal inversion method}
4
+\usage{
5
+  compute.normalInv(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 normal inversion
15
+  method
16
+}
17
+\examples{
18
+p <- c(.1, .01)
19
+compute.normalInv(p)
20
+}
21
+\author{
22
+  Calin Voichita and Sorin Draghici
23
+}
24
+\seealso{
25
+  \code{\link{pe}},\code{\link{compute.fischer}}
26
+}
27
+
... ...
@@ -17,7 +17,7 @@
17 17
 
18 18
   \item{nodeOnlyGraphs}{allow graphs with no edges}
19 19
 
20
-  \item{updateCache}{re-downlaod KEGG data}
20
+  \item{updateCache}{re-download KEGG data}
21 21
 
22 22
   \item{verbose}{show progress of downloading and parsing}
23 23
 }
... ...
@@ -24,7 +24,7 @@ kpn <- keggPathwayNames("hsa")
24 24
 
25 25
 # to update the pathway cache for human run:
26 26
 # kpn <- keggPathwayNames("hsa", updateCache = TRUE)
27
-# this is time consuming and depends on the available bandwith.
27
+# this is time consuming and depends on the available bandwidth.
28 28
 
29 29
 head(kpn)
30 30
 }
... ...
@@ -1,4 +1,3 @@
1
-\docType{methods}
2 1
 \name{nodeWeights}
3 2
 \alias{nodeWeights}
4 3
 \alias{nodeWeights,graph,character-method}
... ...
@@ -68,6 +67,6 @@ nodeWeights(g, attr = "WT", default = 3)
68 67
   Calin Voichita and Sorin Draghici
69 68
 }
70 69
 \seealso{
71
-  \link{nodes} \link{nodeData}
70
+  \link{nodes}, \link{nodeData}
72 71
 }
73 72
 
... ...
@@ -13,7 +13,7 @@
13 13
 
14 14
   \item{graphs}{list of pathway graphs as objects of type
15 15
   \code{graph} (e.g., \code{\link{graphNEL}}); the graphs
16
-  must be weighted graphs (i.e., have an atrribute
16
+  must be weighted graphs (i.e., have an attribute
17 17
   \code{weight} for both nodes and edges)}
18 18
 
19 19
   \item{ref}{the reference vector for all genes in the
... ...
@@ -118,7 +118,9 @@ head(Summary(peRes))
118 118
   17, 2007.
119 119
 }
120 120
 \seealso{
121
-  \code{\link{Summary}} \code{\link{keggPathwayGraphs}}
122
-  \code{\link{setNodeWeights}} \code{\link{setEdgeWeights}}
121
+  \code{\link{Summary}}, \code{\link{plot.peRes}},
122
+  \code{\link{keggPathwayGraphs}},
123
+  \code{\link{setNodeWeights}},
124
+  \code{\link{setEdgeWeights}}
123 125
 }
124 126
 
125 127
new file mode 100644
... ...
@@ -0,0 +1,68 @@
1
+\name{peEdgeRenderInfo}
2
+\alias{peEdgeRenderInfo}
3
+\title{Extract edge render information from a \code{pePathway} object}
4
+\usage{
5
+  peEdgeRenderInfo(x, pos.col = "black", pos.lty = "solid",
6
+    pos.ah = "vee", neg.col = "black", neg.lty = "dashed",
7
+    neg.ah = "tee", zero.col = "lightgray",
8
+    zero.lty = "dotted", zero.ah = "none")
9
+}
10
+\arguments{
11
+  \item{x}{an object of class \code{\link{pePathway}}}
12
+
13
+  \item{pos.col}{color of the edges with possitive weight}
14
+
15
+  \item{pos.lty}{line type of the edges with possitive
16
+  weight}
17
+
18
+  \item{pos.ah}{arrow head of the edges with possitive
19
+  weight}
20
+
21
+  \item{neg.col}{color of the edges with negative weight}
22
+
23
+  \item{neg.lty}{line type of the edges with negative
24
+  weight}
25
+
26
+  \item{neg.ah}{arrow head of the edges with negative
27
+  weight}
28
+
29
+  \item{zero.col}{color of the edges with zero weight}
30
+
31
+  \item{zero.lty}{color of the edges with zero weight}
32
+
33
+  \item{zero.ah}{color of the edges with zero weight}
34
+}
35
+\description{
36
+  Extract edge render information from a \code{pePathway}
37
+  object
38
+}
39
+\examples{
40
+# load experiment
41
+load(system.file("extdata/E-GEOD-21942.topTable.RData", package = "ROntoTools"))
42
+fc <- top$logFC[top$adj.P.Val <= .01]
43
+names(fc) <- top$entrez[top$adj.P.Val <= .01]
44
+ref <- top$entrez
45
+
46
+# load the set of pathways
47
+kpg <- keggPathwayGraphs("hsa")
48
+kpg <- setEdgeWeights(kpg)
49
+kpg <- setNodeWeights(kpg, defaultWeight = 1)
50
+
51
+# perform the pathway analysis
52
+peRes <- pe(fc, graphs = kpg, ref = ref, nboot = 100, verbose = TRUE)
53
+
54
+p <- peRes@pathways[[50]]
55
+g <- layoutGraph(p@map, layoutType = "dot")
56
+graphRenderInfo(g) <- list(fixedsize = FALSE)
57
+edgeRenderInfo(g) <- peEdgeRenderInfo(p)
58
+nodeRenderInfo(g) <- peNodeRenderInfo(p)
59
+# notice the different type of edges in the graph (solid/dashed/dotted)
60
+renderGraph(g)
61
+}
62
+\author{
63
+  Calin Voichita and Sorin Draghici
64
+}
65
+\seealso{
66
+  \code{\link{edgeRenderInfo}},\code{\link{par}}
67
+}
68
+
0 69
new file mode 100644
... ...
@@ -0,0 +1,70 @@
1
+\name{peNodeRenderInfo}
2
+\alias{peNodeRenderInfo}
3
+\title{Extract node render information from a \code{pePathway} object}
4
+\usage{
5
+  peNodeRenderInfo(x, y = "Pert", input.shape = "box",
6
+    default.shape = "ellipse", pos.col = "red",
7
+    neg.col = "blue", zero.col = "white")
8
+}
9
+\arguments{
10
+  \item{x}{an object of class \code{\link{pePathway}}}
11
+
12
+  \item{y}{a string representing the factor to be
13
+  represented (\code{Pert, Acc} or \code{input}; see
14
+  \code{\link{pePathway}})}
15
+
16
+  \item{input.shape}{shape of nodes that have measured
17
+  expression change}
18
+
19
+  \item{default.shape}{shape of all other nodes}
20
+
21
+  \item{pos.col}{color of nodes with a positive \code{y}
22
+  factor}
23
+
24
+  \item{neg.col}{color of nodes with a negative \code{y}
25
+  factor}
26
+
27
+  \item{zero.col}{color of nodes with the \code{y} factor
28
+  equal to zero}
29
+}
30
+\description{
31
+  Extract node render information from a \code{pePathway}
32
+  object
33
+}
34
+\examples{
35
+# load experiment
36
+load(system.file("extdata/E-GEOD-21942.topTable.RData", package = "ROntoTools"))
37
+fc <- top$logFC[top$adj.P.Val <= .01]
38
+names(fc) <- top$entrez[top$adj.P.Val <= .01]
39
+ref <- top$entrez
40
+
41
+# load the set of pathways
42
+kpg <- keggPathwayGraphs("hsa")
43
+kpg <- setEdgeWeights(kpg)
44
+kpg <- setNodeWeights(kpg, defaultWeight = 1)
45
+
46
+# perform the pathway analysis
47
+peRes <- pe(fc, graphs = kpg, ref = ref, nboot = 100, verbose = TRUE)
48
+
49
+p <- peRes@pathways[[50]]
50
+g <- layoutGraph(p@map, layoutType = "dot")
51
+graphRenderInfo(g) <- list(fixedsize = FALSE)
52
+edgeRenderInfo(g) <- peEdgeRenderInfo(p)
53
+nodeRenderInfo(g) <- peNodeRenderInfo(p)
54
+# notice the different type of nodes in the graph (box/circle)
55
+# the color of each node represents the perturbation (red = positive, blue = negative)
56
+# the shade represents the stregth of the perturbation
57
+renderGraph(g)
58
+
59
+nodeRenderInfo(g) <- peNodeRenderInfo(p, "Acc")
60
+# now, the color of each node represents the accumulation (red = positive, blue = negative)
61
+# notice that square nodes with no parents have no accumulation
62
+renderGraph(g)
63
+}
64
+\author{
65
+  Calin Voichita and Sorin Draghici
66
+}
67
+\seealso{
68
+  \code{\link{nodeRenderInfo}},\code{\link{par}}
69
+}
70
+
... ...
@@ -7,22 +7,23 @@
7 7
   single pathway
8 8
 }
9 9
 \section{Slots}{
10
-  \describe{ \item{map}{an object of type graph (e.g.,
11
-  \code{\link{graphNEL}}).} \item{input}{named vector of
12
-  fold changes for genes on this pathway. The names of the
13
-  genes are the orignal IDS used in the analysis}
14
-  \item{ref}{vector of reference IDs on this pathway}
15
-  \item{boot}{an object of class \code{boot} encoding the
16
-  bootstrap information.} \item{PF}{the gene perturbation
17
-  factors for all genes on the pathway, as computed by
18
-  Pathway-Express.} \item{Acc}{the gene accumulations for
19
-  all genes on the pathway, as computed by
20
-  Pathway-Express.} }
10
+  \describe{ \item{\code{map}:}{an object of type graph
11
+  (e.g., \code{\link{graphNEL}}).}
12
+  \item{\code{input}:}{named vector of fold changes for
13
+  genes on this pathway. The names of the genes are the
14
+  orignal IDS used in the analysis}
15
+  \item{\code{ref}:}{vector of reference IDs on this
16
+  pathway} \item{\code{boot}:}{an object of class
17
+  \code{boot} encoding the bootstrap information.}
18
+  \item{\code{Pert}:}{the gene perturbation factors for all
19
+  genes on the pathway, as computed by Pathway-Express.}
20
+  \item{\code{Acc}:}{the gene accumulations for all genes
21
+  on the pathway, as computed by Pathway-Express.} }
21 22
 }
22 23
 \author{
23 24
   Calin Voichita and Sorin Draghici
24 25
 }
25 26
 \seealso{
26
-  \code{\link{pe}} \code{\link{peRes}}
27
+  \code{\link{pe}}, \code{\link{peRes}}
27 28
 }
28 29
 
... ...
@@ -27,6 +27,6 @@
27 27
   Calin Voichita and Sorin Draghici
28 28
 }
29 29
 \seealso{
30
-  \code{\link{pe}} \code{\link{pePathway}}
30
+  \code{\link{pe}}, \code{\link{pePathway}}
31 31
 }
32 32
 
33 33
new file mode 100644
... ...
@@ -0,0 +1,60 @@
1
+\name{plot.pePathway}
2
+\alias{plot,pePathway,character-method}
3
+\alias{plot,pePathway,missing-method}
4
+\alias{plot.pePathway}
5
+\title{Plot pathway level statistics}
6
+\arguments{
7
+  \item{x}{an object of type \code{\link{pePathway}}}
8
+
9
+  \item{y}{if provided, the factor to be ploted (either
10
+  \code{Acc} (default) or \code{Pert}; see
11
+  \code{\link{pePathway}})}
12
+
13
+  \item{...}{Arguments to be passed to methods, such as
14
+  \code{\link{par}}}
15
+
16
+  \item{type}{type of plot (either \code{two.way} (default)
17
+  or \code{boot})}
18
+
19
+  \item{eps}{any value smaller than this will be ploted as
20
+  0}
21
+}
22
+\description{
23
+  Display graphical representation of pathway level
24
+  statistic like: i) two way comparison between the
25
+  measured expression change and one of the factors
26
+  computed by Pathway-Express (\code{\link{pe}}) or ii) the
27
+  boostrap statistics of the same factors.
28
+}
29
+\examples{
30
+# load experiment
31
+load(system.file("extdata/E-GEOD-21942.topTable.RData", package = "ROntoTools"))
32
+fc <- top$logFC[top$adj.P.Val <= .01]
33
+names(fc) <- top$entrez[top$adj.P.Val <= .01]
34
+ref <- top$entrez
35
+
36
+# load the set of pathways
37
+kpg <- keggPathwayGraphs("hsa")
38
+kpg <- setEdgeWeights(kpg)
39
+kpg <- setNodeWeights(kpg, defaultWeight = 1)
40
+
41
+# perform the pathway analysis (for more accurate results use nboot = 2000)
42
+peRes <- pe(fc, graphs = kpg, ref = ref, nboot = 100, verbose = TRUE)
43
+
44
+plot(peRes@pathways[[50]])
45
+
46
+plot(peRes@pathways[[50]], "Pert", main = "Perturbation factor")
47
+
48
+plot(peRes@pathways[[50]], type = "boot")
49
+
50
+plot(peRes@pathways[[50]], "Pert", type = "boot", main = "Perturbation factor")
51
+}
52
+\author{
53
+  Calin Voichita and Sorin Draghici
54
+}
55
+\seealso{
56
+  \code{\link{pe}}, \code{\link{plot.peRes}},
57
+  \code{\link{peNodeRenderInfo}},
58
+  \code{\link{peEdgeRenderInfo}}
59
+}
60
+
0 61
new file mode 100644
... ...
@@ -0,0 +1,59 @@
1
+\name{plot.peRes}
2
+\alias{plot,peRes,character-method}
3
+\alias{plot,peRes,missing-method}
4
+\alias{plot.peRes}
5
+\title{Plot Pathway-Express result}
6
+\arguments{
7
+  \item{x}{an object of type \code{\link{peRes}}}
8
+
9
+  \item{y}{vector of two p-values names to be combined
10
+  using \code{comb.pv.func} (default: \code{c("pAcc",
11
+  "pORA")}).}
12
+
13
+  \item{...}{Arguments to be passed to methods, such as
14
+  \code{\link{par}}.}
15
+
16
+  \item{comb.pv.func}{the function to combine the p-values
17
+  - takes as input a vector of p-values and returns the
18
+  combined p-value (default:
19
+  \code{\link{compute.fischer}}).}
20
+
21
+  \item{adjust.method}{the name of the method to adjust the
22
+  p-value (see \code{\link{p.adjust}})}
23
+
24
+  \item{threshold}{corrected p-value threshold}
25
+
26
+  \item{eps}{any value smaller than this will be considered
27
+  as \code{eps} (default: \code{1e-6}).}
28
+}
29
+\description{
30
+  Display a two-way plot using two of the p-values from the
31
+  Pathway-Express analysis.
32
+}
33
+\examples{
34
+# load experiment
35
+load(system.file("extdata/E-GEOD-21942.topTable.RData", package = "ROntoTools"))
36
+fc <- top$logFC[top$adj.P.Val <= .01]
37
+names(fc) <- top$entrez[top$adj.P.Val <= .01]
38
+ref <- top$entrez
39
+
40
+# load the set of pathways
41
+kpg <- keggPathwayGraphs("hsa")
42
+kpg <- setEdgeWeights(kpg)
43
+kpg <- setNodeWeights(kpg, defaultWeight = 1)
44
+
45
+# perform the pathway analysis (for more accurate results use nboot = 2000)
46
+peRes <- pe(fc, graphs = kpg, ref = ref, nboot = 100, verbose = TRUE)
47
+
48
+plot(peRes)
49
+
50
+plot(peRes, c("pPert","pORA"), comb.pv.func = compute.normalInv, threshold = .01)
51
+}
52
+\author{
53
+  Calin Voichita and Sorin Draghici
54
+}
55
+\seealso{
56
+  \code{\link{pe}}, \code{\link{Summary.peRes}},
57
+  \code{\link{plot.pePathway}}
58
+}
59
+
... ...
@@ -173,7 +173,7 @@ Up to this point all the pieces need for the analysis have been assembled:
173 173
 \item the experiment data - \Robject{fc} and \Robject{ref}
174 174
 \end{itemize}
175 175
 
176
-\noindent To perform the analysis the function \Rfunction{pe} is used (increase the parameter \Robject{nboot} to obtain more accurate results:
176
+\noindent To perform the analysis the function \Rfunction{pe} is used (increase the parameter \Robject{nboot} to obtain more accurate results):
177 177
 <<eval=TRUE, echo=TRUE>>=
178 178
 peRes <- pe(x = fc, graphs = kpg, ref = ref,  nboot = 200, verbose = FALSE)
179 179
 @
... ...
@@ -186,34 +186,108 @@ head(Summary(peRes, pathNames = kpn, totalAcc = FALSE, totalPert = FALSE,
186 186
              pAcc = FALSE, pORA = FALSE, comb.pv = NULL, order.by = "pPert"))
187 187
 @
188 188
 
189
-Here is an example of how to visualize a pathway as analyzed by Pathway-Express (see Fig.~\ref{fig:thyroid}):
189
+\subsection{Graphical representation of results}
190 190
 
191
-<<label=fig1plot,include=FALSE>>=
192
-plot(peRes@pathways[["path:hsa05216"]]@map)
191
+To visualize the summary of the Pathway-Express results use the function \Rfunction{plot} (see Fig.~\ref{fig:twoway}):
192
+
193
+<<label=peRes_twoway1,include=FALSE>>=
194
+plot(peRes)
195
+@
196
+
197
+<<label=peRes_twoway2,include=FALSE>>=
198
+plot(peRes, c("pAcc", "pORA"), comb.pv.func = compute.normalInv, threshold = .01)
193 199
 @
194 200
 
195 201
 \begin{figure}
196 202
 \begin{center}
203
+\resizebox{!}{4in}{
197 204
 <<label=fig1,fig=TRUE,echo=FALSE>>=
198
-<<fig1plot>>
205
+<<peRes_twoway1>>
199 206
 @
207
+}
208
+\resizebox{!}{4in}{
209
+<<label=fig2,fig=TRUE,echo=FALSE>>=
210
+<<peRes_twoway2>>
211
+@
212
+}
200 213
 \end{center}
201
-\caption{Thytroid cancer pathway map as used by Pathway-Express}
202
-\label{fig:thyroid}
214
+\caption{Two-way plot of Pathway-Express result}
215
+\label{fig:twoway}
203 216
 \end{figure}
204 217
 
205
-Other information can also be extracted from the \Robject{peRes}, like the genes with assigned fold changes on the current pathway:
206
-<<eval=TRUE, echo=TRUE>>=
207
-peRes@pathways[["path:hsa05216"]]@input
218
+Pathway level statistics can also be displayed one at a time using the function \Rfunction{plot}~(see Fig.~\ref{fig:pePathway_pAcc}):
219
+
220
+<<label=pePathway_twoway_Acc,include=FALSE>>=
221
+plot(peRes@pathways[["path:hsa05216"]], type = "two.way")
208 222
 @
209
-\noindent the reference genes in the pathway:
210
-<<eval=TRUE, echo=TRUE>>=
211
-peRes@pathways[["path:hsa05216"]]@ref
223
+
224
+<<label=pePathway_boot_Acc,include=FALSE>>=
225
+plot(peRes@pathways[["path:hsa05216"]], type = "boot")
212 226
 @
213
-\noindent the amount of perturbation at each gene:
214
-<<eval=TRUE, echo=TRUE>>=
215
-peRes@pathways[["path:hsa05216"]]@PF
227
+
228
+\begin{figure}
229
+\begin{center}
230
+\resizebox{!}{4in}{
231
+<<label=fig3,fig=TRUE,echo=FALSE>>=
232
+<<pePathway_twoway_Acc>>
233
+@
234
+}
235
+\resizebox{!}{4in}{
236
+<<label=fig4,fig=TRUE,echo=FALSE>>=
237
+<<pePathway_boot_Acc>>
238
+@
239
+}
240
+\end{center}
241
+\caption{Pathway level statistiscs: perturbation accumulation versus the measured expression change (above) and the bootstrap simulations of the perturbation accumulation (below).}
242
+\label{fig:pePathway_pAcc}
243
+\end{figure}
244
+
245
+To visualize the propagation across the pathway, two functions - \Rfunction{peNodeRenderInfo} and \Rfunction{peEdgeRenderInfo} - are provided to extract the required information from a \Robject{pePathway} object:
246
+
247
+<<label=pePathway_graph_Pert,include=FALSE>>=
248
+p <- peRes@pathways[["path:hsa05216"]]
249
+g <- layoutGraph(p@map, layoutType = "dot")
250
+graphRenderInfo(g) <- list(fixedsize = FALSE)
251
+edgeRenderInfo(g) <- peEdgeRenderInfo(p)
252
+nodeRenderInfo(g) <- peNodeRenderInfo(p)
253
+renderGraph(g)
254
+@
255
+
256
+This is the \emph{Thyroid cancer} signaling pathway and is shown in Fig.~\ref{fig:pePathway_graph}. Another example is the \emph{T cell receptor signaling pathway} and is presented in Fig.~\ref{fig:pePathway_graph2}.
257
+
258
+<<label=pePathway_graph_Pert2,include=FALSE,echo=FALSE>>=
259
+p <- peRes@pathways[["path:hsa04660"]]
260
+g <- layoutGraph(p@map, layoutType = "dot")
261
+graphRenderInfo(g) <- list(fixedsize = FALSE)
262
+edgeRenderInfo(g) <- peEdgeRenderInfo(p)
263
+nodeRenderInfo(g) <- peNodeRenderInfo(p)
264
+renderGraph(g)
265
+@
266
+
267
+
268
+\begin{figure}
269
+\begin{center}
270
+\resizebox{!}{4in}{
271
+<<label=fig5,fig=TRUE,echo=FALSE>>=
272
+<<pePathway_graph_Pert>>
216 273
 @
274
+}
275
+\end{center}
276
+\caption{Perturbation propagation on the  \emph{Thyroid cancer signaling pathway}. }
277
+\label{fig:pePathway_graph}
278
+\end{figure}
279
+
280
+\begin{figure}
281
+\begin{center}
282
+\resizebox{!}{6.5in}{
283
+<<label=fig6,fig=TRUE,echo=FALSE>>=
284
+<<pePathway_graph_Pert2>>
285
+@
286
+}
287
+\end{center}
288
+\caption{Perturbation propagation on the \emph{T cell receptor signaling pathway}.}
289
+\label{fig:pePathway_graph2}
290
+\end{figure}
217 291
 
218 292
 
219 293
 \bibliographystyle{abbrv}