... | ... |
@@ -1,6 +1,6 @@ |
1 | 1 |
Package: hipathia |
2 | 2 |
Title: HiPathia: High-throughput Pathway Analysis |
3 |
-Version: 2.99.0 |
|
3 |
+Version: 2.99.1 |
|
4 | 4 |
Authors@R: c(person("Marta R.", "Hidalgo", email = "marta.hidalgo@outlook.es", role = c("aut", "cre")), |
5 | 5 |
person("José", "Carbonell-Caballero", role = c("ctb")), |
6 | 6 |
person("Francisco", "Salavert", role = c("ctb")), |
... | ... |
@@ -15,13 +15,12 @@ Description: Hipathia is a method for the computation of signal transduction alo |
15 | 15 |
the intensity of the signal arriving to it. It also provides a new approach |
16 | 16 |
to functional analysis allowing to compute the signal arriving to the |
17 | 17 |
functions annotated to each pathway. |
18 |
-Depends: R (>= 3.6), igraph (>= 1.0.1), AnnotationHub(>= 2.6.5), MultiAssayExperiment(>= 1.4.9), SummarizedExperiment(>= 1.8.1) |
|
18 |
+Depends: R (>= 4.1), igraph (>= 1.0.1), AnnotationHub(>= 2.6.5), MultiAssayExperiment(>= 1.4.9), SummarizedExperiment(>= 1.8.1) |
|
19 | 19 |
License: GPL-2 |
20 | 20 |
Encoding: UTF-8 |
21 |
-LazyData: true |
|
22 | 21 |
Imports: |
23 |
- coin, stats, limma, grDevices, utils, graphics, preprocessCore, servr, DelayedArray, matrixStats, methods, S4Vectors |
|
24 |
-RoxygenNote: 7.0.0 |
|
22 |
+ coin, stats, limma, grDevices, utils, graphics, preprocessCore, servr, DelayedArray, matrixStats, methods, S4Vectors, ggplot2, ggpubr, dplyr, tibble, visNetwork, reshape2, MetBrewer |
|
23 |
+RoxygenNote: 7.2.2 |
|
25 | 24 |
Suggests: BiocStyle, knitr, rmarkdown, testthat |
26 | 25 |
VignetteBuilder: knitr |
27 | 26 |
biocViews: Pathways, GraphAndNetwork, GeneExpression, GeneSignaling, GO |
... | ... |
@@ -1,6 +1,12 @@ |
1 | 1 |
# Generated by roxygen2: do not edit by hand |
2 | 2 |
|
3 |
+export(DAcomp) |
|
4 |
+export(DAoverview) |
|
5 |
+export(DAreport) |
|
6 |
+export(DAsummary) |
|
7 |
+export(DAtop) |
|
3 | 8 |
export(create_report) |
9 |
+export(define_colors) |
|
4 | 10 |
export(do_pca) |
5 | 11 |
export(do_wilcoxon) |
6 | 12 |
export(get_go_names) |
... | ... |
@@ -24,6 +30,7 @@ export(normalize_paths) |
24 | 30 |
export(paths_to_go_ancestor) |
25 | 31 |
export(pathway_comparison_plot) |
26 | 32 |
export(pca_plot) |
33 |
+export(plotVG) |
|
27 | 34 |
export(quantify_terms) |
28 | 35 |
export(save_results) |
29 | 36 |
export(top_pathways) |
... | ... |
@@ -32,32 +39,32 @@ export(visualize_report) |
32 | 39 |
import(AnnotationHub) |
33 | 40 |
import(MultiAssayExperiment) |
34 | 41 |
import(SummarizedExperiment) |
42 |
+import(ggplot2) |
|
35 | 43 |
import(grDevices) |
36 | 44 |
import(graphics) |
37 | 45 |
import(igraph) |
38 | 46 |
import(preprocessCore) |
39 | 47 |
import(servr) |
40 |
-import(ggplot2) |
|
41 | 48 |
import(visNetwork) |
42 | 49 |
importFrom(DelayedArray,colMaxs) |
43 | 50 |
importFrom(DelayedArray,colMins) |
44 | 51 |
importFrom(DelayedArray,rowMaxs) |
45 | 52 |
importFrom(DelayedArray,rowMins) |
53 |
+importFrom(MetBrewer,scale_fill_met_c) |
|
54 |
+importFrom(S4Vectors,DataFrame) |
|
55 |
+importFrom(dplyr,filter) |
|
56 |
+importFrom(dplyr,mutate) |
|
46 | 57 |
importFrom(dplyr,recode_factor) |
47 | 58 |
importFrom(dplyr,select) |
48 |
-importFrom(dplyr,mutate) |
|
49 |
-importFrom(dplyr,filter) |
|
50 | 59 |
importFrom(ggpubr,ggarrange) |
51 |
-importFrom(grDevices,rgb) |
|
52 | 60 |
importFrom(grDevices,colorRamp) |
61 |
+importFrom(grDevices,rgb) |
|
53 | 62 |
importFrom(matrixStats,colMeans2) |
54 | 63 |
importFrom(matrixStats,colMedians) |
55 | 64 |
importFrom(matrixStats,colProds) |
56 | 65 |
importFrom(matrixStats,rowVars) |
57 |
-importFrom(MetBrewer,scale_fill_met_c) |
|
58 | 66 |
importFrom(methods,is) |
59 | 67 |
importFrom(reshape2,melt) |
60 |
-importFrom(tibble,tibble) |
|
61 | 68 |
importFrom(stats,TukeyHSD) |
62 | 69 |
importFrom(stats,aov) |
63 | 70 |
importFrom(stats,cor.test) |
... | ... |
@@ -70,5 +77,5 @@ importFrom(stats,princomp) |
70 | 77 |
importFrom(stats,quantile) |
71 | 78 |
importFrom(stats,var) |
72 | 79 |
importFrom(stats,wilcox.test) |
73 |
-importFrom(S4Vectors,DataFrame) |
|
80 |
+importFrom(tibble,tibble) |
|
74 | 81 |
importFrom(utils,head) |
... | ... |
@@ -45,3 +45,10 @@ Version 2.3.2 (2019-05-17) |
45 | 45 |
|
46 | 46 |
Version 2.13.1 (2022-07-27) |
47 | 47 |
+ Fixing bug in nodes DE with limma with high rates of 0-variance genes. |
48 |
+ |
|
49 |
+Version 2.99.0 (2022-12-01) |
|
50 |
+ + Adding parameters uni.terms and GO.terms to hipathia, to compute functional activity within this function. |
|
51 |
+ + Adding functions DAcomp, DAtop, DAsummary, DAoverview, define_colors, plotVG, DAreport. |
|
52 |
+ + Modifyng structure of objects, by creating object DAdata, which includes more information than traditional hipathia results object. This includes: |
|
53 |
+ - Activity values of nodes, paths, and selected functions |
|
54 |
+ - Extra information about the paths, nodes and functions in rowData elements of the SummarizedExperiments |
... | ... |
@@ -76,8 +76,9 @@ DAcomp <- function(hidata, groups, expdes, g2 = NULL, |
76 | 76 |
(any(c("uni.terms", "GO.terms") %in% names(hidata)) & |
77 | 77 |
fun.method == "wilcoxon"))) |
78 | 78 |
stop("Wilcoxon comparison method needs two groups to compare, |
79 |
- introduced in arguments expdes and g2 (ex. expdes = 'case', g2 = 'control'). |
|
80 |
- Please provide both arguments or change comparison method to 'limma'.") |
|
79 |
+ introduced in arguments expdes and g2 (ex. expdes = 'case', g2 = |
|
80 |
+ 'control'). Please provide both arguments or change comparison method |
|
81 |
+ to 'limma'.") |
|
81 | 82 |
|
82 | 83 |
# Node comparison |
83 | 84 |
if(node.method == "wilcoxon"){ |
... | ... |
@@ -122,14 +123,16 @@ DAcomp <- function(hidata, groups, expdes, g2 = NULL, |
122 | 123 |
order = order) |
123 | 124 |
} |
124 | 125 |
mesdf <- get_measured_nodes(hidata)[rownames(path.comp),] |
125 |
- alt <- get_altered_nodes(hidata, node.comp, conf.level)[rownames(path.comp),] |
|
126 |
+ alt <- get_altered_nodes(hidata, |
|
127 |
+ node.comp, conf.level)[rownames(path.comp),] |
|
126 | 128 |
path.comp <- tibble(ID = rowData(hidata[["paths"]])$path.ID, |
127 | 129 |
name = rowData(hidata[["paths"]])$path.name, |
128 | 130 |
path.comp, |
129 | 131 |
N.nodes = mesdf$num.nodes, |
130 | 132 |
N.gene.nodes = mesdf$num.gene.nodes, |
131 | 133 |
N.measured.nodes = mesdf$num.measured.nodes, |
132 |
- ratio.measured.gene.nodes = mesdf$ratio.measured.gene.nodes, |
|
134 |
+ ratio.measured.gene.nodes = |
|
135 |
+ mesdf$ratio.measured.gene.nodes, |
|
133 | 136 |
nodes = rowData(hidata[["paths"]])$path.nodes, |
134 | 137 |
N.DA.nodes = alt$N.DA.nodes, |
135 | 138 |
DA.nodes = alt$DA.nodes) |
... | ... |
@@ -212,29 +215,32 @@ DAcomp <- function(hidata, groups, expdes, g2 = NULL, |
212 | 215 |
#' @importFrom dplyr recode_factor |
213 | 216 |
#' @importFrom dplyr mutate |
214 | 217 |
#' |
215 |
-topDA <- function(DAdata, n = 10, conf.level = 0.05, adjust = TRUE, colors = "hiro"){ |
|
218 |
+DAtop <- function(DAdata, n = 10, conf.level = 0.05, adjust = TRUE, |
|
219 |
+ colors = "hiro"){ |
|
216 | 220 |
colors <- define_colors(colors) |
217 | 221 |
toplist <- lapply(names(DAdata), function(feat){ |
218 | 222 |
DA <- DAdata[[feat]] |
219 | 223 |
if(feat == "nodes") DA$name <- paste(DA$name, "(node)") |
220 | 224 |
if(adjust == TRUE){ |
221 | 225 |
newn <- min(n, sum(DA$FDRp.value < conf.level)) |
222 |
- DA[order(DA$p.value, decreasing = FALSE),][1:newn,] %>% |
|
226 |
+ DA[order(DA$p.value, decreasing = FALSE),][seq_along(newn),] %>% |
|
223 | 227 |
mutate(logPV = abs(log10(FDRp.value)) * sign(statistic), |
224 | 228 |
feature = feat) |
225 | 229 |
}else{ |
226 | 230 |
newn <- min(n, sum(DA$p.value < conf.level)) |
227 |
- DA[order(DA$p.value, decreasing = FALSE),][1:newn,] %>% |
|
231 |
+ DA[order(DA$p.value, decreasing = FALSE),][seq_along(newn),] %>% |
|
228 | 232 |
mutate(logPV = abs(log10(p.value)) * sign(statistic), |
229 | 233 |
feature = feat) |
230 | 234 |
} |
231 | 235 |
}) |
232 | 236 |
names(toplist) <- names(DAdata) |
233 |
- top <- do.call(rbind, lapply(toplist, function(tl) select(tl, c(name, logPV, feature)))) |
|
237 |
+ top <- do.call(rbind, lapply(toplist, function(tl) select(tl, c(name, logPV, |
|
238 |
+ feature)))) |
|
234 | 239 |
top$name <- factor(top$name, levels = top$name[nrow(top):1]) |
235 | 240 |
top$feature <- factor(top$feature, |
236 | 241 |
levels = c("nodes", "paths", |
237 |
- names(DAdata)[!names(DAdata) %in% c("nodes", "paths")])) |
|
242 |
+ names(DAdata)[!names(DAdata) %in% |
|
243 |
+ c("nodes", "paths")])) |
|
238 | 244 |
top$feature <- recode_factor(top$feature, nodes = "Nodes", paths = "Paths", |
239 | 245 |
uni.terms = "Uniprot", GO.terms = "GO terms") |
240 | 246 |
dir <- c("UP", "DOWN") |
... | ... |
@@ -243,7 +249,8 @@ topDA <- function(DAdata, n = 10, conf.level = 0.05, adjust = TRUE, colors = "hi |
243 | 249 |
|
244 | 250 |
print(ggplot(top, aes(x = name, y = logPV, color = direction)) + |
245 | 251 |
geom_point(stat = "identity") + |
246 |
- scale_color_manual(name = "Status", values = c(colors$down, colors$up)) + |
|
252 |
+ scale_color_manual(name = "Status", values = c(colors$down, |
|
253 |
+ colors$up)) + |
|
247 | 254 |
# scale_fill_met_d("Hiroshige", direction = 1) + |
248 | 255 |
ylab("abs(Log10 of Adjusted P-value) * direction") + |
249 | 256 |
xlab("") + |
... | ... |
@@ -275,12 +282,13 @@ topDA <- function(DAdata, n = 10, conf.level = 0.05, adjust = TRUE, colors = "hi |
275 | 282 |
#' |
276 | 283 |
#' @return Plot and tibble including top \code{n} altered pathways. |
277 | 284 |
#' |
285 |
+#' @export |
|
278 | 286 |
#' @examples |
279 | 287 |
#' data(DAdata) |
280 | 288 |
#' DAsummary(DAdata) |
281 | 289 |
#' |
282 | 290 |
DAsummary <- function(DAdata, n = 10, conf.level = 0.05, adjust = TRUE, |
283 |
- ratio = F, colors = "hiro", order.by = "number"){ |
|
291 |
+ ratio = FALSE, colors = "hiro", order.by = "number"){ |
|
284 | 292 |
# Summary |
285 | 293 |
Psumm <- pathway_summary(DAdata, conf.level, adjust = adjust, |
286 | 294 |
order.by = order.by) |
... | ... |
@@ -308,7 +316,8 @@ DAsummary <- function(DAdata, n = 10, conf.level = 0.05, adjust = TRUE, |
308 | 316 |
#' @export |
309 | 317 |
#' @importFrom tibble tibble |
310 | 318 |
#' |
311 |
-DAoverview <- function(DAdata, conf.level = 0.05, adjust = TRUE, colors = "hiro"){ |
|
319 |
+DAoverview <- function(DAdata, conf.level = 0.05, adjust = TRUE, |
|
320 |
+ colors = "hiro"){ |
|
312 | 321 |
# Summary |
313 | 322 |
summ <- lapply(names(DAdata), function(feat){ |
314 | 323 |
data <- DAdata[[feat]] |
... | ... |
@@ -316,14 +325,18 @@ DAoverview <- function(DAdata, conf.level = 0.05, adjust = TRUE, colors = "hiro" |
316 | 325 |
summdf <- data.frame(feature = feat, |
317 | 326 |
total = nrow(data), |
318 | 327 |
sigs = sum(data$FDRp.value < conf.level), |
319 |
- UPs = sum(data$FDRp.value < conf.level & data$statistic > 0), |
|
320 |
- DOWNs = sum(data$FDRp.value < conf.level & data$statistic < 0)) |
|
328 |
+ UPs = sum(data$FDRp.value < conf.level & |
|
329 |
+ data$statistic > 0), |
|
330 |
+ DOWNs = sum(data$FDRp.value < conf.level & |
|
331 |
+ data$statistic < 0)) |
|
321 | 332 |
}else{ |
322 | 333 |
summdf <- data.frame(feature = feat, |
323 | 334 |
total = nrow(data), |
324 | 335 |
sigs = sum(data$p.value < conf.level), |
325 |
- UPs = sum(data$p.value < conf.level & data$statistic > 0), |
|
326 |
- DOWNs = sum(data$p.value < conf.level & data$statistic < 0)) |
|
336 |
+ UPs = sum(data$p.value < conf.level & |
|
337 |
+ data$statistic > 0), |
|
338 |
+ DOWNs = sum(data$p.value < conf.level & |
|
339 |
+ data$statistic < 0)) |
|
327 | 340 |
} |
328 | 341 |
}) |
329 | 342 |
summ <- tibble(do.call(rbind, summ)) |
... | ... |
@@ -345,8 +358,10 @@ pathway_summary <- function(DAdata, conf = 0.05, adjust = TRUE, |
345 | 358 |
mini <- comp[comp$pathway.ID == pathway,] |
346 | 359 |
if(adjust == TRUE){ |
347 | 360 |
pdf <- data.frame(sigs = sum(mini$FDRp.value < conf), |
348 |
- UPs = sum(mini$FDRp.value < conf & mini$statistic > 0), |
|
349 |
- DOWNs = sum(mini$FDRp.value < conf & mini$statistic < 0), |
|
361 |
+ UPs = sum(mini$FDRp.value < conf & |
|
362 |
+ mini$statistic > 0), |
|
363 |
+ DOWNs = sum(mini$FDRp.value < conf & |
|
364 |
+ mini$statistic < 0), |
|
350 | 365 |
total = nrow(mini), |
351 | 366 |
ratio.sigs = sum(mini$FDRp.value < conf)/nrow(mini), |
352 | 367 |
ratio.UPs = sum(mini$FDRp.value < conf & |
... | ... |
@@ -355,8 +370,10 @@ pathway_summary <- function(DAdata, conf = 0.05, adjust = TRUE, |
355 | 370 |
mini$statistic < 0)/nrow(mini)) |
356 | 371 |
}else{ |
357 | 372 |
pdf <- data.frame(sigs = sum(mini$p.value < conf), |
358 |
- UPs = sum(mini$p.value < conf & mini$statistic > 0), |
|
359 |
- DOWNs = sum(mini$p.value < conf & mini$statistic < 0), |
|
373 |
+ UPs = sum(mini$p.value < conf & |
|
374 |
+ mini$statistic > 0), |
|
375 |
+ DOWNs = sum(mini$p.value < conf & |
|
376 |
+ mini$statistic < 0), |
|
360 | 377 |
total = nrow(mini), |
361 | 378 |
ratio.sigs = sum(mini$p.value < conf)/nrow(mini), |
362 | 379 |
ratio.UPs = sum(mini$p.value < conf & |
... | ... |
@@ -373,14 +390,18 @@ pathway_summary <- function(DAdata, conf = 0.05, adjust = TRUE, |
373 | 390 |
mini <- ndata[ndata$pathway.ID == pathway,] |
374 | 391 |
if(adjust == TRUE){ |
375 | 392 |
ndf <- data.frame(sig.nodes = sum(mini$FDRp.value < conf), |
376 |
- UP.nodes = sum(mini$FDRp.value < conf & mini$statistic > 0), |
|
377 |
- DOWN.nodes = sum(mini$FDRp.value < conf & mini$statistic < 0), |
|
393 |
+ UP.nodes = sum(mini$FDRp.value < conf & |
|
394 |
+ mini$statistic > 0), |
|
395 |
+ DOWN.nodes = sum(mini$FDRp.value < conf & |
|
396 |
+ mini$statistic < 0), |
|
378 | 397 |
gene.nodes = sum(mini$type == "gene"), |
379 | 398 |
total.nodes = nrow(mini)) |
380 | 399 |
}else{ |
381 | 400 |
ndf <- data.frame(sig.nodes = sum(mini$p.value < conf), |
382 |
- UP.nodes = sum(mini$p.value < conf & mini$statistic > 0), |
|
383 |
- DOWN.nodes = sum(mini$p.value < conf & mini$statistic < 0), |
|
401 |
+ UP.nodes = sum(mini$p.value < conf & |
|
402 |
+ mini$statistic > 0), |
|
403 |
+ DOWN.nodes = sum(mini$p.value < conf & |
|
404 |
+ mini$statistic < 0), |
|
384 | 405 |
gene.nodes = sum(mini$type == "gene"), |
385 | 406 |
total.nodes = nrow(mini)) |
386 | 407 |
} |
... | ... |
@@ -410,9 +431,9 @@ pathway_summary <- function(DAdata, conf = 0.05, adjust = TRUE, |
410 | 431 |
#' @importFrom dplyr mutate |
411 | 432 |
#' @importFrom dplyr select |
412 | 433 |
#' |
413 |
-summary_plot <- function(Psumm, n.paths = 10, ratio = F, colors = "vg"){ |
|
434 |
+summary_plot <- function(Psumm, n.paths = 10, ratio = FALSE, colors = "vg"){ |
|
414 | 435 |
|
415 |
- pdata <- Psumm[1:n.paths,] |
|
436 |
+ pdata <- Psumm[seq_along(n.paths),] |
|
416 | 437 |
pdata$name <- factor(pdata$name, levels = pdata$name[n.paths:1]) |
417 | 438 |
|
418 | 439 |
palette <- define_colors(colors) |
... | ... |
@@ -422,10 +443,12 @@ summary_plot <- function(Psumm, n.paths = 10, ratio = F, colors = "vg"){ |
422 | 443 |
mutate(DOWN = DOWNs) %>% |
423 | 444 |
select(c(name, UP, DOWN, Not)) |
424 | 445 |
data1 <- melt(d1, "name") |
425 |
- data1$variable <- factor(data1$variable, levels = unique(data1$variable)[c(3,1,2)]) |
|
446 |
+ data1$variable <- factor(data1$variable, |
|
447 |
+ levels = unique(data1$variable)[c(3,1,2)]) |
|
426 | 448 |
g1 <- ggplot(data1, aes(x = name, y = value, fill = variable)) + |
427 | 449 |
geom_bar(stat = "identity") + |
428 |
- scale_fill_manual(name = "Status", values = c("#dfe0df", palette$up, palette$down)) + |
|
450 |
+ scale_fill_manual(name = "Status", |
|
451 |
+ values = c("#dfe0df", palette$up, palette$down)) + |
|
429 | 452 |
# scale_fill_met_d("Hiroshige", direction = 1) + |
430 | 453 |
ylab("Total significant paths") + |
431 | 454 |
xlab("Pathway") + |
... | ... |
@@ -442,7 +465,8 @@ summary_plot <- function(Psumm, n.paths = 10, ratio = F, colors = "vg"){ |
442 | 465 |
geom_point(aes(color = variable, size = nodes)) + |
443 | 466 |
geom_point(aes(size = nodes - 5), color = "white") + |
444 | 467 |
geom_point(aes(color = variable, size = value)) + |
445 |
- scale_color_manual(name = "Status", values = c(palette$up, palette$down)) + |
|
468 |
+ scale_color_manual(name = "Status", |
|
469 |
+ values = c(palette$up, palette$down)) + |
|
446 | 470 |
ylab("DE nodes") + |
447 | 471 |
ggtitle("") + |
448 | 472 |
theme_minimal() + |
... | ... |
@@ -488,16 +512,21 @@ nsig_plot <- function(summ, colors = "vg"){ |
488 | 512 |
mutate(UP = UPs) %>% |
489 | 513 |
mutate(DOWN = DOWNs) %>% |
490 | 514 |
select(c(feature, UP, DOWN, Not)) |
491 |
- d1$feature <- factor(d1$feature, levels = c("nodes", "paths", d1$feature[!d1$feature %in% c("nodes", "paths")])) |
|
515 |
+ d1$feature <- factor(d1$feature, |
|
516 |
+ levels = c("nodes", "paths", |
|
517 |
+ d1$feature[!d1$feature %in% |
|
518 |
+ c("nodes", "paths")])) |
|
492 | 519 |
d1$feature <- recode_factor(d1$feature, nodes = "Nodes", paths = "Paths", |
493 | 520 |
uni.terms = "Uniprot", GO.terms = "GO terms") |
494 | 521 |
|
495 | 522 |
data1 <- melt(d1, "feature") |
496 | 523 |
# data1$feature <- factor(data1$feature, levels = levels(data1$feature)[length(levels(data1$feature)):1]) |
497 |
- data1$variable <- factor(data1$variable, levels = unique(data1$variable)[c(3,1,2)]) |
|
524 |
+ data1$variable <- factor(data1$variable, |
|
525 |
+ levels = unique(data1$variable)[c(3,1,2)]) |
|
498 | 526 |
g <- ggplot(data1, aes(x = feature, y = value, fill = variable)) + |
499 | 527 |
geom_bar(stat = "identity") + |
500 |
- scale_fill_manual(name = "Status", values = c("#dfe0df", palette$up, palette$down)) + |
|
528 |
+ scale_fill_manual(name = "Status", |
|
529 |
+ values = c("#dfe0df", palette$up, palette$down)) + |
|
501 | 530 |
ylab("") + |
502 | 531 |
xlab("Feature") + |
503 | 532 |
ggtitle("Results overview") + |
... | ... |
@@ -596,12 +625,14 @@ get_edges_status <- function(pg, edgename, DApaths, adjust = TRUE){ |
596 | 625 |
} |
597 | 626 |
|
598 | 627 |
#' @importFrom dplyr mutate |
599 |
-prepare_DAedges <- function(DApaths, name, pathways, cols, conf = 0.05, adjust = TRUE){ |
|
628 |
+prepare_DAedges <- function(DApaths, name, pathways, cols, conf = 0.05, |
|
629 |
+ adjust = TRUE){ |
|
600 | 630 |
# require(dplyr) |
601 | 631 |
pg <- pathways$pathigraphs[[name]] |
602 | 632 |
|
603 | 633 |
# Define colors |
604 |
- color.edge.type <- c(cols$up, cols$down, cols$both, "lightgray", "gainsboro") # c(met.brewer("Egypt", 4), "gainsboro") # c("#0571b0", "green", "#ca0020", "#ffc868", "gainsboro") |
|
634 |
+ color.edge.type <- c(cols$up, cols$down, cols$both, "lightgray", |
|
635 |
+ "gainsboro") # c(met.brewer("Egypt", 4), "gainsboro") # c("#0571b0", "green", "#ca0020", "#ffc868", "gainsboro") |
|
605 | 636 |
names(color.edge.type) <- c("UP", "DOWN", "Both", "None", "function") |
606 | 637 |
|
607 | 638 |
# Create edges tibble |
... | ... |
@@ -771,6 +802,9 @@ prepare_nodes <- function(name, pathways, conf = 0.05, adjust = TRUE, |
771 | 802 |
#' pathways <- load_pathways("hsa") |
772 | 803 |
#' plotVG("hsa04010", pathways) |
773 | 804 |
#' |
805 |
+#' data(DAdata) |
|
806 |
+#' plotVG("hsa04010", pathways, DAdata) |
|
807 |
+#' |
|
774 | 808 |
#' @import visNetwork |
775 | 809 |
#' @export |
776 | 810 |
#' |
... | ... |
@@ -789,11 +823,14 @@ plotVG <- function(name, pathways, DAdata = NULL, colors = "hiro", |
789 | 823 |
color = c("lightgray", "gainsboro"), |
790 | 824 |
width = c(10, 1)) |
791 | 825 |
}else{ |
792 |
- nodes <- prepare_DAnodes(DAdata, name, pathways, cols, conf, adjust, no.col) |
|
793 |
- edges <- prepare_DAedges(DAdata[["paths"]], name, pathways, cols, conf, adjust) |
|
826 |
+ nodes <- prepare_DAnodes(DAdata, name, pathways, cols, conf, adjust, |
|
827 |
+ no.col) |
|
828 |
+ edges <- prepare_DAedges(DAdata[["paths"]], name, pathways, cols, conf, |
|
829 |
+ adjust) |
|
794 | 830 |
submain <- "Differential activation plot" |
795 | 831 |
ledges <- data.frame(label = c("UP", "DOWN", "Both", "None", "function"), |
796 |
- color = c(cols$up, cols$down, cols$both, "lightgray", "gainsboro"), |
|
832 |
+ color = c(cols$up, cols$down, cols$both, |
|
833 |
+ "lightgray", "gainsboro"), |
|
797 | 834 |
width = c(10, 10, 10, 10, 1)) |
798 | 835 |
} |
799 | 836 |
|
... | ... |
@@ -807,7 +844,8 @@ plotVG <- function(name, pathways, DAdata = NULL, colors = "hiro", |
807 | 844 |
#' @import visNetwork |
808 | 845 |
plotVisGraphDE <- function(nodes, edges, ledges, main = "Pathway", |
809 | 846 |
submain = "Differential activation plot", |
810 |
- cols = list(no = "BlanchedAlmond", up = "red", down = "blue"), |
|
847 |
+ cols = list(no = "BlanchedAlmond", up = "red", |
|
848 |
+ down = "blue"), |
|
811 | 849 |
height = "800px"){ |
812 | 850 |
# require(visNetwork, quietly = TRUE) |
813 | 851 |
|
... | ... |
@@ -887,8 +925,8 @@ plotVisGraphDE <- function(nodes, edges, ledges, main = "Pathway", |
887 | 925 |
visOptions(highlightNearest = list(enabled = TRUE, |
888 | 926 |
degree = 100, |
889 | 927 |
algorithm = "hierarchical", |
890 |
- hover = F, |
|
891 |
- labelOnly = F), |
|
928 |
+ hover = FALSE, |
|
929 |
+ labelOnly = FALSE), |
|
892 | 930 |
# nodesIdSelection = list(enabled = TRUE, |
893 | 931 |
# main = "Select by gene", |
894 | 932 |
# values = nodes$label[groups == "gene"]), |
... | ... |
@@ -897,7 +935,7 @@ plotVisGraphDE <- function(nodes, edges, ledges, main = "Pathway", |
897 | 935 |
# values = unique(nodes$label[groups == "function"]), |
898 | 936 |
# multiple = TRUE) |
899 | 937 |
) %>% |
900 |
- visLegend(position = "right", useGroups = T, main = "Legend", |
|
938 |
+ visLegend(position = "right", useGroups = TRUE, main = "Legend", |
|
901 | 939 |
addEdges = ledges) |
902 | 940 |
|
903 | 941 |
} |
904 | 942 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,89 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/devel.R |
|
3 |
+\name{DAcomp} |
|
4 |
+\alias{DAcomp} |
|
5 |
+\title{Compares the gene expression, pathway activation level and the function |
|
6 |
+activation level of the} |
|
7 |
+\usage{ |
|
8 |
+DAcomp( |
|
9 |
+ hidata, |
|
10 |
+ groups, |
|
11 |
+ expdes, |
|
12 |
+ g2 = NULL, |
|
13 |
+ path.method = "wilcoxon", |
|
14 |
+ node.method = "limma", |
|
15 |
+ fun.method = "wilcoxon", |
|
16 |
+ order = FALSE, |
|
17 |
+ paired = FALSE, |
|
18 |
+ adjust = TRUE, |
|
19 |
+ conf.level = 0.05, |
|
20 |
+ sel_assay = 1 |
|
21 |
+) |
|
22 |
+} |
|
23 |
+\arguments{ |
|
24 |
+\item{hidata}{Either a SummarizedExperiment object or a matrix, returned by |
|
25 |
+function \code{hipathia}.} |
|
26 |
+ |
|
27 |
+\item{groups}{Either a character indicating the name of the column in colData |
|
28 |
+including the classes to compare, or a character vector with the class to |
|
29 |
+which each sample belongs. |
|
30 |
+Samples must be ordered as in \code{hidata}.} |
|
31 |
+ |
|
32 |
+\item{expdes}{String, either an equation expression to pas to \code{limma}, |
|
33 |
+or the label of the first group to be compared} |
|
34 |
+ |
|
35 |
+\item{g2}{String, label of the second group to be compared, if not specified |
|
36 |
+in \code{expdes}.} |
|
37 |
+ |
|
38 |
+\item{path.method}{String, method to be used when comparing pathways. |
|
39 |
+Options include \code{wilcoxon} (default, performs a Wilcoxon test comparing |
|
40 |
+conditions \code{expdes} and \code{g2} - in this case, mandatory parameter) |
|
41 |
+and \code{limma} (performs a limma DE analysis using functions \code{lmFit}, |
|
42 |
+\code{contrasts.fit} and \code{eBayes} using the formula in \code{expdes} or |
|
43 |
+comparing conditions \code{expdes} and \code{g2}.} |
|
44 |
+ |
|
45 |
+\item{node.method}{String, method to be used when comparing nodes. |
|
46 |
+Options include \code{wilcoxon} (performs a Wilcoxon test comparing |
|
47 |
+conditions \code{expdes} and \code{g2} - in this case, mandatory parameter) |
|
48 |
+and \code{limma} (default, performs a limma DE analysis using functions |
|
49 |
+\code{lmFit}, \code{contrasts.fit} and \code{eBayes} using the formula in |
|
50 |
+\code{expdes} or comparing conditions \code{expdes} and \code{g2}.} |
|
51 |
+ |
|
52 |
+\item{fun.method}{String, method to be used when comparing functions. |
|
53 |
+Options include \code{wilcoxon} (default, performs a Wilcoxon test comparing |
|
54 |
+conditions \code{expdes} and \code{g2} - in this case, mandatory parameter) |
|
55 |
+and \code{limma} (performs a limma DE analysis using functions \code{lmFit}, |
|
56 |
+\code{contrasts.fit} and \code{eBayes} using the formula in \code{expdes} or |
|
57 |
+comparing conditions \code{expdes} and \code{g2}.} |
|
58 |
+ |
|
59 |
+\item{order}{Boolean, whether to order the results table by the |
|
60 |
+\code{FDRp.value} column. Default is FALSE.} |
|
61 |
+ |
|
62 |
+\item{paired}{Boolean, whether the samples to be compared are paired. |
|
63 |
+If TRUE, function \code{wilcoxsign_test} from package \code{coin} is |
|
64 |
+used. If FALSE, function \code{wilcox.test} from package \code{stats} |
|
65 |
+is used.} |
|
66 |
+ |
|
67 |
+\item{adjust}{Boolean, whether to adjust the p.value with |
|
68 |
+Benjamini-Hochberg FDR method. Default is TRUE.} |
|
69 |
+ |
|
70 |
+\item{sel_assay}{Character or integer, indicating the assay to be normalized |
|
71 |
+in the SummarizedExperiment. Default is 1.} |
|
72 |
+ |
|
73 |
+\item{conf_level}{Numeric, cut off for significance. Default is 0.05.} |
|
74 |
+} |
|
75 |
+\value{ |
|
76 |
+List including comparison results for nodes, pathways and functions, |
|
77 |
+if present. |
|
78 |
+} |
|
79 |
+\description{ |
|
80 |
+Compares the gene expression, pathway activation level and the function |
|
81 |
+activation level of the |
|
82 |
+} |
|
83 |
+\examples{ |
|
84 |
+data(path_vals) |
|
85 |
+data(brca_design) |
|
86 |
+sample_group <- brca_design[colnames(path_vals),"group"] |
|
87 |
+comp <- DAcomp(path_vals, sample_group, g1 = "Tumor", g2 = "Normal") |
|
88 |
+ |
|
89 |
+} |
0 | 90 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,33 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/devel.R |
|
3 |
+\name{DAoverview} |
|
4 |
+\alias{DAoverview} |
|
5 |
+\title{Table and plot of total number of altered and not altered nodes, paths and |
|
6 |
+functions (Uniprot keywords and/or GO terms, if present).} |
|
7 |
+\usage{ |
|
8 |
+DAoverview(DAdata, conf.level = 0.05, adjust = TRUE, colors = "hiro") |
|
9 |
+} |
|
10 |
+\arguments{ |
|
11 |
+\item{DAdata}{List of comparison results, returned by function \code{DAcomp}.} |
|
12 |
+ |
|
13 |
+\item{conf.level}{Numeric, cut off for significance. Default is 0.05.} |
|
14 |
+ |
|
15 |
+\item{adjust}{Boolean, whether to adjust the p.value with |
|
16 |
+Benjamini-Hochberg FDR method. Default is TRUE.} |
|
17 |
+ |
|
18 |
+\item{colors}{String with the color scheme or vector of colors to be used. |
|
19 |
+See \code{define_colors} for available options. Default is "hiro".} |
|
20 |
+} |
|
21 |
+\value{ |
|
22 |
+Plot and tibble including the number of total, altered, UP- and |
|
23 |
+DOWN-regulated features for nodes, paths and functions if present. |
|
24 |
+} |
|
25 |
+\description{ |
|
26 |
+Table and plot of total number of altered and not altered nodes, paths and |
|
27 |
+functions (Uniprot keywords and/or GO terms, if present). |
|
28 |
+} |
|
29 |
+\examples{ |
|
30 |
+data(DAdata) |
|
31 |
+DAoverview(DAdata) |
|
32 |
+ |
|
33 |
+} |
0 | 34 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,65 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/devel.R |
|
3 |
+\name{DAreport} |
|
4 |
+\alias{DAreport} |
|
5 |
+\title{Create visualization HTML} |
|
6 |
+\usage{ |
|
7 |
+DAreport( |
|
8 |
+ DAdata, |
|
9 |
+ pathways, |
|
10 |
+ conf.level = 0.05, |
|
11 |
+ adjust = TRUE, |
|
12 |
+ group_by = "pathway", |
|
13 |
+ colors = "classic", |
|
14 |
+ output_folder = NULL, |
|
15 |
+ path = NULL, |
|
16 |
+ verbose = TRUE |
|
17 |
+) |
|
18 |
+} |
|
19 |
+\arguments{ |
|
20 |
+\item{DAdata}{List of comparison results, returned by function \code{DAcomp}.} |
|
21 |
+ |
|
22 |
+\item{pathways}{Pathways object as returned by the \code{load_pathways} |
|
23 |
+function} |
|
24 |
+ |
|
25 |
+\item{conf.level}{Level of significance. By default 0.05.} |
|
26 |
+ |
|
27 |
+\item{adjust}{Boolean, whether to adjust the p.value with |
|
28 |
+Benjamini-Hochberg FDR method. Default is TRUE.} |
|
29 |
+ |
|
30 |
+\item{group_by}{How to group the subpathways to be visualized. By default |
|
31 |
+they are grouped by the pathway to which they belong. Available groupings |
|
32 |
+include "uniprot", to group subpathways by their annotated Uniprot functions, |
|
33 |
+"GO", to group subpathways by their annotated GO terms, and "genes", to group |
|
34 |
+subpathways by the genes they include. Default is set to "pathway".} |
|
35 |
+ |
|
36 |
+\item{colors}{String with the color scheme or vector of colors to be used. |
|
37 |
+See \code{define_colors} for available options. Default is "hiro".} |
|
38 |
+ |
|
39 |
+\item{output_folder}{Name of the folder in which the report will be stored.} |
|
40 |
+ |
|
41 |
+\item{path}{Absolute path to the parent directory in which `output_folder` |
|
42 |
+will be saved. If it is not provided, it will be created in a temp folder.} |
|
43 |
+ |
|
44 |
+\item{verbose}{Boolean, whether to show details about the results of the |
|
45 |
+execution} |
|
46 |
+} |
|
47 |
+\value{ |
|
48 |
+Saves the results and creates a report to visualize them through |
|
49 |
+a server in the specified \code{output_folder}. Returns the folder where |
|
50 |
+the report has been stored. |
|
51 |
+} |
|
52 |
+\description{ |
|
53 |
+Saves the results of a DAdata comparison for the Hipathia pathway values |
|
54 |
+into a folder, and creates a HTML from which to visualize the results on |
|
55 |
+top of the pathways. The results are stored into the specified folder. |
|
56 |
+If this folder does not exist, it will be created. The parent folder must |
|
57 |
+exist. |
|
58 |
+} |
|
59 |
+\examples{ |
|
60 |
+data(DAdata) |
|
61 |
+pathways <- load_pathways(species = "hsa", pathways_list = c("hsa03320", |
|
62 |
+"hsa04012")) |
|
63 |
+DAreport(DAdata, pathways) |
|
64 |
+ |
|
65 |
+} |
0 | 66 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,50 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/devel.R |
|
3 |
+\name{DAsummary} |
|
4 |
+\alias{DAsummary} |
|
5 |
+\title{Lists and plots the top \code{n} altered pathways, taking into account the |
|
6 |
+number of altered .} |
|
7 |
+\usage{ |
|
8 |
+DAsummary( |
|
9 |
+ DAdata, |
|
10 |
+ n = 10, |
|
11 |
+ conf.level = 0.05, |
|
12 |
+ adjust = TRUE, |
|
13 |
+ ratio = F, |
|
14 |
+ colors = "hiro", |
|
15 |
+ order.by = "number" |
|
16 |
+) |
|
17 |
+} |
|
18 |
+\arguments{ |
|
19 |
+\item{DAdata}{List of comparison results, returned by function \code{DAcomp}.} |
|
20 |
+ |
|
21 |
+\item{n}{Number of top features to show.} |
|
22 |
+ |
|
23 |
+\item{conf.level}{Numeric, cut off for significance. Default is 0.05.} |
|
24 |
+ |
|
25 |
+\item{adjust}{Boolean, whether to adjust the p.value with |
|
26 |
+Benjamini-Hochberg FDR method. Default is TRUE.} |
|
27 |
+ |
|
28 |
+\item{ratio}{Boolean, whether to plot the ratio of significant paths with |
|
29 |
+respect to the total paths in the pathway. Default is FALSE.} |
|
30 |
+ |
|
31 |
+\item{colors}{String with the color scheme or vector of colors to be used. |
|
32 |
+See \code{define_colors} for available options. Default is "hiro".} |
|
33 |
+ |
|
34 |
+\item{order.by}{String, how to order table of results. Available options |
|
35 |
+include \code{ratio} (default, uses the ratio of significant paths with |
|
36 |
+respect to the total paths in the pathway) and \code{number} (uses the number |
|
37 |
+of significant paths in the pathway).} |
|
38 |
+} |
|
39 |
+\value{ |
|
40 |
+Plot and tibble including top \code{n} altered pathways. |
|
41 |
+} |
|
42 |
+\description{ |
|
43 |
+Lists and plots the top \code{n} altered pathways, taking into account the |
|
44 |
+number of altered . |
|
45 |
+} |
|
46 |
+\examples{ |
|
47 |
+data(DAdata) |
|
48 |
+DAsummary(DAdata) |
|
49 |
+ |
|
50 |
+} |
0 | 51 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,35 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/devel.R |
|
3 |
+\name{DAtop} |
|
4 |
+\alias{DAtop} |
|
5 |
+\title{Lists and plots the top \code{n} altered nodes, paths and functions (Uniprot |
|
6 |
+keywords and/or GO terms, if present).} |
|
7 |
+\usage{ |
|
8 |
+DAtop(DAdata, n = 10, conf.level = 0.05, adjust = TRUE, colors = "hiro") |
|
9 |
+} |
|
10 |
+\arguments{ |
|
11 |
+\item{DAdata}{List of comparison results, returned by function \code{DAcomp}.} |
|
12 |
+ |
|
13 |
+\item{n}{Number of top features to show.} |
|
14 |
+ |
|
15 |
+\item{conf.level}{Numeric, cut off for significance. Default is 0.05.} |
|
16 |
+ |
|
17 |
+\item{adjust}{Boolean, whether to adjust the p.value with |
|
18 |
+Benjamini-Hochberg FDR method. Default is TRUE.} |
|
19 |
+ |
|
20 |
+\item{colors}{String with the color scheme or vector of colors to be used. |
|
21 |
+See \code{define_colors} for available options. Default is "hiro".} |
|
22 |
+} |
|
23 |
+\value{ |
|
24 |
+Plot and list of tables including top \code{n} altered features for |
|
25 |
+nodes, paths and functions if present. |
|
26 |
+} |
|
27 |
+\description{ |
|
28 |
+Lists and plots the top \code{n} altered nodes, paths and functions (Uniprot |
|
29 |
+keywords and/or GO terms, if present). |
|
30 |
+} |
|
31 |
+\examples{ |
|
32 |
+data(DAdata) |
|
33 |
+topDA(DAdata) |
|
34 |
+ |
|
35 |
+} |
... | ... |
@@ -4,12 +4,14 @@ |
4 | 4 |
\name{brca} |
5 | 5 |
\alias{brca} |
6 | 6 |
\title{BRCA gene expression dataset as SummarizedExperiment} |
7 |
-\format{SummarizedExperiment. The assay is a matrix with 40 columns and |
|
7 |
+\format{ |
|
8 |
+SummarizedExperiment. The assay is a matrix with 40 columns and |
|
8 | 9 |
18638 rows. Row names are Entrez IDs and column names are the TCGA |
9 | 10 |
identifyers of the samples. The colData() is a data.frame with 1 column and |
10 | 11 |
40 rows, including the experimental design of the 40 samples from the BRCA-US |
11 | 12 |
project from TCGA. Field \code{group} is the type of sample, either "Tumor" |
12 |
-or "Normal".} |
|
13 |
+or "Normal". |
|
14 |
+} |
|
13 | 15 |
\source{ |
14 | 16 |
\url{https://cancergenome.nih.gov/} |
15 | 17 |
} |
... | ... |
@@ -4,8 +4,10 @@ |
4 | 4 |
\name{brca_data} |
5 | 5 |
\alias{brca_data} |
6 | 6 |
\title{BRCA gene expression dataset} |
7 |
-\format{Matrix with 40 columns and 18638 rows. Row names are Entrez IDs |
|
8 |
-and column names are the TCGA identifyers of the samples.} |
|
7 |
+\format{ |
|
8 |
+Matrix with 40 columns and 18638 rows. Row names are Entrez IDs |
|
9 |
+and column names are the TCGA identifyers of the samples. |
|
10 |
+} |
|
9 | 11 |
\source{ |
10 | 12 |
\url{https://cancergenome.nih.gov/} |
11 | 13 |
} |
... | ... |
@@ -4,9 +4,11 @@ |
4 | 4 |
\name{brca_design} |
5 | 5 |
\alias{brca_design} |
6 | 6 |
\title{BRCA experimental design} |
7 |
-\format{Dataframe with 1 column and 40 rows, including the experimental |
|
7 |
+\format{ |
|
8 |
+Dataframe with 1 column and 40 rows, including the experimental |
|
8 | 9 |
design of the 40 samples from the BRCA-US project from TCGA. Field |
9 |
-\code{group} is the type of sample, either "Tumor" or "Normal".} |
|
10 |
+\code{group} is the type of sample, either "Tumor" or "Normal". |
|
11 |
+} |
|
10 | 12 |
\source{ |
11 | 13 |
\url{https://cancergenome.nih.gov/} |
12 | 14 |
} |
11 | 13 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,27 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/devel.R |
|
3 |
+\name{define_colors} |
|
4 |
+\alias{define_colors} |
|
5 |
+\title{Color palettes to be used in plots.} |
|
6 |
+\usage{ |
|
7 |
+define_colors(colors, no.col = NULL) |
|
8 |
+} |
|
9 |
+\arguments{ |
|
10 |
+\item{colors}{String with the color scheme or vector of colors to be used. |
|
11 |
+Available predefined options include: \code{hipathia}, \code{classic}, |
|
12 |
+\code{soft}, \code{okee}, \code{hiro}, \code{new}, \code{vg}, \code{orchid}.} |
|
13 |
+ |
|
14 |
+\item{no.col}{String with the color given to non-significant nodes, if not |
|
15 |
+given in parameter \code{colors}.} |
|
16 |
+} |
|
17 |
+\value{ |
|
18 |
+Plot and list of tables including top \code{n} altered features for |
|
19 |
+nodes, paths and functions if present. |
|
20 |
+} |
|
21 |
+\description{ |
|
22 |
+Color palettes to be used in plots. |
|
23 |
+} |
|
24 |
+\examples{ |
|
25 |
+define_colors("hiro") |
|
26 |
+ |
|
27 |
+} |
... | ... |
@@ -4,8 +4,10 @@ |
4 | 4 |
\name{exp_data} |
5 | 5 |
\alias{exp_data} |
6 | 6 |
\title{Normalized BRCA gene expression dataset} |
7 |
-\format{Matrix with 40 columns and 3184 rows. Row names are Entrez IDs |
|
8 |
-and column names are the TCGA identifyers of the samples.} |
|
7 |
+\format{ |
|
8 |
+Matrix with 40 columns and 3184 rows. Row names are Entrez IDs |
|
9 |
+and column names are the TCGA identifyers of the samples. |
|
10 |
+} |
|
9 | 11 |
\usage{ |
10 | 12 |
data(exp_data) |
11 | 13 |
} |
... | ... |
@@ -4,7 +4,7 @@ |
4 | 4 |
\alias{get_go_names} |
5 | 5 |
\title{Tranlates GO IDs to GO names} |
6 | 6 |
\usage{ |
7 |
-get_go_names(names, species, maxchar = NULL) |
|
7 |
+get_go_names(names, species, maxchar = NULL, disambiguate = FALSE) |
|
8 | 8 |
} |
9 | 9 |
\arguments{ |
10 | 10 |
\item{names}{Character vector with the GO IDs to be translated.} |
... | ... |
@@ -9,11 +9,11 @@ get_nodes_data(results, matrix = FALSE) |
9 | 9 |
\arguments{ |
10 | 10 |
\item{results}{Results object as returned by \code{hipathia}.} |
11 | 11 |
|
12 |
-\item{matrix}{Boolean, if TRUE the function returns a matrix object, if |
|
12 |
+\item{matrix}{Boolean, if TRUE the function returns a matrix object, if |
|
13 | 13 |
FALSE (as default) returns a SummarizedExperiment object.} |
14 | 14 |
} |
15 | 15 |
\value{ |
16 |
-Object, either a SummarizedExperiment or a matrix, with the levels |
|
16 |
+Object, either a SummarizedExperiment or a matrix, with the levels |
|
17 | 17 |
of activation of each decomposed subpathway for each sample. |
18 | 18 |
} |
19 | 19 |
\description{ |
... | ... |
@@ -9,11 +9,11 @@ get_paths_data(results, matrix = FALSE) |
9 | 9 |
\arguments{ |
10 | 10 |
\item{results}{Results object as returned by \code{hipathia}.} |
11 | 11 |
|
12 |
-\item{matrix}{Boolean, if TRUE the function returns a matrix object, if |
|
12 |
+\item{matrix}{Boolean, if TRUE the function returns a matrix object, if |
|
13 | 13 |
FALSE (as default) returns a SummarizedExperiment object.} |
14 | 14 |
} |
15 | 15 |
\value{ |
16 |
-Object, either a SummarizedExperiment or a matrix, with the levels |
|
16 |
+Object, either a SummarizedExperiment or a matrix, with the levels |
|
17 | 17 |
of activation of each decomposed subpathway for each sample. |
18 | 18 |
} |
19 | 19 |
\description{ |
... | ... |
@@ -4,8 +4,10 @@ |
4 | 4 |
\name{go_vals} |
5 | 5 |
\alias{go_vals} |
6 | 6 |
\title{Gene Ontology matrix of the BRCA gene expression dataset} |
7 |
-\format{Matrix with 40 columns and 1654 rows. Row names are Gene Ontology |
|
8 |
-terms and column names are the TCGA identifyers of the samples.} |
|
7 |
+\format{ |
|
8 |
+Matrix with 40 columns and 1654 rows. Row names are Gene Ontology |
|
9 |
+terms and column names are the TCGA identifyers of the samples. |
|
10 |
+} |
|
9 | 11 |
\usage{ |
10 | 12 |
data(go_vals) |
11 | 13 |
} |
... | ... |
@@ -11,7 +11,7 @@ hhead(mat, n = 5, sel_assay = 1) |
11 | 11 |
|
12 | 12 |
\item{n}{Number of rows and columns} |
13 | 13 |
|
14 |
-\item{sel_assay}{Character or integer, indicating the assay to be translated |
|
14 |
+\item{sel_assay}{Character or integer, indicating the assay to be translated |
|
15 | 15 |
in the SummarizedExperiment. Default is 1.} |
16 | 16 |
} |
17 | 17 |
\value{ |
... | ... |
@@ -2,14 +2,17 @@ |
2 | 2 |
% Please edit documentation in R/main.R |
3 | 3 |
\name{hipathia} |
4 | 4 |
\alias{hipathia} |
5 |
-\title{Computes the level of activation of the subpathways for each |
|
5 |
+\title{Computes the level of activation of the subpathways for each |
|
6 | 6 |
of the samples} |
7 | 7 |
\usage{ |
8 | 8 |
hipathia( |
9 | 9 |
genes_vals, |
10 | 10 |
metaginfo, |
11 |
+ uni.terms = FALSE, |
|
12 |
+ GO.terms = FALSE, |
|
11 | 13 |
sel_assay = 1, |
12 | 14 |
decompose = FALSE, |
15 |
+ scale = TRUE, |
|
13 | 16 |
maxnum = 100, |
14 | 17 |
verbose = TRUE, |
15 | 18 |
tol = 1e-06, |
... | ... |
@@ -17,19 +20,22 @@ hipathia( |
17 | 20 |
) |
18 | 21 |
} |
19 | 22 |
\arguments{ |
20 |
-\item{genes_vals}{A SummarizedExperiment or matrix with the normalized |
|
21 |
-expression values of the genes. Rows represent genes and columns represent |
|
23 |
+\item{genes_vals}{A SummarizedExperiment or matrix with the normalized |
|
24 |
+expression values of the genes. Rows represent genes and columns represent |
|
22 | 25 |
samples. Rownames() must be accepted gene IDs.} |
23 | 26 |
|
24 | 27 |
\item{metaginfo}{Pathways object} |
25 | 28 |
|
26 |
-\item{sel_assay}{Character or integer, indicating the assay to be processed |
|
27 |
-in the SummarizedExperiment. Only applied if \code{genes_vals} is a |
|
29 |
+\item{sel_assay}{Character or integer, indicating the assay to be processed |
|
30 |
+in the SummarizedExperiment. Only applied if \code{genes_vals} is a |
|
28 | 31 |
\code{SummarizedExperiment}.Default is 1.} |
29 | 32 |
|
30 | 33 |
\item{decompose}{Boolean, whether to compute the values for the decomposed |
31 | 34 |
subpathways. By default, effector subpathways are computed.} |
32 | 35 |
|
36 |
+\item{scale}{Boolean, whether to scale the values matrix to [0,1]. Default is |
|
37 |
+TRUE.} |
|
38 |
+ |
|
33 | 39 |
\item{maxnum}{Number of maximum iterations when iterating the signal |
34 | 40 |
through the loops into the pathways} |
35 | 41 |
|
... | ... |
@@ -42,7 +48,7 @@ iterating the signal through the loops into the pathways} |
42 | 48 |
\item{test}{Boolean, whether to test the input objects. Default is TRUE.} |
43 | 49 |
} |
44 | 50 |
\value{ |
45 |
-A MultiAssayExperiment object with the level of activation of the |
|
51 |
+A MultiAssayExperiment object with the level of activation of the |
|
46 | 52 |
subpathways from |
47 | 53 |
the pathways in \code{pathigraphs} for the experiment |
48 | 54 |
with expression values in \code{genes_vals}. |
... | ... |
@@ -55,7 +61,7 @@ data(exp_data) |
55 | 61 |
pathways <- load_pathways(species = "hsa", pathways_list = c("hsa03320", |
56 | 62 |
"hsa04012")) |
57 | 63 |
results <- hipathia(exp_data, pathways, verbose = TRUE) |
58 |
-\dontrun{results <- hipathia(exp_data, pathways, decompose = TRUE, |
|
64 |
+\dontrun{results <- hipathia(exp_data, pathways, decompose = TRUE, |
|
59 | 65 |
verbose = FALSE)} |
60 | 66 |
|
61 | 67 |
} |
... | ... |
@@ -12,7 +12,7 @@ normalize_paths(path_vals, metaginfo) |
12 | 12 |
\item{metaginfo}{Pathways object} |
13 | 13 |
} |
14 | 14 |
\value{ |
15 |
-SummarizedExperiment or matrix of normalized pathway values, |
|
15 |
+SummarizedExperiment or matrix of normalized pathway values, |
|
16 | 16 |
depending on the class of \code{path_vals}. |
17 | 17 |
} |
18 | 18 |
\description{ |
... | ... |
@@ -4,8 +4,10 @@ |
4 | 4 |
\name{path_vals} |
5 | 5 |
\alias{path_vals} |
6 | 6 |
\title{Pathways matrix of the BRCA gene expression dataset} |
7 |
-\format{Matrix with 40 columns and 1868 rows. Row names are Pathway IDs |
|
8 |
-and column names are the TCGA identifyers of the samples.} |
|
7 |
+\format{ |
|
8 |
+Matrix with 40 columns and 1868 rows. Row names are Pathway IDs |
|
9 |
+and column names are the TCGA identifyers of the samples. |
|
10 |
+} |
|
9 | 11 |
\usage{ |
10 | 12 |
data(path_vals) |
11 | 13 |
} |
12 | 14 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,55 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/devel.R |
|
3 |
+\name{plotVG} |
|
4 |
+\alias{plotVG} |
|
5 |
+\title{Plots a pathway with or without the comparison information, using the |
|
6 |
+visNetwork library.} |
|
7 |
+\usage{ |
|
8 |
+plotVG( |
|
9 |
+ name, |
|
10 |
+ pathways, |
|
11 |
+ DAdata = NULL, |
|
12 |
+ colors = "hiro", |
|
13 |
+ conf = 0.05, |
|
14 |
+ adjust = TRUE, |
|
15 |
+ main = "Pathway", |
|
16 |
+ submain = "", |
|
17 |
+ no.col = "BlanchedAlmond", |
|
18 |
+ height = "800px" |
|
19 |
+) |
|
20 |
+} |
|
21 |
+\arguments{ |
|
22 |
+\item{name}{KEGG ID of the pathway to plot.} |
|
23 |
+ |
|
24 |
+\item{pathways}{Pathways object.} |
|
25 |
+ |
|
26 |
+\item{DAdata}{List of comparison results, returned by function \code{DAcomp}.} |
|
27 |
+ |
|
28 |
+\item{colors}{String with the color scheme or vector of colors to be used. |
|
29 |
+See \code{define_colors} for available options. Default is "hiro".} |
|
30 |
+ |
|
31 |
+\item{conf}{Numeric, cut off for significance. Default is 0.05.} |
|
32 |
+ |
|
33 |
+\item{adjust}{Boolean, whether to adjust the p.value with |
|
34 |
+Benjamini-Hochberg FDR method. Default is TRUE.} |
|
35 |
+ |
|
36 |
+\item{main}{Title of the plot.} |
|
37 |
+ |
|
38 |
+\item{submain}{Subtitle of the plot.} |
|
39 |
+ |
|
40 |
+\item{no.col}{String with the color given to non-significant nodes.} |
|
41 |
+ |
|
42 |
+\item{height}{Height of the plot. Default is "800px".} |
|
43 |
+} |
|
44 |
+\value{ |
|
45 |
+Plot of the pathway. |
|
46 |
+} |
|
47 |
+\description{ |
|
48 |
+Plots a pathway with or without the comparison information, using the |
|
49 |
+visNetwork library. |
|
50 |
+} |
|
51 |
+\examples{ |
|
52 |
+pathways <- load_pathways("hsa") |
|
53 |
+plotVG("hsa04010", pathways) |
|
54 |
+ |
|
55 |
+} |
... | ... |
@@ -23,7 +23,7 @@ use ("uniprot" for Uniprot Keywords or "GO" for Gene Ontology terms), or |
23 | 23 |
a dataframe with the annotation of the genes to the functions. First |
24 | 24 |
column are gene symbols, second column the functions.} |
25 | 25 |
|
26 |
-\item{out_matrix}{Boolean, whther the output object should be a matrix |
|
26 |
+\item{out_matrix}{Boolean, whther the output object should be a matrix |
|
27 | 27 |
object. Default is FALSE, returning a SummarizedExperiment object.} |
28 | 28 |
|
29 | 29 |
\item{normalize}{Boolean, whether to normalize the matrix of pathway |
... | ... |
@@ -7,19 +7,19 @@ |
7 | 7 |
translate_data(data, species, sel_assay = 1, verbose = TRUE) |
8 | 8 |
} |
9 | 9 |
\arguments{ |
10 |
-\item{data}{Either a SummarizedExperiment object or a matrix of gene |
|
10 |
+\item{data}{Either a SummarizedExperiment object or a matrix of gene |
|
11 | 11 |
expression.} |
12 | 12 |
|
13 | 13 |
\item{species}{Species of the samples.} |
14 | 14 |
|
15 |
-\item{sel_assay}{Character or integer, indicating the assay to be translated |
|
15 |
+\item{sel_assay}{Character or integer, indicating the assay to be translated |
|
16 | 16 |
in the SummarizedExperiment. Default is 1.} |
17 | 17 |
|
18 | 18 |
\item{verbose}{Boolean, whether to show details about the results of the |
19 | 19 |
execution.} |
20 | 20 |
} |
21 | 21 |
\value{ |
22 |
-Either a SummarizedExperiment or a matrix (depending on the input |
|
22 |
+Either a SummarizedExperiment or a matrix (depending on the input |
|
23 | 23 |
type) of gene expression with Entrez IDs as rownames. |
24 | 24 |
} |
25 | 25 |
\description{ |
... | ... |
@@ -111,8 +111,8 @@ data("brca") |
111 | 111 |
brca |
112 | 112 |
``` |
113 | 113 |
```{r, echo=FALSE, message=FALSE, warning=FALSE} |
114 |
-library(devtools) |
|
115 |
-load_all("~/appl/hipathia/") |
|
114 |
+# library(devtools) |
|
115 |
+# load_all("~/appl/hipathia/") |
|
116 | 116 |
``` |
117 | 117 |
|
118 | 118 |
The dataset `brca` is a `r Biocpkg("SummarizedExperiment")` object, including |