git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/GSVA@130609 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,10 +1,12 @@ |
1 | 1 |
Package: GSVA |
2 |
-Version: 1.25.2 |
|
2 |
+Version: 1.25.3 |
|
3 | 3 |
Title: Gene Set Variation Analysis for microarray and RNA-seq data |
4 | 4 |
Authors@R: c(person("Justin", "Guinney", role=c("aut", "cre"), email="justin.guinney@sagebase.org"), |
5 |
- person("Robert", "Castelo", role="aut", email="robert.castelo@upf.edu")) |
|
5 |
+ person("Robert", "Castelo", role="aut", email="robert.castelo@upf.edu"), |
|
6 |
+ person("Joan", "Fernandez", role="ctb", email="joanfernandez1331@gmail.com")) |
|
6 | 7 |
Depends: R (>= 2.13.0) |
7 |
-Imports: methods, BiocGenerics, Biobase, GSEABase (>= 1.17.4) |
|
8 |
+Imports: methods, BiocGenerics, Biobase, GSEABase (>= 1.17.4), |
|
9 |
+ geneplotter, shiny, shinythemes |
|
8 | 10 |
Suggests: limma, RColorBrewer, genefilter, mclust, |
9 | 11 |
edgeR, snow, parallel, GSVAdata |
10 | 12 |
Description: Gene Set Variation Analysis (GSVA) is a non-parametric, unsupervised method for estimating variation of gene set enrichment through the samples of a expression data set. GSVA performs a change in coordinate systems, transforming the data from a gene by sample matrix to a gene-set by sample matrix, thereby allowing the evaluation of pathway enrichment for each sample. This new matrix of GSVA enrichment scores facilitates applying standard analytical methods like functional enrichment, survival analysis, clustering, CNV-pathway analysis or cross-tissue pathway analysis, in a pathway-centric manner. |
... | ... |
@@ -2,6 +2,7 @@ useDynLib(GSVA) |
2 | 2 |
|
3 | 3 |
import(methods) |
4 | 4 |
import(BiocGenerics) |
5 |
+import(shiny) |
|
5 | 6 |
|
6 | 7 |
importClassesFrom(Biobase, ExpressionSet) |
7 | 8 |
importClassesFrom(GSEABase, GeneSetCollection) |
... | ... |
@@ -17,12 +18,19 @@ importFrom(graphics, plot) |
17 | 18 |
importFrom(stats, ecdf, |
18 | 19 |
na.omit) |
19 | 20 |
importFrom(utils, setTxtProgressBar, |
20 |
- txtProgressBar) |
|
21 |
-importFrom(Biobase, exprs) |
|
22 |
-importFrom(Biobase, annotation) |
|
23 |
-importFrom(GSEABase, AnnoOrEntrezIdentifier) |
|
24 |
-importFrom(GSEABase, mapIdentifiers) |
|
21 |
+ txtProgressBar, |
|
22 |
+ read.csv, |
|
23 |
+ write.csv) |
|
24 |
+importFrom(Biobase, exprs, |
|
25 |
+ annotation) |
|
26 |
+importFrom(GSEABase, AnnoOrEntrezIdentifier, |
|
27 |
+ mapIdentifiers, |
|
28 |
+ getGmt) |
|
29 |
+importFrom(geneplotter, multidensity) |
|
30 |
+importFrom(shinythemes, shinytheme) |
|
25 | 31 |
|
26 |
-exportMethods("gsva", |
|
27 |
- "filterGeneSets", |
|
28 |
- "computeGeneSetsOverlap") |
|
32 |
+exportMethods(gsva, |
|
33 |
+ filterGeneSets, |
|
34 |
+ computeGeneSetsOverlap) |
|
35 |
+ |
|
36 |
+export(igsva) |
29 | 37 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,366 @@ |
1 |
+#' |
|
2 |
+#' @importFrom shiny HTML actionButton animationOptions checkboxGroupInput column div downloadHandler downloadLink eventReactive fileInput fluidPage fluidRow h2 h3 h4 headerPanel htmlOutput mainPanel need numericInput NS observe observeEvent p plotOutput reactiveValues renderPlot renderUI selectInput shinyApp sliderInput stopApp tabPanel tabsetPanel textOutput uiOutput updateSelectInput validate wellPanel withProgress conditionalPanel reactive outputOptions tableOutput tags radioButtons downloadButton |
|
3 |
+#' @importFrom shinythemes shinytheme |
|
4 |
+#' @importFrom utils head |
|
5 |
+#' @importFrom geneplotter multidensity |
|
6 |
+#' @importFrom stats median |
|
7 |
+#' @importFrom graphics plot |
|
8 |
+#' @export |
|
9 |
+#' |
|
10 |
+ |
|
11 |
+selectDataInput <- function(id) { |
|
12 |
+ # Create a namespace function using the provided id |
|
13 |
+ ns <- NS(id) |
|
14 |
+ |
|
15 |
+ #UI declaration |
|
16 |
+ column( |
|
17 |
+ 3, |
|
18 |
+ h3("Select data source:"), |
|
19 |
+ #Select data source |
|
20 |
+ wellPanel(fluidRow( |
|
21 |
+ column( |
|
22 |
+ 12, |
|
23 |
+ #Select matrix |
|
24 |
+ radioButtons("matrixSourceType", "Select matrix:", |
|
25 |
+ c("From file" = "fileMatrix", |
|
26 |
+ "From workspace" = "varMatrix")) |
|
27 |
+ , |
|
28 |
+ #If the selected data source is a file |
|
29 |
+ conditionalPanel( |
|
30 |
+ condition = "input.matrixSourceType == 'fileMatrix'", |
|
31 |
+ fileInput("matrixFile", "Choose matrix file:", |
|
32 |
+ accept = c( |
|
33 |
+ "text/csv", |
|
34 |
+ "text/comma-separated-values,text/plain", |
|
35 |
+ ".csv",".ods",".xls",".xlt") |
|
36 |
+ ) |
|
37 |
+ ), |
|
38 |
+ #If the selected data source is a workspace object |
|
39 |
+ conditionalPanel( |
|
40 |
+ condition = "input.matrixSourceType == 'varMatrix'", |
|
41 |
+ selectInput("matrixVar", "Choose matrix var:", |
|
42 |
+ ls(envir=.GlobalEnv)) |
|
43 |
+ ), |
|
44 |
+ fluidRow(column(12, |
|
45 |
+ HTML("<br>"))), |
|
46 |
+ #Select geneset |
|
47 |
+ radioButtons("genesetSourceType", "Select GeneSet:", |
|
48 |
+ c("From file" = "fileGeneset", |
|
49 |
+ "From workspace" = "varGeneset")) |
|
50 |
+ , |
|
51 |
+ #If the selected data source is a file |
|
52 |
+ conditionalPanel( |
|
53 |
+ condition = "input.genesetSourceType == 'fileGeneset'", |
|
54 |
+ fileInput("genesetFile", "Choose GeneSet file:", |
|
55 |
+ accept = ".gmt") |
|
56 |
+ ), |
|
57 |
+ #If the selected data source is a workspace object |
|
58 |
+ conditionalPanel( |
|
59 |
+ condition = "input.genesetSourceType == 'varGeneset'", |
|
60 |
+ selectInput("genesetVar", "Choose GeneSet var:", |
|
61 |
+ ls(envir=.GlobalEnv)) |
|
62 |
+ ), |
|
63 |
+ HTML("<br>"), |
|
64 |
+ radioButtons("arg", "Control arguments:", |
|
65 |
+ c("No" = "no", |
|
66 |
+ "Yes" = "yes")) |
|
67 |
+ ) |
|
68 |
+ ), |
|
69 |
+ actionButton("button", "Run")) |
|
70 |
+ ) |
|
71 |
+} |
|
72 |
+ |
|
73 |
+mainDataInput <- function(id) { |
|
74 |
+ # Create a namespace function using the provided id |
|
75 |
+ ns <- NS(id) |
|
76 |
+ |
|
77 |
+ #UI Definition |
|
78 |
+ mainPanel(width = 6, |
|
79 |
+ h2("Generated GSVA data:"), |
|
80 |
+ textOutput("information"), |
|
81 |
+ plotOutput("plot"), |
|
82 |
+ tableOutput("result"), |
|
83 |
+ uiOutput("download")) |
|
84 |
+} |
|
85 |
+ |
|
86 |
+argumentsDataInput <- function(id) { |
|
87 |
+ # Create a namespace function using the provided id |
|
88 |
+ ns <- NS(id) |
|
89 |
+ |
|
90 |
+ #UI Definition |
|
91 |
+ column( |
|
92 |
+ 3, |
|
93 |
+ conditionalPanel( |
|
94 |
+ condition = "input.arg == 'yes'", |
|
95 |
+ h3("Select arguments:"), |
|
96 |
+ wellPanel(fluidRow( |
|
97 |
+ column( |
|
98 |
+ 12, |
|
99 |
+ selectInput("method", "Choose method:", |
|
100 |
+ c("gsva","ssgsea","zscore","plage")), |
|
101 |
+ radioButtons("rnaseq", "Rnaseq:", |
|
102 |
+ c("False" = FALSE, |
|
103 |
+ "True" = TRUE)), |
|
104 |
+ radioButtons("absRanking", "abs.ranking:", |
|
105 |
+ c("False" = FALSE, |
|
106 |
+ "True" = TRUE)), |
|
107 |
+ numericInput("minSz","min.sz:",value = 1), |
|
108 |
+ numericInput("maxSz","max.sz (Write 0 for infinite):",value = 0), |
|
109 |
+ numericInput("noBootstraps","no.bootstraps:",value = 0), |
|
110 |
+ numericInput("bootstrapPercent","bootstrap.percent:",value = .632), |
|
111 |
+ numericInput("parallelSz","parallel.sz:",value = 0), |
|
112 |
+ selectInput("parallelType", "parallel.type:", |
|
113 |
+ c("SOCK","MPI","NWS")), |
|
114 |
+ radioButtons("mxDiff", "mx.diff:", |
|
115 |
+ c("True" = TRUE, |
|
116 |
+ "False" = FALSE)), |
|
117 |
+ conditionalPanel( |
|
118 |
+ condition = "input.method == 'gsva'", |
|
119 |
+ numericInput("tau1","tau:",value = 1) |
|
120 |
+ ), |
|
121 |
+ conditionalPanel( |
|
122 |
+ condition = "input.method == 'ssgsea'", |
|
123 |
+ numericInput("tau2","tau:",value = 0.25) |
|
124 |
+ ), |
|
125 |
+ conditionalPanel( |
|
126 |
+ condition = "input.method == 'zscore' || input.method == 'plage'" |
|
127 |
+ ), |
|
128 |
+ radioButtons("kernel", "kernel:", |
|
129 |
+ c("True" = TRUE, |
|
130 |
+ "False" = FALSE)), |
|
131 |
+ radioButtons("ssgseaNorm", "ssgsea.norm:", |
|
132 |
+ c("True" = TRUE, |
|
133 |
+ "False" = FALSE)), |
|
134 |
+ radioButtons("verbose", "verbose:", |
|
135 |
+ c("True" = TRUE, |
|
136 |
+ "False" = FALSE)) |
|
137 |
+ ))) |
|
138 |
+ ) |
|
139 |
+ ) |
|
140 |
+} |
|
141 |
+ |
|
142 |
+gsva_validation <- function(input, output, session) { |
|
143 |
+ success <- FALSE #Variable to control if the GSVA variables are assigned correctly |
|
144 |
+ if(input$matrixSourceType == "fileMatrix") |
|
145 |
+ { |
|
146 |
+ if (is.null(input$matrixFile)) |
|
147 |
+ { |
|
148 |
+ paste("No matrix file selected!") |
|
149 |
+ success <- FALSE |
|
150 |
+ } |
|
151 |
+ else |
|
152 |
+ { |
|
153 |
+ #Matrix file selected |
|
154 |
+ if(input$genesetSourceType == "fileGeneset") |
|
155 |
+ { |
|
156 |
+ if (is.null(input$genesetFile)) |
|
157 |
+ { |
|
158 |
+ paste("No geneSet file selected!") |
|
159 |
+ success <- FALSE |
|
160 |
+ } |
|
161 |
+ else |
|
162 |
+ { |
|
163 |
+ #User selects matrix file and geneSet file |
|
164 |
+ inFile <- input$matrixFile |
|
165 |
+ newY <- as.matrix(read.csv(inFile$datapath, header = TRUE, sep = ",")) #Reading file as matrix |
|
166 |
+ rownames(newY) <- newY[,1] #Taking the first column as rownames |
|
167 |
+ newY <- newY[,-1] #Deleting the first column |
|
168 |
+ inGenesetFile <- input$genesetFile |
|
169 |
+ genes <- getGmt(inGenesetFile$datapath) |
|
170 |
+ if(input$maxSz == 0) { |
|
171 |
+ varMaxsz <- Inf |
|
172 |
+ }else { |
|
173 |
+ varMaxsz <- input$maxSz |
|
174 |
+ } |
|
175 |
+ success <- TRUE |
|
176 |
+ } |
|
177 |
+ } |
|
178 |
+ else |
|
179 |
+ { |
|
180 |
+ #User selects matrix file and geneset var |
|
181 |
+ inFile <- input$matrixFile |
|
182 |
+ newY <- as.matrix(read.csv(inFile$datapath, header = TRUE, sep = ",")) #Reading file as matrix |
|
183 |
+ rownames(newY) <- newY[,1] #Taking the first column as rownames |
|
184 |
+ newY <- newY[,-1] #Deleting the first column |
|
185 |
+ assign("genes",get(input$genesetVar)) |
|
186 |
+ if(input$maxSz == 0) { |
|
187 |
+ varMaxsz <- Inf |
|
188 |
+ }else { |
|
189 |
+ varMaxsz <- input$maxSz |
|
190 |
+ } |
|
191 |
+ success <- TRUE |
|
192 |
+ } |
|
193 |
+ } |
|
194 |
+ } |
|
195 |
+ else |
|
196 |
+ { |
|
197 |
+ #User selects matrix varand geneset file |
|
198 |
+ if(input$genesetSourceType == "fileGeneset") |
|
199 |
+ { |
|
200 |
+ if (is.null(input$genesetFile)) |
|
201 |
+ { |
|
202 |
+ paste("No geneSet file selected!") |
|
203 |
+ success <- FALSE |
|
204 |
+ } |
|
205 |
+ else |
|
206 |
+ { |
|
207 |
+ assign("newY",get(input$matrixVar)) |
|
208 |
+ inGenesetFile <- input$genesetFile |
|
209 |
+ genes <- getGmt(inGenesetFile$datapath) |
|
210 |
+ if(input$maxSz == 0) { |
|
211 |
+ varMaxsz <- Inf |
|
212 |
+ }else { |
|
213 |
+ varMaxsz <- input$maxSz |
|
214 |
+ } |
|
215 |
+ success <- TRUE |
|
216 |
+ } |
|
217 |
+ } |
|
218 |
+ else |
|
219 |
+ { |
|
220 |
+ #User selects matrix var selected and geneset var |
|
221 |
+ assign("newY",get(input$matrixVar)) |
|
222 |
+ assign("genes",get(input$genesetVar)) |
|
223 |
+ if(input$maxSz == 0) { |
|
224 |
+ varMaxsz <- Inf |
|
225 |
+ }else { |
|
226 |
+ varMaxsz <- input$maxSz |
|
227 |
+ } |
|
228 |
+ success <- TRUE |
|
229 |
+ } |
|
230 |
+ } |
|
231 |
+ if(success==TRUE) |
|
232 |
+ { |
|
233 |
+ gsva_generation(input, output, session, newY, genes,varMaxsz) |
|
234 |
+ gsva_information(input,output,session) |
|
235 |
+ } |
|
236 |
+} |
|
237 |
+ |
|
238 |
+gsva_generation <- function(input, output, session, newY, genes,varMaxsz) { |
|
239 |
+ x <- input$method |
|
240 |
+ selectedTau <- NULL |
|
241 |
+ switch (x, |
|
242 |
+ "gsva" = { |
|
243 |
+ selectedTau <- input$tau1 |
|
244 |
+ }, |
|
245 |
+ "ssgsea" = { |
|
246 |
+ selectedTau <- input$tau2 |
|
247 |
+ }, |
|
248 |
+ "zscore" = { |
|
249 |
+ selectedTau <- NULL |
|
250 |
+ }, |
|
251 |
+ "plage" = { |
|
252 |
+ selectedTau <- NULL |
|
253 |
+ } |
|
254 |
+ ) |
|
255 |
+ #GSVA Generation |
|
256 |
+ withProgress(message = 'Runing GSVA', value = 0, { |
|
257 |
+ incProgress(1, detail = "This may take a while...") |
|
258 |
+ generated_gsva <<- gsva(newY, genes, method = input$method, rnaseq = as.logical(input$rnaseq), abs.ranking = as.logical(input$absRanking), |
|
259 |
+ min.sz = input$minSz, max.sz = varMaxsz, no.bootstraps = input$noBootstraps, bootstrap.percent = input$bootstrapPercent, |
|
260 |
+ parallel.sz = input$parallelSz, parallel.type = input$parallelType, mx.diff = as.logical(input$mxDiff), tau = selectedTau, kernel = as.logical(input$kernel), |
|
261 |
+ ssgsea.norm = as.logical(input$ssgseaNorm), verbose = as.logical(input$verbose)) #Result asignation |
|
262 |
+ }) |
|
263 |
+} |
|
264 |
+ |
|
265 |
+gsva_information <- function(input, output, session) { |
|
266 |
+ if(class(generated_gsva) == "matrix") |
|
267 |
+ { |
|
268 |
+ resultInformation <- matrix(data = c(input$matrixVar,input$genesetVar,ncol(generated_gsva),nrow(generated_gsva)), nrow = 1, ncol = 4) |
|
269 |
+ colnames(resultInformation) <- c("Matrix used","GeneSet used", "Col num", "Row num") |
|
270 |
+ output$result <- renderTable(resultInformation) |
|
271 |
+ output$plot <- renderPlot(multidensity(as.list(as.data.frame(generated_gsva)), legend=NA, las=1, xlab=sprintf("%s scores", input$method), main="", lwd=2)) |
|
272 |
+ tagList( |
|
273 |
+ downloadButton('downloadData', 'Download'), |
|
274 |
+ actionButton('closeSave','Save & Close') |
|
275 |
+ ) |
|
276 |
+ } |
|
277 |
+ else |
|
278 |
+ { |
|
279 |
+ |
|
280 |
+ resultInformation <- matrix(data = c(input$matrixVar,input$genesetVar,ncol(generated_gsva$es.obs),nrow(generated_gsva$es.obs)), nrow = 1, ncol = 4) |
|
281 |
+ colnames(resultInformation) <- c("Matrix used","GeneSet used", "Col num", "Row num") |
|
282 |
+ output$result <- renderTable(resultInformation) |
|
283 |
+ if(class(generated_gsva$es.obs) == "ExpressionSet") #If the generated gsva is an ExpressionSet |
|
284 |
+ { |
|
285 |
+ expressionSetObs <- exprs(generated_gsva$es.obs) |
|
286 |
+ output$plot <- renderPlot(multidensity(as.list(as.data.frame(expressionSetObs)), legend=NA, las=1, xlab=sprintf("%s scores", input$method), main="", lwd=2)) |
|
287 |
+ } |
|
288 |
+ else |
|
289 |
+ { |
|
290 |
+ output$plot <- renderPlot(multidensity(as.list(as.data.frame(generated_gsva$es.obs)), legend=NA, las=1, xlab=sprintf("%s scores", input$method), main="", lwd=2)) |
|
291 |
+ } |
|
292 |
+ tagList( |
|
293 |
+ downloadButton('downloadData', 'Download'), |
|
294 |
+ actionButton('closeSave','Save & Close') |
|
295 |
+ ) |
|
296 |
+ } |
|
297 |
+} |
|
298 |
+ |
|
299 |
+download_handler <- function(input, output, session) { |
|
300 |
+ #Controls the Download button |
|
301 |
+ output$downloadData <- downloadHandler( |
|
302 |
+ filename = function() { |
|
303 |
+ paste("gsva_es-", Sys.Date(), ".csv", sep="") |
|
304 |
+ }, |
|
305 |
+ content = function(file) { |
|
306 |
+ if(class(generated_gsva) == "matrix") #If the whole object is a matrix |
|
307 |
+ { |
|
308 |
+ dataFrameObs <- as.data.frame(generated_gsva) |
|
309 |
+ write.csv(dataFrameObs, file) |
|
310 |
+ } |
|
311 |
+ else |
|
312 |
+ { |
|
313 |
+ if(class(generated_gsva$es.obs) == "ExpressionSet") #If the generated gsva es.obs is an ExpressionSet |
|
314 |
+ { |
|
315 |
+ expressionSetObs <- exprs(generated_gsva$es.obs) |
|
316 |
+ dataFrameObs <- as.data.frame(expressionSetObs) |
|
317 |
+ write.csv(dataFrameObs, file) |
|
318 |
+ } |
|
319 |
+ else |
|
320 |
+ { |
|
321 |
+ dataFrameObs <- as.data.frame(generated_gsva$es.obs) |
|
322 |
+ write.csv(dataFrameObs, file) |
|
323 |
+ } |
|
324 |
+ } |
|
325 |
+ } |
|
326 |
+ ) |
|
327 |
+} |
|
328 |
+ |
|
329 |
+igsva <- function() { |
|
330 |
+ app <- list(ui = NULL, server = NULL) |
|
331 |
+ app$ui <- fluidPage(theme = shinytheme("simplex"), |
|
332 |
+ fluidRow( |
|
333 |
+ selectDataInput("dataInput"), |
|
334 |
+ mainDataInput("mainInput") |
|
335 |
+ , |
|
336 |
+ fluidRow( |
|
337 |
+ argumentsDataInput("argumentsInput") |
|
338 |
+ ) |
|
339 |
+ ) |
|
340 |
+ ) |
|
341 |
+ |
|
342 |
+ app$server <- function(input, output, session) { |
|
343 |
+ v <- reactiveValues(action = FALSE) |
|
344 |
+ |
|
345 |
+ observeEvent(input$button, { |
|
346 |
+ v$action <- input$button |
|
347 |
+ }) |
|
348 |
+ |
|
349 |
+ output$download <- renderUI({ |
|
350 |
+ if(v$action) |
|
351 |
+ { |
|
352 |
+ #Isolates the Run event, that allows the program to run the generation only if the user clicks the button. |
|
353 |
+ isolate({ |
|
354 |
+ gsva_validation(input,output,session) |
|
355 |
+ }) |
|
356 |
+ } |
|
357 |
+ }) |
|
358 |
+ download_handler(input,output,session) |
|
359 |
+ |
|
360 |
+ #Observe the Save & Close button |
|
361 |
+ observeEvent(input$closeSave, { |
|
362 |
+ stopApp(generated_gsva) #Stops the app and returns the generated_gsva object |
|
363 |
+ }) |
|
364 |
+ } |
|
365 |
+ runApp(app) |
|
366 |
+} |
0 | 367 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,52 @@ |
1 |
+\name{igsva} |
|
2 |
+\alias{igsva} |
|
3 |
+ |
|
4 |
+\encoding{latin1} |
|
5 |
+ |
|
6 |
+\title{ |
|
7 |
+Gene Set Variation Analysis |
|
8 |
+} |
|
9 |
+\description{ |
|
10 |
+Starts an interactive GSVA shiny web app. |
|
11 |
+} |
|
12 |
+\usage{ |
|
13 |
+igsva() |
|
14 |
+} |
|
15 |
+\details{ |
|
16 |
+GSVA assesses the relative enrichment of gene sets across samples using |
|
17 |
+a non-parametric approach. Conceptually, GSVA transforms a p-gene by n-sample |
|
18 |
+gene expression matrix into a g-geneset by n-sample pathway enrichment matrix. |
|
19 |
+This facilitates many forms of statistical analysis in the 'space' of pathways |
|
20 |
+rather than genes, providing a higher level of interpretability. |
|
21 |
+ |
|
22 |
+The \code{igsva()} function starts an interactive shiny web app that allows the |
|
23 |
+user to configure the arguments of the \code{\link{gsva}()} function and runs it |
|
24 |
+on the computer. Please see the manual page of the \code{\link{gsva}()} function |
|
25 |
+for a description of the arguments and their default and alternative values. |
|
26 |
+ |
|
27 |
+The input data may be loaded from the users workspace or by selecting a CSV file |
|
28 |
+for the expression data, and a GMT file for the gene sets data. |
|
29 |
+} |
|
30 |
+\value{ |
|
31 |
+A gene-set by sample matrix of GSVA enrichment scores after |
|
32 |
+pressing the button 'Save & Close'. This result can be also downloaded as a |
|
33 |
+CSV file with the 'Download' button. |
|
34 |
+} |
|
35 |
+\references{ |
|
36 |
+\enc{H�nzelmann}{Hanzelmann}, S., Castelo, R. and Guinney, J. |
|
37 |
+GSVA: Gene set variation analysis for microarray and RNA-Seq data. |
|
38 |
+\emph{BMC Bioinformatics}, 14:7, 2013. |
|
39 |
+} |
|
40 |
+\author{J. \enc{Fern�ndez}{Fernandez} and R. Castelo} |
|
41 |
+\seealso{ |
|
42 |
+ \code{\link{gsva}} |
|
43 |
+} |
|
44 |
+\examples{ |
|
45 |
+ |
|
46 |
+\dontrun{ |
|
47 |
+res <- igsva() ## this will open your browser with the GSVA shiny web app |
|
48 |
+} |
|
49 |
+ |
|
50 |
+} |
|
51 |
+\keyword{GSVA} |
|
52 |
+\keyword{shiny} |