Browse code

added novel method and increase version to 1.99

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

Calin Voichita authored on 15/04/2016 05:40:35
Showing 45 changed files

... ...
@@ -1,10 +1,11 @@
1 1
 Package: ROntoTools
2 2
 Type: Package
3 3
 Title: R Onto-Tools suite
4
-Version: 1.11.0
5
-Author: Calin Voichita <calin@wayne.edu> and Sorin Draghici <sorin@wayne.edu>
4
+Version: 1.99.0
5
+Author: Calin Voichita <calin@wayne.edu> and Sahar Ansari
6
+    <saharansari@wayne.edu> and Sorin Draghici <sorin@wayne.edu>
6 7
 Maintainer: Calin Voichita <calin@wayne.edu>
7
-Description: Suite of tools for functional analysis
8
+Description: Suite of tools for functional analysis.
8 9
 biocViews: NetworkAnalysis, Microarray, GraphsAndNetworks
9 10
 License: CC BY-NC-ND 4.0 + file LICENSE
10 11
 Depends:
... ...
@@ -17,15 +18,4 @@ Depends:
17 18
 Suggests:
18 19
     RUnit,
19 20
     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'
21
+RoxygenNote: 5.0.1
... ...
@@ -1,22 +1,29 @@
1
+# Generated by roxygen2: do not edit by hand
2
+
3
+S3method(summary,pDisRes)
4
+S3method(summary,peRes)
1 5
 export(alpha1MR)
2 6
 export(alphaMLG)
3 7
 export(compute.fisher)
4 8
 export(compute.normalInv)
5 9
 export(keggPathwayGraphs)
6 10
 export(keggPathwayNames)
11
+export(nodeWeights)
12
+export(pDis)
7 13
 export(pe)
8 14
 export(peEdgeRenderInfo)
9 15
 export(peNodeRenderInfo)
10 16
 export(setEdgeWeights)
11 17
 export(setNodeWeights)
18
+exportClasses(pDisPathway)
19
+exportClasses(pDisRes)
12 20
 exportClasses(pePathway)
13 21
 exportClasses(peRes)
22
+exportMethods(Summary)
14 23
 exportMethods(nodeWeights)
15 24
 exportMethods(plot)
16
-exportMethods(Summary)
17
-import(boot)
18
-import(graph)
19 25
 import(KEGGREST)
20 26
 import(KEGGgraph)
27
+import(boot)
28
+import(graph)
21 29
 import(parallel)
22
-importMethodsFrom(KEGGgraph)
... ...
@@ -1,3 +1,8 @@
1
+VERSION 2.0.0
2
+--------
3
+
4
+* added a novel pathway analysis method based on the primary dis-regulation of the genes in each pathway
5
+
1 6
 VERSION 1.2.0
2 7
 --------
3 8
 
... ...
@@ -5,13 +5,13 @@
5 5
 #' @details
6 6
 #' 
7 7
 #' The slots \code{input} and \code{ref} record global information related to the whole analysis, 
8
-#' while the \code{pathways} slot records the specific results as \code{\link{pePathway}} for each one of the pathways used in the analysis.
8
+#' while the \code{pathways} slot records the specific results as \code{\link{pePathway-class}} for each one of the pathways used in the analysis.
9 9
 #' 
10 10
 #' 
11 11
 #' @section Slots: 
12 12
 #' 
13 13
 #' \describe{
14
-#'     \item{\code{pathways}:}{A list of \code{\link{pePathway}} objects.}
14
+#'     \item{\code{pathways}:}{A list of \code{\link{pePathway-class}} objects.}
15 15
 #'     \item{\code{input}:}{named vector of fold changes used for the analysis. The names of the vector are the IDs originaly used.}
16 16
 #'     \item{\code{ref}:}{character vector containing the IDs used as reference in the analysis.}
17 17
 #'     \item{\code{cutOffFree}:}{boolean value indicating if a cut-of-free analysis has been performed.}
... ...
@@ -21,9 +21,8 @@
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-class}}
25 25
 #'
26
-#' @aliases peRes-class
27 26
 #' @exportClass peRes
28 27
 setClass("peRes",
29 28
          representation(pathways = "list",
... ...
@@ -45,6 +44,7 @@ setClass("peRes",
45 44
 #'    \item{\code{boot}:}{an object of class \code{boot} encoding the bootstrap information.}
46 45
 #'    \item{\code{Pert}:}{the gene perturbation factors for all genes on the pathway, as computed by Pathway-Express.}
47 46
 #'    \item{\code{Acc}:}{the gene accumulations for all genes on the pathway, as computed by Pathway-Express.}
47
+#'    \item{\code{asGS}:}{pathway was considered as gene set}
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-class}}
56 56
 #' 
57 57
 #' @aliases pePathway-class
58 58
 #' @import graph
... ...
@@ -69,3 +69,75 @@ setClass("pePathway",
69 69
          prototype(map = new("graphNEL")
70 70
          )
71 71
 )
72
+
73
+
74
+#' Primary dis-regulation (pDis) result class
75
+#' 
76
+#' This class is used to encode the results of the pathway analysis performed by the function \code{\link{pDis}}.
77
+#' 
78
+#' @details
79
+#' 
80
+#' The slots \code{input} and \code{ref} record global information related to the whole analysis, 
81
+#' while the \code{pathways} slot records the specific results as \code{\link{pDisPathway-class}} for each one of the pathways used in the analysis.
82
+#' 
83
+#' 
84
+#' @section Slots: 
85
+#' 
86
+#' \describe{
87
+#'     \item{\code{pathways}:}{A list of \code{\link{pDisPathway-class}} objects.}
88
+#'     \item{\code{input}:}{named vector of fold changes used for the analysis. The names of the vector are the IDs originaly used.}
89
+#'     \item{\code{ref}:}{character vector containing the IDs used as reference in the analysis.}
90
+#'     \item{\code{cutOffFree}:}{boolean value indicating if a cut-of-free analysis has been performed.}
91
+#'   }
92
+#' 
93
+#' @author
94
+#' 
95
+#' Calin Voichita, Sahar Ansari and Sorin Draghici
96
+#'
97
+#' @seealso \code{\link{pDis}}, \code{\link{pDisPathway-class}}
98
+#'
99
+#' @aliases pDisRes-class
100
+#' @exportClass pDisRes
101
+setClass("pDisRes",
102
+         representation(pathways = "list",
103
+                        input = "numeric",
104
+                        ref = "character",
105
+                        cutOffFree = "logical"),
106
+         prototype(pathways = list(), cutOffFree = FALSE)
107
+)
108
+
109
+#' Class that encodes the result of pDis analysis for a single pathway
110
+#' 
111
+#' 
112
+#' @section Slots:
113
+#' 
114
+#' \describe{
115
+#'    \item{\code{map}:}{an object of type graph (e.g., \code{\link{graphNEL}}).}
116
+#'    \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}
117
+#'    \item{\code{ref}:}{vector of reference IDs on this pathway}
118
+#'    \item{\code{boot}:}{an object of class \code{boot} encoding the bootstrap information.}
119
+#'    \item{\code{pDis}:}{the gene primary dis-regulation for all genes on the pathway, as computed by primary dis-regulation.}
120
+#'    \item{\code{asGS}:}{pathway was considered as gene set}
121
+#' }
122
+#' 
123
+#' @author
124
+#' 
125
+#' Calin Voichita, Sahar Ansari and Sorin Draghici
126
+#'
127
+#'             
128
+#' @seealso \code{\link{pDis}}, \code{\link{pDisRes-class}}
129
+#' 
130
+#' @aliases pDisPathway-class
131
+#' @import graph
132
+#' @exportClass pDisPathway
133
+setClass("pDisPathway", 
134
+         representation(map = "graph",
135
+                        input = "numeric",
136
+                        ref = "character",
137
+                        boot = "ANY",
138
+                        pDis = "numeric",
139
+                        asGS = "logical"
140
+         ), 
141
+         prototype(map = new("graphNEL")
142
+         )
143
+)
... ...
@@ -1,133 +1,30 @@
1
+
1 2
 #' Summarize the results of a Pathway-Express analysis
2 3
 #' 
3
-#' 
4
-#' @usage Summary(x, pathNames = NULL, totalAcc = TRUE, totalPert = TRUE, normalize = TRUE, 
5
-#'  pPert = TRUE, pAcc = TRUE, pORA = TRUE, 
6
-#'  comb.pv = c("pPert", "pORA"), comb.pv.func = compute.fisher,
7
-#'  order.by = "pComb", adjust.method = "fdr")
8
-#' 
9
-#' @param x Pathways-Express result object obtained using \code{\link{pe}}
10
-#' @param pathNames named vector of pathway names; the names of the vector are the IDs of the pathways
11
-#' @param totalAcc boolean value indicating if the total accumulation should be computed
12
-#' @param totalPert boolean value indicating if the total perturbation should be computed
13
-#' @param normalize boolean value indicating if normalization with regards to the boostrap simulations should be performed on totalAcc and totalPert
14
-#' @param pPert boolean value indicating if the significance of the total perturbation in regards to the bootstrap permutations should be computed
15
-#' @param pAcc boolean value indicating if the significance of the total accumulation in regards to the bootstrap permutations should be computed
16
-#' @param pORA boolean value indicating if the over-represtation p-value should be computed
17
-#' @param comb.pv vector of the p-value names to be combine (any of the above p-values)
18
-#' @param comb.pv.func the function to combine the p-values; takes as input a vector of p-values and returns the combined p-value
19
-#' @param order.by the name of the p-value that is used to order the results
20
-#' @param adjust.method the name of the method to adjust the p-value (see \link{p.adjust})
21
-#' 
22
-#' @seealso \code{\link{pe}}
23
-#' 
24
-#' @examples
25
-#' 
26
-#' # load experiment
27
-#' load(system.file("extdata/E-GEOD-21942.topTable.RData", package = "ROntoTools"))
28
-#' fc <- top$logFC[top$adj.P.Val <= .01]
29
-#' names(fc) <- top$entrez[top$adj.P.Val <= .01]
30
-#' ref <- top$entrez
31
-#' 
32
-#' # load the set of pathways
33
-#' kpg <- keggPathwayGraphs("hsa")
34
-#' kpg <- setEdgeWeights(kpg)
35
-#' kpg <- setNodeWeights(kpg, defaultWeight = 1)
36
-#' 
37
-#' # perform the pathway analysis
38
-#' peRes <- pe(fc, graphs = kpg, ref = ref, nboot = 100, verbose = TRUE)
39
-#' 
40
-#' # obtain summary of results
41
-#' head(Summary(peRes))
42
-#' 
43
-#' kpn <- keggPathwayNames("hsa")
44
-#' 
45
-#' head(Summary(peRes))
46
-#' 
47
-#' head(Summary(peRes, pathNames = kpn, totalAcc = FALSE, totalPert = FALSE, 
48
-#'              pAcc = FALSE, pORA = FALSE, comb.pv = NULL, order.by = "pPert"))
49
-#' 
50
-#' @rdname Summary-methods
51
-#' 
52
-#' @aliases Summary.peRes
4
+#' @param x Pathway-Express analysis result object obtained using \code{\link{pe}}
5
+#' @param ... see \code{\link{summary.peRes}}
6
+#' @param na.rm ignored
7
+#'
53 8
 #' @aliases Summary,peRes-method
9
+#'
54 10
 #' @export
55 11
 setMethod("Summary", c("x" = "peRes"),
56
-          function(x, pathNames = NULL, totalAcc = TRUE, totalPert = TRUE, normalize = TRUE, 
57
-                   pPert = TRUE, pAcc = TRUE, pORA = TRUE, 
58
-                   comb.pv = c("pPert", "pORA"), comb.pv.func = compute.fisher,
59
-                   order.by = "pComb", adjust.method = "fdr")
60
-          {  
61
-            ifelse <- function(test, trueCase, falseCase){
62
-              if(test) return(trueCase)
63
-              else return(falseCase)
64
-            }
65
-            
66
-            pathStats <- function(pePath)
67
-            {
68
-              pStats <- NULL
69
-              
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
-              
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
-              
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
-              
79
-              pStats$pORA <- ifelse(pORA & !x@cutOffFree, compute.pORA(pePath, length(x@input), length(x@ref)), NULL)
80
-              
81
-              pStats$pComb <- ifelse(!is.null(comb.pv) & !any(is.null(pStats[comb.pv])), 
82
-                                     ifelse(!any(is.na(pStats[comb.pv])), as.numeric(comb.pv.func(unlist(pStats[comb.pv]))), NA), NULL)
83
-              
84
-              return(unlist(pStats))
85
-            }
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
-            
98
-            if(!is.null(comb.pv))
99
-            {
100
-              if(!all(comb.pv %in% c("pPert","pAcc","pORA")))
101
-              {
102
-                warning("The p-value to be combined are not specified correctly. No combination p-value will be calculated!")
103
-                comb.pv <- NULL
104
-                if(order.by == "pComb")
105
-                  order.by <- NULL
106
-              }else{
107
-                for(i in 1:length(comb.pv))
108
-                  assign(comb.pv[i], TRUE)
109
-              }
110
-            }
111
-            
112
-            topStats <- data.frame(do.call(rbind, lapply(x@pathways, pathStats)))
113
-            
114
-            if(!is.null(pathNames))
115
-            {
116
-              pathNames <- pathNames[rownames(topStats)]
117
-              topStats <- cbind(pathNames, topStats)
118
-            }
119
-            
120
-            if(order.by %in% colnames(topStats))
121
-            {
122
-              topStats <- topStats[order(topStats[,order.by]),]
123
-            }
124
-            
125
-            allPVs <- c("pPert","pAcc","pORA", "pComb")
126
-            
127
-            lapply(allPVs[allPVs %in% colnames(topStats)],
128
-                   function(pv)
129
-                     topStats[[paste(pv, "." , adjust.method, sep = "")]] <<- p.adjust(topStats[[pv]], adjust.method)
130
-            )
131
-            return(topStats)
132
-          }
133
-)
134 12
\ No newline at end of file
13
+  function(x, ..., na.rm = FALSE) {
14
+    return(summary.peRes(x, ...));
15
+  }
16
+)
17
+
18
+#' Summarize the results of a Pathway-Express analysis
19
+#' 
20
+#' @param x Primary dis-regulation analysis result object obtained using \code{\link{pDis}}
21
+#' @param ... see \code{\link{summary.pDisRes}}
22
+#' @param na.rm ignored
23
+#'
24
+#' @aliases Summary,pDisRes-method
25
+#'
26
+#' @export
27
+setMethod("Summary", c("x" = "pDisRes"),
28
+  function(x, ..., na.rm = FALSE) {
29
+    return(summary.pDisRes(x, ...));
30
+  }
31
+)
... ...
@@ -82,7 +82,6 @@ loadKEGGpathwayDataREST <- function(organism = "hsa",
82 82
 #' head(nodes(kpg[["path:hsa04110"]]))
83 83
 #' head(edges(kpg[["path:hsa04110"]]))
84 84
 #' 
85
-#' @importMethodsFrom KEGGgraph
86 85
 #' @export
87 86
 keggPathwayGraphs <- function(organism = "hsa", 
88 87
                               targRelTypes = c("GErel","PCrel","PPrel"),
89 88
new file mode 100644
... ...
@@ -0,0 +1,254 @@
1
+#' Primary dis-regulation: Pathway analysis approach based on the unexplained dis-regulation of genes 
2
+#' 
3
+#' 
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 attribute \code{weight} for both nodes and edges)
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
+#' @param nboot number of bootstrap iterations
8
+#' @param verbose print progress output
9
+#' @param cluster a cluster object created by makeCluster for parallel computations
10
+#' @param seed an integer value passed to set.seed() during the boostrap permutations
11
+#' 
12
+#' @details
13
+#' 
14
+#' See details in the cited articles.
15
+#' 
16
+#' @return
17
+#' 
18
+#' An object of class \code{\link{pDisRes-class}}.
19
+#' 
20
+#' @author
21
+#' 
22
+#' Calin Voichita, Sahar Ansari and Sorin Draghici
23
+#' 
24
+#' @references
25
+#' 
26
+#' Voichita C., Donato M., Draghici S.: "Incorporating gene significance in the impact analysis of signaling pathways", IEEE Machine Learning and Applications (ICMLA), 2012 11th International Conference on, Vol. 1, p.126-131, 2012
27
+#' Ansari, S., Voichita, C., Donato, M., Tagett, R., & Draghici, S. A Novel Pathway Analysis Approach Based on the Unexplained Disregulation of Genes.
28
+#' 
29
+#' 
30
+#' @seealso \code{\link{Summary}}, 
31
+#' \code{\link{keggPathwayGraphs}}, \code{\link{setNodeWeights}}, \code{\link{setEdgeWeights}}
32
+#' 
33
+#' @examples
34
+#' 
35
+#' # load a multiple sclerosis study (public data available in Array Express 
36
+#' # ID: E-GEOD-21942)
37
+#' # This file contains the top table, produced by the limma package with 
38
+#' # added gene information. All the probe sets with no gene associate to them,
39
+#' # have been removed. Only the most significant probe set for each gene has been
40
+#' # kept (the table is already ordered by p-value)
41
+#' # The table contains the expression fold change and signficance of each  
42
+#' # probe set in peripheral blood mononuclear cells (PBMC) from 12 MS patients
43
+#' # and 15 controls.
44
+#' load(system.file("extdata/E-GEOD-21942.topTable.RData", package = "ROntoTools"))
45
+#' head(top)
46
+#' 
47
+#' # select differentially expressed genes at 1% and save their fold change in a 
48
+#' # vector fc and their p-values in a vector pv
49
+#' fc <- top$logFC[top$adj.P.Val <= .01]
50
+#' names(fc) <- top$entrez[top$adj.P.Val <= .01]
51
+#' 
52
+#' pv <- top$P.Value[top$adj.P.Val <= .01]
53
+#' names(pv) <- top$entrez[top$adj.P.Val <= .01]
54
+#' 
55
+#' # alternativly use all the genes for the analysis
56
+#' # NOT RUN: 
57
+#' # fc <- top$logFC
58
+#' # names(fc) <- top$entrez
59
+#' 
60
+#' # pv <- top$P.Value
61
+#' # names(pv) <- top$entrez
62
+#' 
63
+#' # get the reference
64
+#' ref <- top$entrez
65
+#' 
66
+#' # load the set of pathways
67
+#' kpg <- keggPathwayGraphs("hsa")
68
+#' 
69
+#' # set the beta information (see the citated documents for meaning of beta)
70
+#' kpg <- setEdgeWeights(kpg)
71
+#' 
72
+#' # inlcude the significance information in the analysis (see Voichita:2012 
73
+#' # for more information)
74
+#' # set the alpha information based on the pv with one of the predefined methods
75
+#' kpg <- setNodeWeights(kpg, weights = alphaMLG(pv), defaultWeight = 1)
76
+#' 
77
+#' # perform the pathway analysis
78
+#' # in order to obtain accurate results the number of boostraps, nboot, should 
79
+#' # be increase to a number like 2000
80
+#' pDisRes <- pDis(fc, graphs = kpg, ref = ref, nboot = 100, verbose = TRUE)
81
+#' 
82
+#' # obtain summary of results
83
+#' head(Summary(pDisRes))
84
+#' 
85
+#' @export
86
+pDis <- function(x, graphs, ref = NULL, nboot = 2000, verbose = TRUE, cluster = NULL, seed = NULL)
87
+{
88
+  cutOffFree <- FALSE
89
+  if (is.null(ref))
90
+  {
91
+    ref <- names(x)
92
+    cutOffFree <- TRUE
93
+  }
94
+  else
95
+  {
96
+    if (!any(is.na(match(ref,names(x)))))
97
+    {
98
+      warning("All the reference IDs are part of the input. Cut-off free analysis is performed.") 
99
+      ref <- names(x)
100
+      cutOffFree <- TRUE
101
+    }
102
+  }
103
+  
104
+  preservedSeed <- NULL
105
+  if (exists(".Random.seed"))
106
+    preservedSeed <- .Random.seed
107
+  
108
+  if(!is.null(seed))
109
+    set.seed(seed)
110
+  
111
+  if (any(is.na(match(names(x), ref))))
112
+  {
113
+    warning("There are input IDs not available in the reference. These will be excluded from analysis.")
114
+    x <- x[!is.na(match(names(x), ref))]
115
+  }
116
+  
117
+  pDisRes <- pDis.helper(x = x, ref = ref, graphs = graphs, nboot = nboot, verbose = verbose, cluster = cluster, seed = seed)
118
+  pDisRes@cutOffFree <- cutOffFree
119
+  
120
+  if(is.null(preservedSeed))
121
+  {
122
+    if(!is.null(seed))
123
+      rm(.Random.seed)
124
+  }
125
+  else
126
+    .Random.seed <- preservedSeed
127
+  
128
+  return(pDisRes)
129
+}
130
+
131
+#' @import parallel
132
+pDis.helper <- function(x, graphs, ref = NULL, nboot = 2000, verbose = TRUE, cluster = NULL, seed = NULL)
133
+{
134
+  if(verbose)
135
+  {
136
+    message("Performing pathway analysis...")
137
+    if(is.null(cluster))
138
+    {
139
+      pb <- txtProgressBar(min = 0, max = length(graphs), style = 3)  
140
+    }
141
+  }
142
+  
143
+  t1 <- Sys.time()
144
+  if (is.null(cluster))
145
+  {
146
+    allBoot <- lapply(graphs, function(g, seed) {
147
+      if(!is.null(seed))
148
+        set.seed(seed)
149
+      ret <- pDis.boot(g, x = x, ref = ref, nboot = nboot)
150
+      if(verbose)
151
+        setTxtProgressBar(pb, getTxtProgressBar(pb) + 1)
152
+      return(ret)
153
+    }, seed = seed)
154
+  }
155
+  else
156
+  {
157
+    clusterExport(cluster, c("pDis.boot", "compute.inverse", "compute.B_pDis"))
158
+    clusterEvalQ(cluster, library(ROntoTools))
159
+    
160
+    allBoot <- parLapply(cluster, graphs, function(g, seed) {
161
+      if(!is.null(seed))
162
+        set.seed(seed)
163
+      ret <- pDis.boot(g, x = x, ref = ref, nboot = nboot)
164
+      return(ret)
165
+    }, seed = seed)
166
+    
167
+  }
168
+  t2 <- Sys.time()
169
+  
170
+  if(verbose)
171
+  {
172
+    message("Analysis completed in ", format(t2-t1), ".")
173
+  }
174
+  
175
+  allBoot <- allBoot[!sapply(allBoot, is.null)]
176
+  
177
+  pDisRes <- new("pDisRes", pathways = allBoot, input = x, ref = ref)
178
+  
179
+  return(pDisRes)
180
+}
181
+
182
+#' @import boot
183
+#' @keywords internal
184
+pDis.boot <- function(g, x, ref, nboot, all.genes = F)
185
+{
186
+  inv <- (compute.B_pDis(g))
187
+  
188
+  pDisPath <- new("pDisPathway", 
189
+                map = g, 
190
+                input = x[names(x) %in% nodes(g)],
191
+                ref = ref[ref %in% nodes(g)])
192
+  
193
+  if (length(pDisPath@input) == 0)
194
+    return(NULL)
195
+  
196
+  if (is.null(inv))
197
+  {
198
+    pDisPath@asGS <- TRUE
199
+    return(pDisPath)
200
+  }
201
+  
202
+  # same number of DE genes at any position in the pathway 
203
+  # (given by the gene from the pathway in the reference)
204
+  ran.gen.de <- function(x, l)  {
205
+    y <- sample(l$fc, length(x))
206
+    names(y) <- sample(l$ref, length(x))
207
+    return(y)
208
+  }
209
+  
210
+  pDisPath@boot <- boot(pDisPath@input, 
211
+                      function(x, inv) {
212
+                        xx <- rep(0, nrow(inv));  names(xx) <- rownames(inv);
213
+                        xx[names(x)] <- x
214
+                        xx <- xx * nodeWeights(pDisPath@map, names(xx))
215
+                        tt = inv %*% xx;
216
+                        ret <- c(sum(abs(tt)))
217
+                        names(ret) <- c("tpDis")
218
+                        return(ret)
219
+                      }, 
220
+                      nboot,
221
+                      "parametric", ran.gen = ran.gen.de, mle = list(ref = pDisPath@ref, fc = as.numeric(x)),
222
+                      inv = inv
223
+  )
224
+  colnames(pDisPath@boot$t) <- names(pDisPath@boot$t0)
225
+  
226
+  xx <- rep(0, nrow(inv))
227
+  names(xx) <- rownames(inv)
228
+  xx[names(pDisPath@input)] <- pDisPath@input  
229
+  pDisPath@pDis = (inv %*% xx)[,1];
230
+  pDisPath@asGS <- FALSE
231
+  
232
+  return(pDisPath) 
233
+}
234
+
235
+
236
+compute.B_pDis <- function(g, non.zero = TRUE)
237
+{
238
+  if (non.zero)
239
+    # number of downstream genes (like in SPIA)
240
+    nds <- sapply(edgeWeights(g), function(x) sum(x != 0 ))
241
+  else
242
+    nds <- sapply(edges(g), length)
243
+  
244
+  # add 1 for all genes that do not have downstream genes to avoid division by 0
245
+  # this does not affect the computation
246
+  nds[nds == 0] <- 1
247
+  
248
+  # compute B = (I - beta/nds)
249
+  #B <- t(diag(length(nodes(g))) - as(g, "matrix") / nds)
250
+  #
251
+  B <- diag(length(nodes(g))) - t(as(g, "matrix")) / matrix(nds, byrow=TRUE, nrow = length(nds), ncol = length(nds))
252
+   return(B)
253
+}
254
+ 
0 255
new file mode 100644
... ...
@@ -0,0 +1,23 @@
1
+
2
+compute.ppDis <- function(pDisPath)
3
+  ifelse( !all(pDisPath@boot$t[,"tpDis"] == 0),
4
+          compute.bootPV(pDisPath@boot$t0["tpDis"], pDisPath@boot$t[,"tpDis"]),
5
+          NA)
6
+
7
+
8
+compute.pORA <- function(pDisPath, inputSize, refSize)
9
+  phyper(q = length(pDisPath@input)-1,
10
+         m = length(pDisPath@ref),
11
+         n = refSize-length(pDisPath@ref),
12
+         k = inputSize,
13
+         lower.tail = FALSE) 
14
+
15
+
16
+get.totalpDis <- function(pDisPath)
17
+  as.numeric(pDisPath@boot$t0["tpDis"])
18
+
19
+get.totalpDisNorm <- function(pDisPath)
20
+  ifelse( !all(pDisPath@boot$t[,"tpDis"] == 0),
21
+          as.numeric((pDisPath@boot$t0["tpDis"] - mean(pDisPath@boot$t[,"tpDis"])) / sd(pDisPath@boot$t[,"tpDis"])),
22
+          NA)
23
+
... ...
@@ -15,7 +15,7 @@
15 15
 #' 
16 16
 #' @return
17 17
 #' 
18
-#' An object of class \code{\link{peRes}}.
18
+#' An object of class \code{\link{peRes-class}}.
19 19
 #' 
20 20
 #' @author
21 21
 #' 
... ...
@@ -31,7 +31,7 @@
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{plot.peRes}}, 
34
+#' @seealso \code{\link{Summary}}, \code{\link{plot,peRes,missing-method}}, 
35 35
 #' \code{\link{keggPathwayGraphs}}, \code{\link{setNodeWeights}}, \code{\link{setEdgeWeights}}
36 36
 #' 
37 37
 #' @examples
... ...
@@ -1,19 +1,3 @@
1
-# setMethod("plot", signature(x="pePathway", y="ANY"),
2
-#           function(x, y, ...){
3
-#             
4
-#             nShape <- rep("circle", length(nodes(x@map)))
5
-#             names(nShape) <- nodes(x@map)
6
-#             nShape[names(x@input)] <- "box"
7
-#             
8
-#             m <- as(x@map, "matrix")
9
-#             nodeToPlot <- nodes(x@map)[(colSums(abs(m)) != 0) & (rowSums(abs(m)) != 0)]
10
-#             
11
-#             plot(x@map,  nodeAttrs = list(
12
-#               fillcolor = pf2col(x@PF), 
13
-#               fontsize = addNames(340.0, nodes(x@map)),
14
-#               shape = nShape
15
-#               ))
16
-#           })
17 1
 
18 2
 compute.pAcc <- function(pePath)
19 3
   ifelse( !all(pePath@boot$t[,"tAcc"] == 0),
... ...
@@ -6,15 +6,16 @@
6 6
 #' statistics of the same factors.
7 7
 #' 
8 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}})
9
+#' @param x an object of type \code{\link{pePathway-class}}
10
+#' @param y if provided, the factor to be ploted (either \code{Acc} (default) or \code{Pert}; see \code{\link{pePathway-class}})
11
+#' @param main title
11 12
 #' @param ... Arguments to be passed to methods, such as \code{\link{par}}
12 13
 #' @param type type of plot (either \code{two.way} (default) or \code{boot})
13 14
 #' @param eps any value smaller than this will be ploted as 0
14 15
 #' 
15 16
 #' @author Calin Voichita and Sorin Draghici
16 17
 #' 
17
-#' @seealso \code{\link{pe}}, \code{\link{plot.peRes}}, \code{\link{peNodeRenderInfo}}, \code{\link{peEdgeRenderInfo}}
18
+#' @seealso \code{\link{pe}}, \code{\link{plot,peRes,missing-method}}, \code{\link{peNodeRenderInfo}}, \code{\link{peEdgeRenderInfo}}
18 19
 #' 
19 20
 #' @examples
20 21
 #' 
... ...
@@ -41,10 +42,7 @@
41 42
 #' plot(peRes@@pathways[[50]], "Pert", type = "boot", main = "Perturbation factor")
42 43
 #' 
43 44
 #' @rdname plot.pePathway-methods
44
-#' @name plot.pePathway
45 45
 #' 
46
-#' @aliases plot.pePathway
47
-#' @aliases plot,pePathway,missing-method
48 46
 #' @export
49 47
 setMethod("plot", signature(x="pePathway", y="missing"),
50 48
           function(x, y, ..., type = "two.way", eps = 1e-6)
... ...
@@ -55,8 +53,6 @@ setMethod("plot", signature(x="pePathway", y="missing"),
55 53
 
56 54
 #' @rdname plot.pePathway-methods
57 55
 #' 
58
-#' @aliases plot.pePathway
59
-#' @aliases plot,pePathway,character-method
60 56
 #' @export
61 57
 setMethod("plot", signature(x="pePathway", y="character"),
62 58
           function(x, y, main = "", ... , type = "two.way", eps = 1e-6)
... ...
@@ -110,7 +106,7 @@ setMethod("plot", signature(x="pePathway", y="character"),
110 106
 #' 
111 107
 #' @description Display a two-way plot using two of the p-values from the Pathway-Express analysis.
112 108
 #' 
113
-#' @param x an object of type \code{\link{peRes}}
109
+#' @param x an object of type \code{\link{peRes-class}}
114 110
 #' @param y vector of two p-values names to be combined using \code{comb.pv.func} (default: \code{c("pAcc", "pORA")}).
115 111
 #' @param ... Arguments to be passed to methods, such as \code{\link{par}}.
116 112
 #' @param comb.pv.func the function to combine the p-values - takes as input a vector of p-values 
... ...
@@ -121,7 +117,7 @@ setMethod("plot", signature(x="pePathway", y="character"),
121 117
 #' 
122 118
 #' @author Calin Voichita and Sorin Draghici
123 119
 #' 
124
-#' @seealso \code{\link{pe}}, \code{\link{Summary.peRes}}, \code{\link{plot.pePathway}}
120
+#' @seealso \code{\link{pe}}, \code{\link{summary.peRes}}, \code{\link{plot,pePathway,missing-method}}
125 121
 #' 
126 122
 #' @examples
127 123
 #' 
... ...
@@ -144,10 +140,7 @@ setMethod("plot", signature(x="pePathway", y="character"),
144 140
 #' plot(peRes, c("pPert","pORA"), comb.pv.func = compute.normalInv, threshold = .01)
145 141
 #' 
146 142
 #' @rdname plot.peRes-methods
147
-#' @name plot.peRes
148 143
 #' 
149
-#' @aliases plot.peRes
150
-#' @aliases plot,peRes,missing-method
151 144
 #' @export
152 145
 setMethod("plot", signature(x="peRes", y="missing"),
153 146
           function(x, y, ... , comb.pv.func = compute.fisher, adjust.method = "fdr", threshold = .05, eps = 1e-6)
... ...
@@ -158,9 +151,7 @@ setMethod("plot", signature(x="peRes", y="missing"),
158 151
 )
159 152
 
160 153
 #' @rdname plot.peRes-methods
161
-#' 
162
-#' @aliases plot.peRes
163
-#' @aliases plot,peRes,character-method
154
+#'
164 155
 #' @export
165 156
 setMethod("plot", signature(x="peRes", y="character"),
166 157
           function(x, y, ... , comb.pv.func = compute.fisher, adjust.method = "fdr", threshold = .05, eps = 1e-6)
... ...
@@ -1,6 +1,6 @@
1
-#' Extract edge render information from a \code{pePathway} object
1
+#' Extract edge render information from a \code{pePathway-class} object
2 2
 #' 
3
-#' @param x an object of class \code{\link{pePathway}}
3
+#' @param x an object of class \code{\link{pePathway-class}}
4 4
 #' @param pos.col color of the edges with possitive weight
5 5
 #' @param pos.lty line type of the edges with possitive weight
6 6
 #' @param pos.ah arrow head of the edges with possitive weight 
... ...
@@ -11,7 +11,7 @@
11 11
 #' @param zero.lty color of the edges with zero weight
12 12
 #' @param zero.ah color of the edges with zero weight
13 13
 #' 
14
-#' @value a named list as expected by \code{\link{edgeRenderInfo}}
14
+#' @return a named list as expected by \code{\link{edgeRenderInfo}}
15 15
 #' 
16 16
 #' @author Calin Voichita and Sorin Draghici
17 17
 #' 
... ...
@@ -76,17 +76,17 @@ peEdgeRenderInfo <- function(x,
76 76
   ))
77 77
 }
78 78
 
79
-#' Extract node render information from a \code{pePathway} object
79
+#' Extract node render information from a \code{pePathway-class} object
80 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}})
81
+#' @param x an object of class \code{\link{pePathway-class}}
82
+#' @param y a string representing the factor to be represented (\code{Pert, Acc} or \code{input}; see \code{\link{pePathway-class}})
83 83
 #' @param input.shape shape of nodes that have measured expression change
84 84
 #' @param default.shape shape of all other nodes
85 85
 #' @param pos.col color of nodes with a positive \code{y} factor
86 86
 #' @param neg.col color of nodes with a negative \code{y} factor
87 87
 #' @param zero.col color of nodes with the \code{y} factor equal to zero
88 88
 #' 
89
-#' @value a named list as expected by \code{\link{nodeRenderInfo}}
89
+#' @return a named list as expected by \code{\link{nodeRenderInfo}}
90 90
 #' 
91 91
 #' @author Calin Voichita and Sorin Draghici
92 92
 #' 
93 93
new file mode 100644
... ...
@@ -0,0 +1,123 @@
1
+#' Summarize the results of a primary dis-regulation (pDis) analysis
2
+#' 
3
+#' @usage summary.pDisRes(object, ..., pathNames = NULL, totalpDis = TRUE, normalize = TRUE, 
4
+#'  ppDis = TRUE, pORA = TRUE, 
5
+#'  comb.pv = c("ppDis", "pORA"), comb.pv.func = compute.fisher,
6
+#'  order.by = "pComb", adjust.method = "fdr")
7
+#' 
8
+#' @param object pDis analysis result object obtained using \code{\link{pDis}}
9
+#' @param ... ignored
10
+#' @param pathNames named vector of pathway names; the names of the vector are the IDs of the pathways
11
+#' @param totalpDis boolean value indicating if the total primary dis-regulation should be computed
12
+#' @param normalize boolean value indicating if normalization with regards to the boostrap simulations should be performed on totalpDis
13
+#' @param ppDis boolean value indicating if the significance of the total primary dis-regulation in regards to the bootstrap permutations should be computed
14
+#' @param pORA boolean value indicating if the over-represtation p-value should be computed
15
+#' @param comb.pv vector of the p-value names to be combine (any of the above p-values)
16
+#' @param comb.pv.func the function to combine the p-values; takes as input a vector of p-values and returns the combined p-value
17
+#' @param order.by the name of the p-value that is used to order the results
18
+#' @param adjust.method the name of the method to adjust the p-value (see \link{p.adjust})
19
+#' 
20
+#' @seealso \code{\link{pDis}}
21
+#' 
22
+#' @examples
23
+#' 
24
+#' # load experiment
25
+#' load(system.file("extdata/E-GEOD-21942.topTable.RData", package = "ROntoTools"))
26
+#' fc <- top$logFC[top$adj.P.Val <= .01]
27
+#' names(fc) <- top$entrez[top$adj.P.Val <= .01]
28
+#' ref <- top$entrez
29
+#' 
30
+#' # load the set of pathways
31
+#' kpg <- keggPathwayGraphs("hsa")
32
+#' kpg <- setEdgeWeights(kpg)
33
+#' kpg <- setNodeWeights(kpg, defaultWeight = 1)
34
+#' 
35
+#' # perform the pathway analysis
36
+#' pDisRes <- pDis(fc, graphs = kpg, ref = ref, nboot = 100, verbose = TRUE)
37
+#' 
38
+#' # obtain summary of results
39
+#' head(summary(pDisRes))
40
+#' 
41
+#' kpn <- keggPathwayNames("hsa")
42
+#' 
43
+#' head(summary(pDisRes))
44
+#' 
45
+#' head(summary(pDisRes, pathNames = kpn, totalpDis = FALSE, 
46
+#'             pORA = FALSE, comb.pv = NULL, order.by = "pDis"))
47
+#' 
48
+#' @export
49
+summary.pDisRes <- function(object, ..., pathNames = NULL, totalpDis = TRUE, normalize = TRUE, 
50
+                   ppDis = TRUE, pORA = TRUE, 
51
+                   comb.pv = c("ppDis", "pORA"), comb.pv.func = compute.fisher,
52
+                   order.by = "pComb", adjust.method = "fdr")
53
+{  
54
+  ifelse <- function(test, trueCase, falseCase){
55
+    if(test) return(trueCase)
56
+    else return(falseCase)
57
+  }
58
+  
59
+  pathStats <- function(pDisPath)
60
+  {
61
+    pStats <- NULL
62
+    
63
+    
64
+    pStats$totalpDis <- ifelse(totalpDis, ifelse(!pDisPath@asGS, get.totalpDis(pDisPath), NA), NULL)
65
+    
66
+    pStats$totalpDisNorm <- ifelse(totalpDis & normalize, ifelse(!pDisPath@asGS, get.totalpDisNorm(pDisPath), NA), NULL)
67
+    
68
+    pStats$ppDis <- ifelse(ppDis, ifelse(!pDisPath@asGS, compute.ppDis(pDisPath), NA), NULL)
69
+    
70
+    pStats$pORA <- ifelse(pORA & !object@cutOffFree, compute.pORA(pDisPath, length(object@input), length(object@ref)), NULL)
71
+    
72
+    pStats$pComb <- ifelse(!is.null(comb.pv) & !any(is.null(pStats[comb.pv])), 
73
+                           ifelse(!any(is.na(pStats[comb.pv])), as.numeric(comb.pv.func(unlist(pStats[comb.pv]))), NA), NULL)
74
+    
75
+    return(unlist(pStats))
76
+  }
77
+  
78
+  if (pORA & object@cutOffFree)
79
+  {
80
+    pORA <- FALSE
81
+    if ("pORA" %in% comb.pv)
82
+    {
83
+      order.by <- setdiff(comb.pv, "pORA")[1]
84
+      comb.pv <- NULL
85
+    }
86
+    message("The over-representaion p-value is not defined for cut-off free analysis and will not be computed!")  
87
+  }
88
+  
89
+  if(!is.null(comb.pv))
90
+  {
91
+    if(!all(comb.pv %in% c("ppDis","pORA")))
92
+    {
93
+      warning("The p-value to be combined are not specified correctly. No combination p-value will be calculated!")
94
+      comb.pv <- NULL
95
+      if(order.by == "pComb")
96
+        order.by <- NULL
97
+    }else{
98
+      for(i in 1:length(comb.pv))
99
+        assign(comb.pv[i], TRUE)
100
+    }
101
+  }
102
+  
103
+  topStats <- data.frame(do.call(rbind, lapply(object@pathways, pathStats)))
104
+  
105
+  if(!is.null(pathNames))
106
+  {
107
+    pathNames <- pathNames[rownames(topStats)]
108
+    topStats <- cbind(pathNames, topStats)
109
+  }
110
+  
111
+  if(order.by %in% colnames(topStats))
112
+  {
113
+    topStats <- topStats[order(topStats[,order.by]),]
114
+  }
115
+  
116
+  allPVs <- c("ppDis","pORA", "pComb")
117
+  
118
+  lapply(allPVs[allPVs %in% colnames(topStats)],
119
+         function(pv)
120
+           topStats[[paste(pv, "." , adjust.method, sep = "")]] <<- p.adjust(topStats[[pv]], adjust.method)
121
+  )
122
+  return(topStats)
123
+}
0 124
\ No newline at end of file
1 125
new file mode 100644
... ...
@@ -0,0 +1,128 @@
1
+#' Summarize the results of a Pathway-Express analysis
2
+#' 
3
+#' 
4
+#' @usage summary.peRes(object, ..., pathNames = NULL, totalAcc = TRUE, totalPert = TRUE, normalize = TRUE, 
5
+#'  pPert = TRUE, pAcc = TRUE, pORA = TRUE, 
6
+#'  comb.pv = c("pPert", "pORA"), comb.pv.func = compute.fisher,
7
+#'  order.by = "pComb", adjust.method = "fdr")
8
+#' 
9
+#' @param object Pathways-Express result object obtained using \code{\link{pe}}
10
+#' @param ... ignored
11
+#' @param pathNames named vector of pathway names; the names of the vector are the IDs of the pathways
12
+#' @param totalAcc boolean value indicating if the total accumulation should be computed
13
+#' @param totalPert boolean value indicating if the total perturbation should be computed
14
+#' @param normalize boolean value indicating if normalization with regards to the boostrap simulations should be performed on totalAcc and totalPert
15
+#' @param pPert boolean value indicating if the significance of the total perturbation in regards to the bootstrap permutations should be computed
16
+#' @param pAcc boolean value indicating if the significance of the total accumulation in regards to the bootstrap permutations should be computed
17
+#' @param pORA boolean value indicating if the over-represtation p-value should be computed
18
+#' @param comb.pv vector of the p-value names to be combine (any of the above p-values)
19
+#' @param comb.pv.func the function to combine the p-values; takes as input a vector of p-values and returns the combined p-value
20
+#' @param order.by the name of the p-value that is used to order the results
21
+#' @param adjust.method the name of the method to adjust the p-value (see \link{p.adjust})
22
+#' 
23
+#' @seealso \code{\link{pe}}
24
+#' 
25
+#' @examples
26
+#' 
27
+#' # load experiment
28
+#' load(system.file("extdata/E-GEOD-21942.topTable.RData", package = "ROntoTools"))
29
+#' fc <- top$logFC[top$adj.P.Val <= .01]
30
+#' names(fc) <- top$entrez[top$adj.P.Val <= .01]
31
+#' ref <- top$entrez
32
+#' 
33
+#' # load the set of pathways
34
+#' kpg <- keggPathwayGraphs("hsa")
35
+#' kpg <- setEdgeWeights(kpg)
36
+#' kpg <- setNodeWeights(kpg, defaultWeight = 1)
37
+#' 
38
+#' # perform the pathway analysis
39
+#' peRes <- pe(fc, graphs = kpg, ref = ref, nboot = 100, verbose = TRUE)
40
+#' 
41
+#' # obtain summary of results
42
+#' head(summary(peRes))
43
+#' 
44
+#' kpn <- keggPathwayNames("hsa")
45
+#' 
46
+#' head(summary(peRes))
47
+#' 
48
+#' head(summary(peRes, pathNames = kpn, totalAcc = FALSE, totalPert = FALSE, 
49
+#'              pAcc = FALSE, pORA = FALSE, comb.pv = NULL, order.by = "pPert"))
50
+#'
51
+#' @export
52
+summary.peRes <- function(object, ..., pathNames = NULL, totalAcc = TRUE, totalPert = TRUE, normalize = TRUE, 
53
+                   pPert = TRUE, pAcc = TRUE, pORA = TRUE, 
54
+                   comb.pv = c("pPert", "pORA"), comb.pv.func = compute.fisher,
55
+                   order.by = "pComb", adjust.method = "fdr")
56
+{  
57
+  ifelse <- function(test, trueCase, falseCase){
58
+    if(test) return(trueCase)
59
+    else return(falseCase)
60
+  }
61
+  
62
+  pathStats <- function(pePath)
63
+  {
64
+    pStats <- NULL
65
+    
66
+    pStats$totalAcc <- ifelse(totalAcc, ifelse(!pePath@asGS, get.totalAcc(pePath), NA), NULL)
67
+    pStats$totalPert <- ifelse(totalPert, ifelse(!pePath@asGS, get.totalPert(pePath), NA), NULL)
68
+    
69
+    pStats$totalAccNorm <- ifelse(totalAcc & normalize, ifelse(!pePath@asGS, get.totalAccNorm(pePath), NA), NULL)
70
+    pStats$totalPertNorm <- ifelse(totalPert & normalize, ifelse(!pePath@asGS, get.totalPertNorm(pePath), NA), NULL)
71
+    
72
+    pStats$pPert <- ifelse(pPert, ifelse(!pePath@asGS, compute.pPert(pePath), NA), NULL)
73
+    pStats$pAcc <- ifelse(pAcc, ifelse(!pePath@asGS, compute.pAcc(pePath), NA), NULL)
74
+    
75
+    pStats$pORA <- ifelse(pORA & !object@cutOffFree, compute.pORA(pePath, length(object@input), length(object@ref)), NULL)
76
+    
77
+    pStats$pComb <- ifelse(!is.null(comb.pv) & !any(is.null(pStats[comb.pv])), 
78
+                           ifelse(!any(is.na(pStats[comb.pv])), as.numeric(comb.pv.func(unlist(pStats[comb.pv]))), NA), NULL)
79
+    
80
+    return(unlist(pStats))
81
+  }
82
+  
83
+  if (pORA & object@cutOffFree)
84
+  {
85
+    pORA <- FALSE
86
+    if ("pORA" %in% comb.pv)
87
+    {
88
+      order.by <- setdiff(comb.pv, "pORA")[1]
89
+      comb.pv <- NULL
90
+    }
91
+    message("The over-representaion p-value is not defined for cut-off free analysis and will not be computed!")  
92
+  }
93
+  
94
+  if(!is.null(comb.pv))
95
+  {
96
+    if(!all(comb.pv %in% c("pPert","pAcc","pORA")))
97
+    {
98
+      warning("The p-value to be combined are not specified correctly. No combination p-value will be calculated!")
99
+      comb.pv <- NULL
100
+      if(order.by == "pComb")
101
+        order.by <- NULL
102
+    }else{
103
+      for(i in 1:length(comb.pv))
104
+        assign(comb.pv[i], TRUE)
105
+    }
106
+  }
107
+  
108
+  topStats <- data.frame(do.call(rbind, lapply(object@pathways, pathStats)))
109
+  
110
+  if(!is.null(pathNames))
111
+  {
112
+    pathNames <- pathNames[rownames(topStats)]
113
+    topStats <- cbind(pathNames, topStats)
114
+  }
115
+  
116
+  if(order.by %in% colnames(topStats))
117
+  {
118
+    topStats <- topStats[order(topStats[,order.by]),]
119
+  }
120
+  
121
+  allPVs <- c("pPert","pAcc","pORA", "pComb")
122
+  
123
+  lapply(allPVs[allPVs %in% colnames(topStats)],
124
+         function(pv)
125
+           topStats[[paste(pv, "." , adjust.method, sep = "")]] <<- p.adjust(topStats[[pv]], adjust.method)
126
+  )
127
+  return(topStats)
128
+}
0 129
\ No newline at end of file
... ...
@@ -19,7 +19,7 @@ compute.bootPV <- function(real, dist)
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)
21 21
 #' 
22
-#' @value the combined p-value
22
+#' @return the combined p-value
23 23
 #' 
24 24
 #' @author Calin Voichita and Sorin Draghici
25 25
 #' 
... ...
@@ -49,7 +49,7 @@ compute.fisher <- function(p, eps = 1e-6)
49 49
 #' @param p a vector of independent p-values
50 50
 #' @param eps the minimal p-value considered (all p-values smaller will be set to this value)
51 51
 #' 
52
-#' @value the combined p-value
52
+#' @return the combined p-value
53 53
 #' 
54 54
 #' @author Calin Voichita and Sorin Draghici
55 55
 #' 
56 56
new file mode 100644
... ...
@@ -0,0 +1,13 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/keggDataREST.R
3
+\name{KEGGpathway2Graph}
4
+\alias{KEGGpathway2Graph}
5
+\title{Modified version of the same function from KEGGgraph}
6
+\usage{
7
+KEGGpathway2Graph(pathway, genesOnly = TRUE, expandGenes = TRUE)
8
+}
9
+\description{
10
+Modified version of the same function from KEGGgraph
11
+}
12
+\keyword{internal}
13
+
0 14
deleted file mode 100644
... ...
@@ -1,78 +0,0 @@
1
-\name{Summary}
2
-\alias{Summary}
3
-\alias{Summary,peRes-method}
4
-\alias{Summary.peRes}
5
-\title{Summarize the results of a Pathway-Express analysis}
6
-\arguments{
7
-  \item{x}{Pathways-Express result object obtained using
8
-  \code{\link{pe}}}
9
-
10
-  \item{pathNames}{named vector of pathway names; the names
11
-  of the vector are the IDs of the pathways}
12
-
13
-  \item{totalAcc}{boolean value indicating if the total
14
-  accumulation should be computed}
15
-
16
-  \item{totalPert}{boolean value indicating if the total
17
-  perturbation should be computed}
18
-
19
-  \item{normalize}{boolean value indicating if
20
-  normalization with regards to the boostrap simulations
21
-  should be performed on totalAcc and totalPert}
22
-
23
-  \item{pPert}{boolean value indicating if the significance
24
-  of the total perturbation in regards to the bootstrap
25
-  permutations should be computed}
26
-
27
-  \item{pAcc}{boolean value indicating if the significance
28
-  of the total accumulation in regards to the bootstrap
29
-  permutations should be computed}
30
-
31
-  \item{pORA}{boolean value indicating if the
32
-  over-represtation p-value should be computed}
33
-
34
-  \item{comb.pv}{vector of the p-value names to be combine
35
-  (any of the above p-values)}
36
-
37
-  \item{comb.pv.func}{the function to combine the p-values;
38
-  takes as input a vector of p-values and returns the
39
-  combined p-value}
40
-
41
-  \item{order.by}{the name of the p-value that is used to
42
-  order the results}
43
-
44
-  \item{adjust.method}{the name of the method to adjust the
45
-  p-value (see \link{p.adjust})}
46
-}
47
-\description{
48
-  Summarize the results of a Pathway-Express analysis
49
-}
50
-\examples{
51
-# load experiment
52
-load(system.file("extdata/E-GEOD-21942.topTable.RData", package = "ROntoTools"))
53
-fc <- top$logFC[top$adj.P.Val <= .01]
54
-names(fc) <- top$entrez[top$adj.P.Val <= .01]
55
-ref <- top$entrez
56
-
57
-# load the set of pathways
58
-kpg <- keggPathwayGraphs("hsa")
59
-kpg <- setEdgeWeights(kpg)
60
-kpg <- setNodeWeights(kpg, defaultWeight = 1)
61
-
62
-# perform the pathway analysis
63
-peRes <- pe(fc, graphs = kpg, ref = ref, nboot = 100, verbose = TRUE)
64
-
65
-# obtain summary of results
66
-head(Summary(peRes))
67
-
68
-kpn <- keggPathwayNames("hsa")
69
-
70
-head(Summary(peRes))
71
-
72
-head(Summary(peRes, pathNames = kpn, totalAcc = FALSE, totalPert = FALSE,
73
-             pAcc = FALSE, pORA = FALSE, comb.pv = NULL, order.by = "pPert"))
74
-}
75
-\seealso{
76
-  \code{\link{pe}}
77
-}
78
-
79 0
new file mode 100644
... ...
@@ -0,0 +1,20 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/Summary-methods.R
3
+\docType{methods}
4
+\name{Summary,pDisRes-method}
5
+\alias{Summary,pDisRes-method}
6
+\title{Summarize the results of a Pathway-Express analysis}
7
+\usage{
8
+\S4method{Summary}{pDisRes}(x, ..., na.rm = FALSE)
9
+}
10
+\arguments{
11
+\item{x}{Primary dis-regulation analysis result object obtained using \code{\link{pDis}}}
12
+
13
+\item{...}{see \code{\link{summary.pDisRes}}}
14
+
15
+\item{na.rm}{ignored}
16
+}
17
+\description{
18
+Summarize the results of a Pathway-Express analysis
19
+}
20
+
0 21
new file mode 100644
... ...
@@ -0,0 +1,20 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/Summary-methods.R
3
+\docType{methods}
4
+\name{Summary,peRes-method}
5
+\alias{Summary,peRes-method}
6
+\title{Summarize the results of a Pathway-Express analysis}
7
+\usage{
8
+\S4method{Summary}{peRes}(x, ..., na.rm = FALSE)
9
+}
10
+\arguments{
11
+\item{x}{Pathway-Express analysis result object obtained using \code{\link{pe}}}
12
+
13
+\item{...}{see \code{\link{summary.peRes}}}
14
+
15
+\item{na.rm}{ignored}
16
+}
17
+\description{
18
+Summarize the results of a Pathway-Express analysis
19
+}
20
+
... ...
@@ -1,31 +1,33 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/utils.R
1 3
 \name{alpha1MR}
2 4
 \alias{alpha1MR}
3 5
 \title{Compute alpha weights}
4 6
 \usage{
5
-  alpha1MR(pv, threshold = max(pv))
7
+alpha1MR(pv, threshold = max(pv))
6 8
 }
7 9
 \arguments{
8
-  \item{pv}{vector of p-values}
10
+\item{pv}{vector of p-values}
9 11
 
10
-  \item{threshold}{the threshold value that was used to
11
-  select DE genes}
12
+\item{threshold}{the threshold value that was used to select DE genes}
12 13
 }
13 14
 \description{
14
-  Transform a vector of p-values into weights.
15
+Transform a vector of p-values into weights.
15 16
 }
16 17
 \details{
17
-  Computes a set of weights from p-values using the formula
18
-  \code{1-pv/threshold}.
18
+Computes a set of weights from p-values using the formula \code{1-pv/threshold}.
19 19
 }
20 20
 \examples{
21
+
21 22
 load(system.file("extdata/E-GEOD-21942.topTable.RData", package = "ROntoTools"))
22 23
 
23 24
 head(alpha1MR(top$adj.P.Val))
25
+
24 26
 }
25 27
 \author{
26
-  Calin Voichita and Sorin Draghici
28
+Calin Voichita and Sorin Draghici
27 29
 }
28 30
 \seealso{
29
-  \code{\link{pe}}
31
+\code{\link{pe}}
30 32
 }
31 33
 
... ...
@@ -1,31 +1,33 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/utils.R
1 3
 \name{alphaMLG}
2 4
 \alias{alphaMLG}
3 5
 \title{Compute alpha weights}
4 6
 \usage{
5
-  alphaMLG(pv, threshold = max(pv))
7
+alphaMLG(pv, threshold = max(pv))
6 8
 }
7 9
 \arguments{
8
-  \item{pv}{vector of p-values}
10
+\item{pv}{vector of p-values}
9 11
 
10
-  \item{threshold}{the threshold value that was used to
11
-  select DE genes}
12
+\item{threshold}{the threshold value that was used to select DE genes}
12 13
 }
13 14
 \description{
14
-  Transform a vector of p-values into weights.
15
+Transform a vector of p-values into weights.
15 16
 }
16 17
 \details{
17
-  Computes a set of weights from p-values using the formula
18
-  \code{-log10(pv/threshold)}.
18
+Computes a set of weights from p-values using the formula \code{-log10(pv/threshold)}.
19 19
 }
20 20
 \examples{
21
+
21 22
 load(system.file("extdata/E-GEOD-21942.topTable.RData", package = "ROntoTools"))
22 23
 
23 24
 head(alphaMLG(top$adj.P.Val))
25
+
24 26
 }
25 27
 \author{
26
-  Calin Voichita and Sorin Draghici
28
+Calin Voichita and Sorin Draghici
27 29
 }
28 30
 \seealso{
29
-  \code{\link{pe}}
31
+\code{\link{pe}}
30 32
 }
31 33
 
... ...
@@ -1,32 +1,35 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/utils.R
1 3
 \name{compute.fisher}
2 4
 \alias{compute.fisher}
3 5
 \title{Combine independent p-values using the Fisher method}
4 6
 \usage{
5
-  compute.fisher(p, eps = 1e-06)
7
+compute.fisher(p, eps = 1e-06)
6 8
 }
7 9
 \arguments{
8
-  \item{p}{a vector of independent p-values}
10
+\item{p}{a vector of independent p-values}
9 11
 
10
-  \item{eps}{the minimal p-value considered (all p-values
11
-  smaller will be set to this value)}
12
+\item{eps}{the minimal p-value considered (all p-values smaller will be set to this value)}
13
+}
14
+\value{
15
+the combined p-value
12 16
 }
13 17
 \description{
14
-  Combine independent p-values using the Fisher method
18
+Combine independent p-values using the Fisher method
15 19
 }
16 20
 \examples{
21
+
17 22
 p <- c(.1, .01)
18 23
 compute.fisher(p)
24
+
19 25
 }
20 26
 \author{
21
-  Calin Voichita and Sorin Draghici
27
+Calin Voichita and Sorin Draghici
22 28
 }
23 29
 \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.
30
+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.
28 31
 }
29 32
 \seealso{
30
-  \code{\link{pe}},\code{\link{compute.normalInv}}
33
+\code{\link{pe}},\code{\link{compute.normalInv}}
31 34
 }
32 35
 
... ...
@@ -1,32 +1,35 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/utils.R
1 3
 \name{compute.normalInv}
2 4
 \alias{compute.normalInv}
3 5
 \title{Combine independent p-values using the normal inversion method}
4 6
 \usage{
5
-  compute.normalInv(p, eps = 1e-06)
7
+compute.normalInv(p, eps = 1e-06)
6 8
 }
7 9
 \arguments{
8
-  \item{p}{a vector of independent p-values}
10
+\item{p}{a vector of independent p-values}
9 11
 
10
-  \item{eps}{the minimal p-value considered (all p-values
11
-  smaller will be set to this value)}
12
+\item{eps}{the minimal p-value considered (all p-values smaller will be set to this value)}
13
+}
14
+\value{
15
+the combined p-value
12 16
 }
13 17
 \description{
14
-  Combine independent p-values using the normal inversion
15
-  method
18
+Combine independent p-values using the normal inversion method
16 19
 }
17 20
 \examples{
21
+
18 22
 p <- c(.1, .01)
19 23
 compute.normalInv(p)
24
+
20 25
 }
21 26
 \author{
22
-  Calin Voichita and Sorin Draghici
27
+Calin Voichita and Sorin Draghici
23 28
 }
24 29
 \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.
30
+Tarca AL., Draghici S., Romero R.: "A Mmore Specific Method To Combine Perturbation and Over-representation Evidence in Pathway Analysis", PSB 2010 poster.
28 31
 }
29 32