added plotCytoscapeGML , Geneset export formats, bug fixes
... | ... |
@@ -1,27 +1,32 @@ |
1 | 1 |
Package: NetPathMiner |
2 |
-Version: 1.1.3 |
|
2 |
+Version: 1.1.6 |
|
3 | 3 |
Date: 2014 onwards |
4 | 4 |
Title: NetPathMiner for Biological Network Construction, Path Mining |
5 |
- and Visualization |
|
5 |
+ and Visualization |
|
6 | 6 |
Author: Ahmed Mohamed <mohamed@kuicr.kyoto-u.ac.jp>, Tim Hancock |
7 |
- <timothy.hancock@kuicr.kyoto-u.ac.jp>, Ichigaku Takigawa |
|
8 |
- <takigawa@kuicr.kyoto-u.ac.jp>, Nicolas Wicker |
|
9 |
- <nicolas.wicker@unistra.fr> |
|
7 |
+ <timothy.hancock@kuicr.kyoto-u.ac.jp>, Ichigaku Takigawa |
|
8 |
+ <takigawa@kuicr.kyoto-u.ac.jp>, Nicolas Wicker |
|
9 |
+ <nicolas.wicker@unistra.fr> |
|
10 | 10 |
Maintainer: Ahmed Mohamed <mohamed@kuicr.kyoto-u.ac.jp> |
11 | 11 |
Description: NetPathMiner is a general framework for network path |
12 |
- mining using genome-scale networks. It constructs networks from |
|
13 |
- KGML, SBML and BioPAX files, providing three network |
|
14 |
- representations, metabolic, reaction and gene representations. |
|
15 |
- NetPathMiner finds active paths and applies machine learning |
|
16 |
- methods to summarize found paths for easy interpretation. It |
|
17 |
- also provides static and interactive visualizations of networks |
|
18 |
- and paths to aid manual investigation. |
|
19 |
-Depends: R (>= 3.0.2), igraph (>= 0.6) |
|
20 |
-Suggests: rBiopaxParser (>= 2.1), RCurl, RCytoscape |
|
12 |
+ mining using genome-scale networks. It constructs networks from |
|
13 |
+ KGML, SBML and BioPAX files, providing three network |
|
14 |
+ representations, metabolic, reaction and gene representations. |
|
15 |
+ NetPathMiner finds active paths and applies machine learning |
|
16 |
+ methods to summarize found paths for easy interpretation. It |
|
17 |
+ also provides static and interactive visualizations of networks |
|
18 |
+ and paths to aid manual investigation. |
|
19 |
+Depends: |
|
20 |
+ R (>= 3.0.2), |
|
21 |
+ igraph (>= 0.6) |
|
22 |
+Suggests: |
|
23 |
+ rBiopaxParser (>= 2.1), |
|
24 |
+ RCurl, |
|
25 |
+ RCytoscape |
|
21 | 26 |
License: GPL (>= 2) |
22 | 27 |
URL: https://github.com/ahmohamed/NetPathMiner |
23 | 28 |
NeedsCompilation: yes |
24 | 29 |
SystemRequirements: libxml2, libSBML (>= 5.5) |
25 | 30 |
Biarch: TRUE |
26 | 31 |
biocViews: GraphAndNetwork, Pathways, Network, Clustering, |
27 |
- Classification |
|
32 |
+ Classification |
... | ... |
@@ -1,3 +1,5 @@ |
1 |
+# Generated by roxygen2 (4.0.1): do not edit by hand |
|
2 |
+ |
|
1 | 3 |
export(KGML2igraph) |
2 | 4 |
export(NPMdefaults) |
3 | 5 |
export(SBML2igraph) |
... | ... |
@@ -26,6 +28,7 @@ export(plotClusterMatrix) |
26 | 28 |
export(plotClusterProbs) |
27 | 29 |
export(plotClusters) |
28 | 30 |
export(plotCytoscape) |
31 |
+export(plotCytoscapeGML) |
|
29 | 32 |
export(plotNetwork) |
30 | 33 |
export(plotPathClassifier) |
31 | 34 |
export(plotPathCluster) |
... | ... |
@@ -0,0 +1,12 @@ |
1 |
+NetPathMiner 1.1.6 |
|
2 |
+=========== |
|
3 |
+ |
|
4 |
+* plotCytoscapeGML: a new function to export network plots as GML files, for Cytoscape 3.0 compatibility. |
|
5 |
+* getGetsetNetworks now can return pathway-class objects, used by graphite package, which allows fast topology-based geneset analyses. |
|
6 |
+* getGenesets now can export the results in GMT file format, readily parsed by most GSEA packages. |
|
7 |
+* Bug fixes on KGML signaling network construction. |
|
8 |
+ |
|
9 |
+NetPathMiner 1.1.3 |
|
10 |
+=========== |
|
11 |
+ |
|
12 |
+* Bioconductor stable release on the development branch |
... | ... |
@@ -144,7 +144,7 @@ KGML2igraph <- function(filename, parse.as=c("metabolic","signaling"), expand.co |
144 | 144 |
|
145 | 145 |
|
146 | 146 |
KGML_signal <- function(fileList, expand.complexes, verbose){ |
147 |
- if(verbose) message("Parsing KGML files as metabolic networks") |
|
147 |
+ if(verbose) message("Parsing KGML files as signaling networks") |
|
148 | 148 |
zkgml <- .Call("readkgml_sign", FILENAME = fileList, |
149 | 149 |
EXPAND_COMPLEXES = expand.complexes, VERBOSE=verbose) |
150 | 150 |
|
... | ... |
@@ -377,6 +377,8 @@ expandComplexes <- function(graph, v.attr, |
377 | 377 |
for(i in list.edge.attributes(graph)){ |
378 | 378 |
gout <- set.edge.attribute(gout, i, value=get.edge.attribute(graph, i)[z$e.parents] ) |
379 | 379 |
} |
380 |
+ |
|
381 |
+ gout$source <- graph$source |
|
380 | 382 |
return(gout); |
381 | 383 |
} |
382 | 384 |
|
... | ... |
@@ -493,9 +493,11 @@ assignEdgeWeights <- function(microarray, graph, use.attr, y, weight.method="cor |
493 | 493 |
#' |
494 | 494 |
#' @param graph An annotated igraph object.. |
495 | 495 |
#' @param use.attr The attribute by which vertices are grouped (tepically pathway, or GO) |
496 |
-#' @param gene.attr The attribute listing genes annotated with each vertex (ex: miriam.ncbigene, miriam.uniprot, ...) |
|
496 |
+#' @param gene.attr The attribute listing genes annotated with each vertex (ex: miriam.ncbigene, miriam.uniprot, ...) |
|
497 |
+#' @param gmt.file Optinal. If provided, Results are exported to a GMT file. GMT files are readily used |
|
498 |
+#' by most gene set analysis packages. |
|
497 | 499 |
#' |
498 |
-#' @return A list of genesets. |
|
500 |
+#' @return A list of genesets or written to gmt file if provided. |
|
499 | 501 |
#' |
500 | 502 |
#' @author Ahmed Mohamed |
501 | 503 |
#' @seealso \code{\link{getGeneSetNetworks}} |
... | ... |
@@ -503,8 +505,19 @@ assignEdgeWeights <- function(microarray, graph, use.attr, y, weight.method="cor |
503 | 505 |
#' @examples |
504 | 506 |
#' data(ex_kgml_sig) # Ras and chemokine signaling pathways in human |
505 | 507 |
#' genesets <- getGeneSets(ex_kgml_sig, use.attr="pathway", gene.attr="miriam.ncbigene") |
508 |
+#' |
|
509 |
+#' \donttest{ |
|
510 |
+#' # Write the genesets in a GMT file, and read it using GSEABase package. |
|
511 |
+#' getGeneSets(ex_kgml_sig, use.attr="pathway", gene.attr="miriam.ncbigene", gmt.file="kgml.gmt") |
|
512 |
+#' if(require(GSEABase)) |
|
513 |
+#' toGmt("kgml.gmt") |
|
514 |
+#' } |
|
515 |
+#' |
|
516 |
+#' # Create genesets using compartment information |
|
517 |
+#' data(ex_sbml) # bipartite metabolic network of Carbohydrate metabolism. |
|
518 |
+#' genesets <- getGeneSets(ex_sbml, use.attr="compartment.name", gene.attr="miriam.uniprot") |
|
506 | 519 |
#' |
507 |
-getGeneSets <- function(graph, use.attr="pathway", gene.attr="genes"){ |
|
520 |
+getGeneSets <- function(graph, use.attr="pathway", gene.attr="genes", gmt.file){ |
|
508 | 521 |
attr.names <- getAttrNames(graph) |
509 | 522 |
if(!use.attr %in% getAttrNames(graph)) |
510 | 523 |
stop(use.attr, ": attribute not found in graph.") |
... | ... |
@@ -521,7 +534,23 @@ getGeneSets <- function(graph, use.attr="pathway", gene.attr="genes"){ |
521 | 534 |
sets <- split(as.numeric(attr[,1]), attr[,2]) |
522 | 535 |
genesets <- lapply(sets, function(x) unlist(genes[x])) |
523 | 536 |
|
524 |
- return(genesets) |
|
537 |
+ if(!missing(gmt.file)){ |
|
538 |
+ pos <- regexpr("\\.([[:alnum:]]+)$", gmt.file) |
|
539 |
+ ext <- ifelse(pos > -1L, substring(gmt.file, pos + 1L), "") |
|
540 |
+ ext <- tolower(ext) |
|
541 |
+ |
|
542 |
+ if(!ext == "gmt") |
|
543 |
+ stop("File format not suuported. Please rename the file as *.gmt") |
|
544 |
+ |
|
545 |
+ gmt <- paste(names(genesets), paste(graph$source, use.attr), |
|
546 |
+ lapply(genesets, paste, sep="", collapse="\t"), |
|
547 |
+ sep="\t", collapse="\n") |
|
548 |
+ |
|
549 |
+ write(gmt, file=gmt.file) |
|
550 |
+ |
|
551 |
+ }else{ |
|
552 |
+ return(genesets) |
|
553 |
+ } |
|
525 | 554 |
} |
526 | 555 |
|
527 | 556 |
#' Generate geneset networks from an annotated network. |
... | ... |
@@ -531,8 +560,11 @@ getGeneSets <- function(graph, use.attr="pathway", gene.attr="genes"){ |
531 | 560 |
#' |
532 | 561 |
#' @param graph An annotated igraph object.. |
533 | 562 |
#' @param use.attr The attribute by which vertices are grouped (tepically pathway, or GO) |
563 |
+#' @param format The output format. If "list" is specified, a list of subgraphs are returned (default). |
|
564 |
+#' If "pathway-class" is specified, a list of pathway-class objects are returned. \link[graphite]{pathway-class} |
|
565 |
+#' is used by graphite package to run several methods of topology-based enrichment analyses. |
|
534 | 566 |
#' |
535 |
-#' @return A list of geneset networks. |
|
567 |
+#' @return A list of geneset networks as igraph or \link[graphite]{pathway-class} objects. |
|
536 | 568 |
#' |
537 | 569 |
#' @author Ahmed Mohamed |
538 | 570 |
#' @seealso \code{\link{getGeneSets}} |
... | ... |
@@ -540,8 +572,25 @@ getGeneSets <- function(graph, use.attr="pathway", gene.attr="genes"){ |
540 | 572 |
#' @examples |
541 | 573 |
#' data(ex_kgml_sig) # Ras and chemokine signaling pathways in human |
542 | 574 |
#' genesetnets <- getGeneSetNetworks(ex_kgml_sig, use.attr="pathway") |
575 |
+#' |
|
576 |
+#' # Integration with graphite package |
|
577 |
+#' \donttest{ |
|
578 |
+#' if(require(graphite) & require(clipper) & require(ALL)){ |
|
579 |
+#' genesetnets <- getGeneSetNetworks(ex_kgml_sig, |
|
580 |
+#' use.attr="pathway", format="pathway-class") |
|
581 |
+#' path <- convertIdentifiers(genesetnets$`Chemokine signaling pathway`, |
|
582 |
+#' "entrez") |
|
583 |
+#' genes <- nodes(path) |
|
584 |
+#' data(ALL) |
|
585 |
+#' all <- as.matrix(exprs(ALL[1:length(genes),1:20])) |
|
586 |
+#' classes <- c(rep(1,10), rep(2,10)) |
|
587 |
+#' rownames(all) <- genes |
|
588 |
+#' |
|
589 |
+#' runClipper(path, all, classes, "mean", pathThr=0.1) |
|
590 |
+#' } |
|
591 |
+#' } |
|
543 | 592 |
#' |
544 |
-getGeneSetNetworks <- function(graph, use.attr="pathway"){ |
|
593 |
+getGeneSetNetworks <- function(graph, use.attr="pathway", format=c("list", "pathway-class")){ |
|
545 | 594 |
attr.names <- getAttrNames(graph) |
546 | 595 |
if(!use.attr %in% getAttrNames(graph)) |
547 | 596 |
stop(use.attr, ": attribute not found in graph.") |
... | ... |
@@ -554,6 +603,68 @@ getGeneSetNetworks <- function(graph, use.attr="pathway"){ |
554 | 603 |
sets <- split(as.numeric(attr[,1]), attr[,2]) |
555 | 604 |
genesetnet <- lapply(sets, function(x) induced.subgraph(graph, x)) |
556 | 605 |
|
606 |
+ if(!missing(format) && format=="pathway-class"){ |
|
607 |
+ pathway <- setClass("pathway", |
|
608 |
+ representation(title="vector", |
|
609 |
+ nodes="vector", |
|
610 |
+ edges="data.frame", |
|
611 |
+ ident="vector", |
|
612 |
+ database="vector", |
|
613 |
+ timestamp="Date")) |
|
614 |
+ |
|
615 |
+ stds <- stdAttrNames(graph, "matches") |
|
616 |
+ if("miriam.ncbigene" %in% stds$standard){ |
|
617 |
+ annotation <- "miriam.ncbigene" |
|
618 |
+ }else if("miriam.uniprot" %in% stds$standard){ |
|
619 |
+ annotation <- "miriam.uniprot" |
|
620 |
+ }else{ |
|
621 |
+ stop("Provided graph doesn't contain Entrez IDs nor UniProt IDs needed for graphite package") |
|
622 |
+ } |
|
623 |
+ |
|
624 |
+ genesetnet <- lapply(genesetnet, function(g) |
|
625 |
+ try( |
|
626 |
+ expandComplexes(g, rownames(stds[stds$standard==annotation,]), missing.method="remove"), |
|
627 |
+ silent=TRUE) |
|
628 |
+ ) |
|
629 |
+ |
|
630 |
+ genesetnet <- genesetnet[ !sapply(genesetnet, class) == "try-error" ] |
|
631 |
+ |
|
632 |
+ genesetnet <- genesetnet[ !sapply(genesetnet, ecount) == 0 ] |
|
633 |
+ ann.prefix <- ifelse(annotation == "miriam.ncbigene", "EntrezGene", "UniProt") |
|
634 |
+ genesetnet <- lapply(genesetnet, function(g) |
|
635 |
+ set.vertex.attribute(g, "name", |
|
636 |
+ value=paste(ann.prefix, V(g)$name, sep=":") ) |
|
637 |
+ ) |
|
638 |
+ |
|
639 |
+ prepareEdges <- function(g){ |
|
640 |
+ ret <- data.frame( get.edgelist(g), |
|
641 |
+ direction="directed", |
|
642 |
+ type=as.character(E(g)$attr) |
|
643 |
+ ) |
|
644 |
+ names(ret)[1:2] <- c("src", "dest") |
|
645 |
+ ret$src <- as.character(ret$src) |
|
646 |
+ ret$dest <- as.character(ret$dest) |
|
647 |
+ return(ret) |
|
648 |
+ } |
|
649 |
+ |
|
650 |
+ edges <- lapply(genesetnet, function(g){ |
|
651 |
+ |
|
652 |
+ } ) |
|
653 |
+ |
|
654 |
+ pathwayset <- mapply(function(name, g){ |
|
655 |
+ pathway(title=name, |
|
656 |
+ nodes=V(g)$name, |
|
657 |
+ edges=prepareEdges(g), |
|
658 |
+ ident="native", |
|
659 |
+ database=paste("NetPathMiner(",graph$source,")", sep=""), |
|
660 |
+ timestamp=Sys.Date() |
|
661 |
+ ) |
|
662 |
+ }, names(genesetnet), genesetnet |
|
663 |
+ ) |
|
664 |
+ |
|
665 |
+ return(pathwayset) |
|
666 |
+ }# End pathway-class return |
|
667 |
+ |
|
557 | 668 |
return(genesetnet) |
558 | 669 |
} |
559 | 670 |
|
... | ... |
@@ -493,7 +493,7 @@ processNetwork <- function(graph, start, end, scale=c("ecdf", "rescale"), normal |
493 | 493 |
|
494 | 494 |
# Get edge.weights and apply ecdf on each column |
495 | 495 |
edge.weights <- do.call("rbind", as.list(E(graph)$edge.weights)) |
496 |
- cat("weights: ", nrow(edge.weights)) |
|
496 |
+ |
|
497 | 497 |
if(sum(!is.finite(edge.weights))>0){ |
498 | 498 |
warning("Edge weights contain non-finite numbers. Setting them to the minimum edge weight") |
499 | 499 |
|
... | ... |
@@ -512,7 +512,7 @@ processNetwork <- function(graph, start, end, scale=c("ecdf", "rescale"), normal |
512 | 512 |
if (ncol(edge.probs) > 1 & normalize == TRUE) { |
513 | 513 |
edge.probs <- edge.probs / rowSums(edge.probs) |
514 | 514 |
} |
515 |
- cat("weights: ", nrow(edge.probs)) |
|
515 |
+ |
|
516 | 516 |
if(scale=="ecdf") |
517 | 517 |
edge.probs <- -log(edge.probs) |
518 | 518 |
|
... | ... |
@@ -521,7 +521,7 @@ processNetwork <- function(graph, start, end, scale=c("ecdf", "rescale"), normal |
521 | 521 |
edgelist = get.edgelist(graph, names=FALSE) |
522 | 522 |
edgelist = data.frame(from=edgelist[,1], to=edgelist[,2], label=unlist(label), stringsAsFactors=FALSE) |
523 | 523 |
|
524 |
- cat("edges: ", nrow(edgelist), ",weights: ", nrow(edge.probs)) |
|
524 |
+ |
|
525 | 525 |
return(list(nodes=V(graph)$name, edges=edgelist, weights=edge.probs)) |
526 | 526 |
} |
527 | 527 |
|
... | ... |
@@ -295,12 +295,16 @@ colorVertexByAttr <- function(graph, attr.name, col.palette = palette()){ |
295 | 295 |
|
296 | 296 |
#' Plots an annotated igraph object in Cytoscape. |
297 | 297 |
#' |
298 |
-#' This function uses RCytoscape interface to plot igraph object in Cytoscape, enabling |
|
299 |
-#' interactive investigation of the network. The function requires an open Cytoscape window, |
|
300 |
-#' with CytoscapeRPC plugin activated. |
|
298 |
+#' Thess functions provide ways to plot igraph object in Cytoscape, enabling |
|
299 |
+#' interactive investigation of the network. \link{plotCytoscape} uses RCytoscape |
|
300 |
+#' interface to plot graphs in Cytoscape directly form R. The function is compatible with Cytoscape |
|
301 |
+#' 2.8.3 or lower, and requires an open Cytoscape window, with CytoscapeRPC plugin installed and activated. |
|
302 |
+#' \link{plotCytoscapeGML} exports the network plot in GML format, that can be later imported into Cytoscape |
|
303 |
+#' (using "import network from file" option). This fuction is compatible with all Cytoscape versions. |
|
301 | 304 |
#' |
302 | 305 |
#' @param graph An annotated igraph object. |
303 | 306 |
#' @param title Will be set as a window title in Cytoscape. |
307 |
+#' @param file Output GML file name to which the network plot is exported. |
|
304 | 308 |
#' @param layout Either a graph layout function, or a two-column matrix specifiying vertex coordinates. |
305 | 309 |
#' @param vertex.size Vertex size. If missing, the vertex attribute "size" (\preformatted{V(g)$size)}) will be used. |
306 | 310 |
#' @param vertex.label Vertex labels. If missing, the vertex attribute "label" (\preformatted{V(g)$label)}) will be used. |
... | ... |
@@ -317,13 +321,16 @@ colorVertexByAttr <- function(graph, attr.name, col.palette = palette()){ |
317 | 321 |
#' |
318 | 322 |
#' @author Ahmed Mohamed |
319 | 323 |
#' @family Plotting methods |
324 |
+#' @rdname plotCytoscape |
|
320 | 325 |
#' @export |
321 | 326 |
#' @examples |
327 |
+#' data("ex_sbml") |
|
328 |
+#' rgraph <- makeReactionNetwork(ex_sbml, simplify=TRUE) |
|
329 |
+#' v.layout <- layoutVertexByAttr(rgraph, "compartment") |
|
330 |
+#' v.color <- colorVertexByAttr(rgraph, "compartment") |
|
331 |
+#' |
|
322 | 332 |
#' \dontrun{ |
323 |
-#' data("ex_kgml_sig") |
|
324 |
-#' v.layout <- layoutVertexByAttr(ex_kgml_sig, "pathway") |
|
325 |
-#' |
|
326 |
-#' cw<-plotCytoscape(ex_kgml_sig, title="example", layout = v.layout, |
|
333 |
+#' cw<-plotCytoscape(rgraph, title="example", layout = v.layout, |
|
327 | 334 |
#' vertex.size = 5, vertex.color = v.color) |
328 | 335 |
#' } |
329 | 336 |
#' |
... | ... |
@@ -343,14 +350,14 @@ plotCytoscape <- function(graph, title, layout=layout.auto, |
343 | 350 |
for(i in 1:length(v.attrs)){ |
344 | 351 |
nel <- RCytoscape::initNodeAttribute(nel, names(v.attrs)[[i]], |
345 | 352 |
ifelse(v.attrs[[i]], "numeric", "char"), |
346 |
- ifelse(v.attrs, 1, "")) |
|
353 |
+ ifelse(v.attrs[[i]], 1, "")) |
|
347 | 354 |
} |
348 | 355 |
|
349 | 356 |
e.attrs <- sapply(list.edge.attributes(graph), function(x) is.numeric(get.edge.attribute(graph,x))) |
350 |
- for(i in 1:length(e.attrs)){ |
|
351 |
- nel <- RCytoscape::initEdgeAttribute(nel, names(e.attrs)[[i]], |
|
357 |
+ for(i in names(e.attrs)){ |
|
358 |
+ nel <- RCytoscape::initEdgeAttribute(nel, i, |
|
352 | 359 |
ifelse(e.attrs[[i]], "numeric", "char"), |
353 |
- ifelse(e.attrs, 1, "")) |
|
360 |
+ ifelse(e.attrs[[i]], 1, "")) |
|
354 | 361 |
} |
355 | 362 |
|
356 | 363 |
cw <- RCytoscape::new.CytoscapeWindow (title, graph=nel) |
... | ... |
@@ -446,6 +453,137 @@ plotCytoscape <- function(graph, title, layout=layout.auto, |
446 | 453 |
} |
447 | 454 |
|
448 | 455 |
|
456 |
+#' @return For \code{plotCytoscapeGML}, results are written to file. |
|
457 |
+#' |
|
458 |
+#' @export |
|
459 |
+#' @rdname plotCytoscape |
|
460 |
+#' @examples |
|
461 |
+#' # Export network plot to GML file |
|
462 |
+#' plotCytoscapeGML(rgraph, file="example.gml", layout=v.layout, |
|
463 |
+#' vertex.color=v.color, vertex.size=10) |
|
464 |
+#' |
|
465 |
+plotCytoscapeGML <- function(graph, file, layout=layout.auto, |
|
466 |
+ vertex.size, vertex.label, vertex.shape, vertex.color, edge.color){ |
|
467 |
+ |
|
468 |
+ #v.size |
|
469 |
+ if(!missing(vertex.size)){ |
|
470 |
+ if(length(vertex.size)==1) |
|
471 |
+ vertex.size <- rep(vertex.size, vcount(graph)) |
|
472 |
+ |
|
473 |
+ vertex.size <- as.integer(vertex.size) |
|
474 |
+ if(length(vertex.size) != vcount(graph)){ |
|
475 |
+ warning("Vertex sizes length and number of vertices don't match") |
|
476 |
+ }else{ |
|
477 |
+ V(graph)$size <- vertex.size |
|
478 |
+ } |
|
479 |
+ }else if(is.null(V(graph)$size)){ |
|
480 |
+ V(graph)$size <- 15 |
|
481 |
+ } |
|
482 |
+ |
|
483 |
+ #v.label |
|
484 |
+ if(!missing(vertex.label)){ |
|
485 |
+ if(length(vertex.label) == vcount(graph)){ |
|
486 |
+ V(graph)$label <- as.character(vertex.label) |
|
487 |
+ }else |
|
488 |
+ warning("Vertex lebels length and number of vertices don't match") |
|
489 |
+ } |
|
490 |
+ |
|
491 |
+ #v.shape |
|
492 |
+ igraphShape2Cyto <- function(x){ |
|
493 |
+ return(ifelse( x %in% c("square","rectangle","vrectangle"), "rect", |
|
494 |
+ ifelse(x %in% c("csquare","crectangle"), "round_rect", "ellipse" )) |
|
495 |
+ ) |
|
496 |
+ } |
|
497 |
+ if(!missing(vertex.shape)){ |
|
498 |
+ vertex.shape <- as.character(vertex.shape) |
|
499 |
+ if(length(vertex.shape)==1) |
|
500 |
+ vertex.shape <- rep(vertex.shape, vcount(graph)) |
|
501 |
+ |
|
502 |
+ if(length(vertex.shape) == vcount(graph)){ |
|
503 |
+ V(graph)$type <- vertex.shape |
|
504 |
+ }else |
|
505 |
+ warning("Vertex shapes length and number of vertices don't match") |
|
506 |
+ |
|
507 |
+ }else if(!is.null(V(graph)$shape)){ |
|
508 |
+ V(graph)$type <- igraphShape2Cyto(V(graph)$shape) |
|
509 |
+ }else{ |
|
510 |
+ V(graph)$type <- "ellipse" |
|
511 |
+ } |
|
512 |
+ |
|
513 |
+ #v.color |
|
514 |
+ col2hex <- function(x) return( rgb(t(col2rgb( x )/255)) ) |
|
515 |
+ if(!missing(vertex.color)){ |
|
516 |
+ vertex.color <- as.character(vertex.color) |
|
517 |
+ if(length(vertex.color)==1) |
|
518 |
+ vertex.color <- rep(vertex.color, vcount(graph)) |
|
519 |
+ |
|
520 |
+ if(length(vertex.color) == vcount(graph)){ |
|
521 |
+ V(graph)$fill <- col2hex(vertex.color) |
|
522 |
+ }else{ |
|
523 |
+ warning("Vertex colors length and number of vertices don't match.\n |
|
524 |
+ Multi-colored vertices are not supported in Cytoscape plots") |
|
525 |
+ } |
|
526 |
+ }else if(!is.null(V(graph)$color)){ |
|
527 |
+ V(graph)$fill <- col2hex(V(graph)$color) |
|
528 |
+ }else{ |
|
529 |
+ V(graph)$fill <- col2hex("skyblue") |
|
530 |
+ } |
|
531 |
+ |
|
532 |
+ #e.color |
|
533 |
+ if(!missing(edge.color)){ |
|
534 |
+ edge.color <- col2hex(edge.color) |
|
535 |
+ if(length(edge.color)==1) |
|
536 |
+ edge.color <- rep(edge.color, ecount(graph)) |
|
537 |
+ |
|
538 |
+ if(length(edge.color) == ecount(graph)){ |
|
539 |
+ E(graph)$fill <- col2hex(edge.color) |
|
540 |
+ }else |
|
541 |
+ warning("Edge colors length and number of vertices don't match") |
|
542 |
+ |
|
543 |
+ }else if(!is.null(E(graph)$color)){ |
|
544 |
+ E(graph)$fill <- col2hex(E(graph)$color) |
|
545 |
+ }else{ |
|
546 |
+ E(graph)$fill <- col2hex("grey") |
|
547 |
+ } |
|
548 |
+ |
|
549 |
+ if(!is.null(layout)){ |
|
550 |
+ if(is.function(layout)){ |
|
551 |
+ l <- layout(graph) #* max(V(graph)$size) |
|
552 |
+ V(graph)$x <- l[,1] |
|
553 |
+ V(graph)$y <- l[,2] |
|
554 |
+ }else if(ncol(layout)==2 && nrow(layout)==vcount(graph)){ |
|
555 |
+ V(graph)$x <- layout[,1] |
|
556 |
+ V(graph)$y <- layout[,2] |
|
557 |
+ }else{ |
|
558 |
+ warning("Incompatible layout dimensions. It should be 2 columns and rows matching number of vertices") |
|
559 |
+ } |
|
560 |
+ } |
|
561 |
+ |
|
562 |
+ attr <- get.data.frame(graph, what="both") |
|
563 |
+ node.attr <- attr$vertices[!sapply(attr$vertices, is.list)] |
|
564 |
+ node.graphics <- node.attr[ ,colnames(node.attr) %in% c("x", "y", "size", "type", "fill"), drop=FALSE] |
|
565 |
+ |
|
566 |
+ node.attr <- node.attr[ ,!colnames(node.attr) %in% c("x", "y", "size", "type", "fill", "shape", "color"), drop=FALSE] |
|
567 |
+ node.attr <- cbind(id=as.numeric(V(graph)), node.attr, graphics=toGML(node.graphics, "graphics")) |
|
568 |
+ nodes.gml <- toGML(node.attr, "node", "\n") |
|
569 |
+ |
|
570 |
+ |
|
571 |
+ edge.attr <- attr$edges[!sapply(attr$edges, is.list)] |
|
572 |
+ names(edge.attr)[1:2] <- c("source", "target") |
|
573 |
+ edge.attr[1:2] <- get.edgelist(graph,names=FALSE) |
|
574 |
+ edge.graphics <- edge.attr[ ,colnames(edge.attr) %in% c("size", "type", "fill"), drop=FALSE] |
|
575 |
+ |
|
576 |
+ edge.attr <- edge.attr[ ,!colnames(edge.attr) %in% c("size", "type", "fill", "shape", "color"), drop=FALSE] |
|
577 |
+ edge.attr <- cbind(edge.attr, graphics=toGML(edge.graphics, "graphics")) |
|
578 |
+ edges.gml <- toGML(edge.attr, "edge", "\n") |
|
579 |
+ |
|
580 |
+ gml.ret <- paste('Creator "NetPathMiner ', packageVersion("NetPathMiner"), |
|
581 |
+ ' ', date(),'" \n', |
|
582 |
+ 'graph [\n', nodes.gml, '\n', edges.gml, '\n]', |
|
583 |
+ sep='') |
|
584 |
+ |
|
585 |
+ write(gml.ret, file=file) |
|
586 |
+} |
|
449 | 587 |
####################### Internal functions for plotting ####################### |
450 | 588 |
|
451 | 589 |
plotNetwork_internal <- function(graph, vertex.color, col.palette = palette(), layout = layout.auto, legend,...){ |
... | ... |
@@ -731,6 +869,36 @@ drawLegend <- function(vertices, paths){ |
731 | 869 |
|
732 | 870 |
} |
733 | 871 |
|
872 |
+toGML <- function(attr, element, collapse=NULL){ |
|
873 |
+ l <- length(attr) |
|
874 |
+ num <- sapply(attr,is.numeric) |
|
875 |
+ |
|
876 |
+ # Formats create sprintf formulas for GML formatting. |
|
877 |
+ # In general, GML format follow the pattern: attr.name attr.val \n |
|
878 |
+ # Attribute string values are quoted. |
|
879 |
+ # |
|
880 |
+ # Format1 deals with attribute names. |
|
881 |
+ # Format2 deals with attribute values. |
|
882 |
+ # Format interwines format1 and format2, and supply it to sprintf method. |
|
883 |
+ |
|
884 |
+ format1 <- paste('%',1:l,'$s ', sep='') # attribute names exported as strings. |
|
885 |
+ format1[names(attr)== "graphics"] <- '' |
|
886 |
+ format2 <- paste('%', (1:l) + l,'$', ifelse(num, 'g', 's'), sep='') |
|
887 |
+ format2 <- paste(ifelse(num, '', '"'), |
|
888 |
+ format2, |
|
889 |
+ ifelse(num, '\n', '"\n'), |
|
890 |
+ sep='') |
|
891 |
+ |
|
892 |
+ format2[names(attr)== "graphics"] <- paste('%', which(names(attr)== "graphics") + l, '$s\n', sep='') |
|
893 |
+ |
|
894 |
+ format <- paste(t(cbind(format1, format2)), collapse='') |
|
895 |
+ format <- paste(element, '[\n', format, ']') |
|
896 |
+ |
|
897 |
+ |
|
898 |
+ ret <- paste( do.call(function(...) sprintf(format, ...), c(names(attr), attr)) ,collapse=collapse) |
|
899 |
+ return(ret) |
|
900 |
+} |
|
901 |
+ |
|
734 | 902 |
strWrap <- function(s, width=20){ |
735 | 903 |
for(i in 1:(floor( max(nchar(s))/ width )+1) ){ |
736 | 904 |
s <- gsub( paste( "(^| |\n)(.{", width-2, ",", width, "}) ", sep=""),"\\1\\2\n", s , perl=TRUE) |
... | ... |
@@ -1,3 +1,4 @@ |
1 |
+% Generated by roxygen2 (4.0.1): do not edit by hand |
|
1 | 2 |
\name{KGML2igraph} |
2 | 3 |
\alias{KGML2igraph} |
3 | 4 |
\title{Processes KGML files into igraph objects} |
... | ... |
@@ -6,51 +7,38 @@ KGML2igraph(filename, parse.as = c("metabolic", "signaling"), |
6 | 7 |
expand.complexes = FALSE, verbose = TRUE) |
7 | 8 |
} |
8 | 9 |
\arguments{ |
9 |
- \item{filename}{A character vector containing the KGML |
|
10 |
- files to be processed. If a directory path is provided, |
|
11 |
- all *.xml files in it and its subdirectories are |
|
12 |
- included.} |
|
10 |
+\item{filename}{A character vector containing the KGML files to be processed. |
|
11 |
+If a directory path is provided, all *.xml files in it and its subdirectories are included.} |
|
13 | 12 |
|
14 |
- \item{parse.as}{Whether to process file into a metabolic |
|
15 |
- or a signaling network.} |
|
13 |
+\item{parse.as}{Whether to process file into a metabolic or a signaling network.} |
|
16 | 14 |
|
17 |
- \item{expand.complexes}{Split protein complexes into |
|
18 |
- individual gene nodes. This argument is ignored if |
|
19 |
- \code{parse.as="metabolic"}} |
|
15 |
+\item{expand.complexes}{Split protein complexes into individual gene nodes. This argument is |
|
16 |
+ignored if \code{parse.as="metabolic"}} |
|
20 | 17 |
|
21 |
- \item{verbose}{Whether to display the progress of the |
|
22 |
- function.} |
|
18 |
+\item{verbose}{Whether to display the progress of the function.} |
|
23 | 19 |
} |
24 | 20 |
\value{ |
25 |
-An igraph object, representing a metbolic or a signaling |
|
26 |
-network. |
|
21 |
+An igraph object, representing a metbolic or a signaling network. |
|
27 | 22 |
} |
28 | 23 |
\description{ |
29 |
-This function takes KGML files as input, and returns either |
|
30 |
-a metabolic or a signaling network as output. |
|
24 |
+This function takes KGML files as input, and returns either a metabolic or a signaling |
|
25 |
+network as output. |
|
31 | 26 |
} |
32 | 27 |
\details{ |
33 |
-Users can specify whether files are processes as metabolic |
|
34 |
-or signaling networks. |
|
28 |
+Users can specify whether files are processes as metabolic or signaling networks. |
|
35 | 29 |
|
36 |
-Metabolic networks are given as bipartite graphs, where |
|
37 |
-metabolites and reactions represent vertex types. This is |
|
38 |
-constructed from <reaction> xml node in KGML file, |
|
39 |
-connecting them to their corresponding substrates and |
|
40 |
-products. Each reaction vertex has \code{genes} attribute, |
|
41 |
-listing all genes associated with the reaction. As a |
|
42 |
-general rule, reactions inherit all annotation attributes |
|
43 |
-of its catalyzig genes. |
|
30 |
+Metabolic networks are given as bipartite graphs, where metabolites and reactions represent |
|
31 |
+vertex types. This is constructed from <reaction> xml node in KGML file, connecting them |
|
32 |
+to their corresponding substrates and products. Each reaction vertex has \code{genes} attribute, |
|
33 |
+listing all genes associated with the reaction. As a general rule, reactions inherit all annotation |
|
34 |
+attributes of its catalyzig genes. |
|
44 | 35 |
|
45 |
-Signaling network have genes as vertices and edges |
|
46 |
-represent interactions, such as activiation / inhibition. |
|
47 |
-Genes participating in successive reactions are also |
|
48 |
-connected. Signaling parsing method processes <ECrel>, |
|
49 |
-<PPrel> and <PCrel> interactions from KGML files. |
|
36 |
+Signaling network have genes as vertices and edges represent interactions, such as activiation / inhibition. |
|
37 |
+Genes participating in successive reactions are also connected. Signaling parsing method processes <ECrel>, <PPrel> |
|
38 |
+and <PCrel> interactions from KGML files. |
|
50 | 39 |
|
51 |
-To generate a genome scale network, simply provide a list |
|
52 |
-of files to be parsed, or put all file in a directory, as |
|
53 |
-pass the directory path as \code{filename} |
|
40 |
+To generate a genome scale network, simply provide a list of files to be parsed, or put all |
|
41 |
+file in a directory, as pass the directory path as \code{filename} |
|
54 | 42 |
} |
55 | 43 |
\examples{ |
56 | 44 |
if(is.loaded("readkgmlfile")){ # This is false if libxml2 wasn't available at installation. |
... | ... |
@@ -69,7 +57,7 @@ if(is.loaded("readkgmlfile")){ # This is false if libxml2 wasn't available at in |
69 | 57 |
Ahmed Mohamed |
70 | 58 |
} |
71 | 59 |
\seealso{ |
72 |
-Other Database extraction methods: |
|
73 |
-\code{\link{SBML2igraph}}; \code{\link{biopax2igraph}} |
|
60 |
+Other Database extraction methods: \code{\link{SBML2igraph}}; |
|
61 |
+ \code{\link{biopax2igraph}} |
|
74 | 62 |
} |
75 | 63 |
|
... | ... |
@@ -1,3 +1,4 @@ |
1 |
+% Generated by roxygen2 (4.0.1): do not edit by hand |
|
1 | 2 |
\name{stdAttrNames} |
2 | 3 |
\alias{fetchAttribute} |
3 | 4 |
\alias{stdAttrNames} |
... | ... |
@@ -9,38 +10,28 @@ fetchAttribute(graph, organism = "Homo sapiens", target.attr, source.attr, |
9 | 10 |
bridge.web = NPMdefaults("bridge.web")) |
10 | 11 |
} |
11 | 12 |
\arguments{ |
12 |
- \item{graph}{An annotated igraph object.} |
|
13 |
+\item{graph}{An annotated igraph object.} |
|
13 | 14 |
|
14 |
- \item{return.value}{Specify whether to return the names |
|
15 |
- of matched standard annotations, or modify the graph |
|
16 |
- attribute names to match the standards.} |
|
15 |
+\item{return.value}{Specify whether to return the names of matched standard annotations, or modify the |
|
16 |
+graph attribute names to match the standards.} |
|
17 | 17 |
|
18 |
- \item{organism}{The latin name of the organism |
|
19 |
- (Case-sensitive).} |
|
18 |
+\item{organism}{The latin name of the organism (Case-sensitive).} |
|
20 | 19 |
|
21 |
- \item{target.attr}{The target annotation, given as MIRIAM |
|
22 |
- standard in the format \code{miriam.xxx}} |
|
20 |
+\item{target.attr}{The target annotation, given as MIRIAM standard in the format \code{miriam.xxx}} |
|
23 | 21 |
|
24 |
- \item{source.attr}{The source annotation attribute from |
|
25 |
- \code{graph}} |
|
22 |
+\item{source.attr}{The source annotation attribute from \code{graph}} |
|
26 | 23 |
|
27 |
- \item{bridge.web}{The base URL for Brigde Database |
|
28 |
- webservices.} |
|
24 |
+\item{bridge.web}{The base URL for Brigde Database webservices.} |
|
29 | 25 |
} |
30 | 26 |
\value{ |
31 |
-For \code{stdAttrNames}, \code{matches} gives the original |
|
32 |
-attribute names and their MIRIAM version. Since this is |
|
33 |
-done by simple text matching, mismatches may occur for |
|
34 |
-ambiguous annotations (such as GO, EC number). \code{graph} |
|
35 |
-returns the input graph with attribute names standardized. |
|
27 |
+For \code{stdAttrNames}, \code{matches} gives the original attribute names and their MIRIAM version. |
|
28 |
+Since this is done by simple text matching, mismatches may occur for ambiguous annotations (such as GO, EC number). |
|
29 |
+\code{graph} returns the input graph with attribute names standardized. |
|
36 | 30 |
|
37 |
-For \code{fetchAttribute}, the input \code{graph} with the |
|
38 |
-fetched attribute mapped to vertices. |
|
31 |
+For \code{fetchAttribute}, the input \code{graph} with the fetched attribute mapped to vertices. |
|
39 | 32 |
} |
40 | 33 |
\description{ |
41 |
-These functions deals with conforming with MIRIAM |
|
42 |
-annotation guidelines, conversion and mapping between |
|
43 |
-MIRIAM identifiers. |
|
34 |
+These functions deals with conforming with MIRIAM annotation guidelines, conversion and mapping between MIRIAM identifiers. |
|
44 | 35 |
} |
45 | 36 |
\examples{ |
46 | 37 |
data(ex_kgml_sig) # Ras and chemokine signaling pathways in human |
... | ... |
@@ -56,9 +47,8 @@ data(ex_kgml_sig) # Ras and chemokine signaling pathways in human |
56 | 47 |
Ahmed Mohamed |
57 | 48 |
} |
58 | 49 |
\seealso{ |
59 |
-Other Attribute handling methods: |
|
60 |
-\code{\link{getAttrNames}}, \code{\link{getAttrStatus}}, |
|
61 |
-\code{\link{getAttribute}}, \code{\link{rmAttribute}}, |
|
62 |
-\code{\link{setAttribute}} |
|
50 |
+Other Attribute handling methods: \code{\link{getAttrNames}}, |
|
51 |
+ \code{\link{getAttrStatus}}, \code{\link{getAttribute}}, |
|
52 |
+ \code{\link{rmAttribute}}, \code{\link{setAttribute}} |
|
63 | 53 |
} |
64 | 54 |
|
... | ... |
@@ -1,3 +1,4 @@ |
1 |
+% Generated by roxygen2 (4.0.1): do not edit by hand |
|
1 | 2 |
\name{NPMdefaults} |
2 | 3 |
\alias{NPMdefaults} |
3 | 4 |
\title{Default values for NetPathMiner} |
... | ... |
@@ -5,26 +6,22 @@ |
5 | 6 |
NPMdefaults(value) |
6 | 7 |
} |
7 | 8 |
\arguments{ |
8 |
- \item{value}{a character string indicating the variable |
|
9 |
- name.} |
|
9 |
+\item{value}{a character string indicating the variable name.} |
|
10 | 10 |
} |
11 | 11 |
\value{ |
12 | 12 |
The defuult value for the given variable. |
13 | 13 |
} |
14 | 14 |
\description{ |
15 |
-This function gets a NetPathMiner default value for a |
|
16 |
-variable. |
|
15 |
+This function gets a NetPathMiner default value for a variable. |
|
17 | 16 |
} |
18 | 17 |
\details{ |
19 |
-NetPathMiner defines the following defaults: \itemize{ |
|
20 |
-\item small.comp.ls Dataframe of ubiquitous metabolites. |
|
21 |
-Used by \code{\link{rmSmallCompounds}}. \item bridge |
|
22 |
-Dataframe of attributes supported by Brigde Database. Used |
|
23 |
-by \code{\link{fetchAttribute}}. \item bridge.organisms A |
|
24 |
-list of bridge supported organisms. Used by |
|
25 |
-\code{\link{fetchAttribute}}. \item bridge.web The base |
|
26 |
-URL for Brigde Database webservices. Used by |
|
27 |
-\code{\link{fetchAttribute}}. } |
|
18 |
+NetPathMiner defines the following defaults: |
|
19 |
+\itemize{ |
|
20 |
+ \item small.comp.ls Dataframe of ubiquitous metabolites. Used by \code{\link{rmSmallCompounds}}. |
|
21 |
+ \item bridge Dataframe of attributes supported by Brigde Database. Used by \code{\link{fetchAttribute}}. |
|
22 |
+ \item bridge.organisms A list of bridge supported organisms. Used by \code{\link{fetchAttribute}}. |
|
23 |
+ \item bridge.web The base URL for Brigde Database webservices. Used by \code{\link{fetchAttribute}}. |
|
24 |
+} |
|
28 | 25 |
} |
29 | 26 |
\examples{ |
30 | 27 |
# Get the default list of small compounds (uniquitous metabolites). |
... | ... |
@@ -1,3 +1,4 @@ |
1 |
+% Generated by roxygen2 (4.0.1): do not edit by hand |
|
1 | 2 |
\docType{package} |
2 | 3 |
\name{NetPathMiner-package} |
3 | 4 |
\alias{NPM} |
... | ... |
@@ -5,15 +6,12 @@ |
5 | 6 |
\alias{NetPathMiner-package} |
6 | 7 |
\title{General framework for network extraction, path mining.} |
7 | 8 |
\description{ |
8 |
-NetPathMiner implements a flexible module-based process |
|
9 |
-flow for network path mining and visualization, which can |
|
10 |
-be fully inte-grated with user-customized functions. |
|
11 |
-NetPathMiner supports construction of various types of |
|
12 |
-genome scale networks from KGML, SBML and BioPAX formats, |
|
13 |
-enabling its utility to most common pathway databases. |
|
14 |
-NetPathMiner also provides different visualization |
|
15 |
-techniques to facilitate the analysis of even thousands of |
|
16 |
-output paths. |
|
9 |
+NetPathMiner implements a flexible module-based process flow for network path mining and visualization, |
|
10 |
+which can be fully inte-grated with user-customized functions. |
|
11 |
+NetPathMiner supports construction of various types of genome scale networks from KGML, SBML and BioPAX |
|
12 |
+formats, enabling its utility to most common pathway databases. |
|
13 |
+NetPathMiner also provides different visualization techniques to facilitate the analysis of even |
|
14 |
+thousands of output paths. |
|
17 | 15 |
} |
18 | 16 |
\author{ |
19 | 17 |
Ahmed Mohamed \email{mohamed@kuicr.kyoto-u.ac.jp} |
... | ... |
@@ -1,3 +1,4 @@ |
1 |
+% Generated by roxygen2 (4.0.1): do not edit by hand |
|
1 | 2 |
\name{SBML2igraph} |
2 | 3 |
\alias{SBML2igraph} |
3 | 4 |
\title{Processes SBML files into igraph objects} |
... | ... |
@@ -6,83 +7,57 @@ SBML2igraph(filename, parse.as = c("metabolic", "signaling"), |
6 | 7 |
miriam.attr = "all", gene.attr, expand.complexes, verbose = TRUE) |
7 | 8 |
} |
8 | 9 |
\arguments{ |
9 |
- \item{filename}{A character vector containing the SBML |
|
10 |
- files to be processed. If a directory path is provided, |
|
11 |
- all *.xml and *.sbml files in it and its subdirectories |
|
12 |
- are included.} |
|
10 |
+\item{filename}{A character vector containing the SBML files to be processed. If a directory path |
|
11 |
+is provided, all *.xml and *.sbml files in it and its subdirectories are included.} |
|
13 | 12 |
|
14 |
- \item{parse.as}{Whether to process file into a metabolic |
|
15 |
- or a signaling network.} |
|
13 |
+\item{parse.as}{Whether to process file into a metabolic or a signaling network.} |
|
16 | 14 |
|
17 |
- \item{miriam.attr}{A list of annotation attributes to be |
|
18 |
- extracted. If \code{"all"}, then all attibutes written in |
|
19 |
- MIRIAM guidelines (see Details) are extracted (Default). |
|
20 |
- If \code{"none"}, then no attributes are extracted. |
|
21 |
- Otherwise, only attributes matching those specified are |
|
22 |
- extracted.} |
|
15 |
+\item{miriam.attr}{A list of annotation attributes to be extracted. If \code{"all"}, then all attibutes |
|
16 |
+written in MIRIAM guidelines (see Details) are extracted (Default). If \code{"none"}, then no attributes |
|
17 |
+are extracted. Otherwise, only attributes matching those specified are extracted.} |
|
23 | 18 |
|
24 |
- \item{gene.attr}{An attribute to distinguish |
|
25 |
- \code{species} representing genes from those representing |
|
26 |
- small molecules (see Details). Ignored if |
|
27 |
- \code{parse.as="metabolic"}.} |
|
19 |
+\item{gene.attr}{An attribute to distinguish \code{species} representing genes from those |
|
20 |
+representing small molecules (see Details). Ignored if \code{parse.as="metabolic"}.} |
|
28 | 21 |
|
29 |
- \item{expand.complexes}{Split protein complexes into |
|
30 |
- individual gene nodes. Ignored if |
|
31 |
- \code{parse.as="metabolic"}, or when \code{gene.attr} is |
|
32 |
- not provided.} |
|
22 |
+\item{expand.complexes}{Split protein complexes into individual gene nodes. Ignored if |
|
23 |
+\code{parse.as="metabolic"}, or when \code{gene.attr} is not provided.} |
|
33 | 24 |
|
34 |
- \item{verbose}{Whether to display the progress of the |
|
35 |
- function.} |
|
25 |
+\item{verbose}{Whether to display the progress of the function.} |
|
36 | 26 |
} |
37 | 27 |
\value{ |
38 |
-An igraph object, representing a metbolic or a signaling |
|
39 |
-network. |
|
28 |
+An igraph object, representing a metbolic or a signaling network. |
|
40 | 29 |
} |
41 | 30 |
\description{ |
42 |
-This function takes SBML files as input, and returns either |
|
43 |
-a metabolic or a signaling network as output. |
|
31 |
+This function takes SBML files as input, and returns either a metabolic or a signaling |
|
32 |
+network as output. |
|
44 | 33 |
} |
45 | 34 |
\details{ |
46 |
-Users can specify whether files are processes as metabolic |
|
47 |
-or signaling networks. |
|
35 |
+Users can specify whether files are processes as metabolic or signaling networks. |
|
48 | 36 |
|
49 |
-Metabolic networks are given as bipartite graphs, where |
|
50 |
-metabolites and reactions represent vertex types. This is |
|
51 |
-constructed from \code{ListOfReactions} in SBML file, |
|
52 |
-connecting them to their corresponding substrates and |
|
53 |
-products (\code{ListOfSpecies}). Each reaction vertex has |
|
54 |
-\code{genes} attribute, listing all \code{modifiers} of |
|
55 |
-this reaction. As a general rule, reactions inherit all |
|
56 |
-annotation attributes of its catalyzig genes. |
|
37 |
+Metabolic networks are given as bipartite graphs, where metabolites and reactions represent |
|
38 |
+vertex types. This is constructed from \code{ListOfReactions} in SBML file, connecting them |
|
39 |
+to their corresponding substrates and products (\code{ListOfSpecies}). Each reaction vertex has \code{genes} attribute, |
|
40 |
+listing all \code{modifiers} of this reaction. As a general rule, reactions inherit all annotation |
|
41 |
+attributes of its catalyzig genes. |
|
57 | 42 |
|
58 |
-Signaling network have genes as vertices and edges |
|
59 |
-represent interactions. Since SBML format may represent |
|
60 |
-singling events as \code{reaction}, all species are assumed |
|
61 |
-to be genes (rather than small molecules). For a simple |
|
62 |
-path \code{S0 -> R1 -> S1}, in signaling network, the path |
|
63 |
-will be \code{S0 -> M(R1) -> S1} where \code{M(R1)} is R1 |
|
64 |
-modifier(s). To ditiguish gene species from small |
|
65 |
-molecules, user can provide \code{gene.attr} (for example: |
|
66 |
-\code{miriam.uniprot} or \code{miriam.ncbigene}) where only |
|
67 |
-annotated species are considered genes. |
|
43 |
+Signaling network have genes as vertices and edges represent interactions. Since SBML format may |
|
44 |
+represent singling events as \code{reaction}, all species are assumed to be genes (rather than small |
|
45 |
+molecules). For a simple path \code{S0 -> R1 -> S1}, in signaling network, the path will be |
|
46 |
+\code{S0 -> M(R1) -> S1} where \code{M(R1)} is R1 modifier(s). To ditiguish gene species from small |
|
47 |
+molecules, user can provide \code{gene.attr} (for example: \code{miriam.uniprot} or \code{miriam.ncbigene}) |
|
48 |
+where only annotated species are considered genes. |
|
68 | 49 |
|
69 |
-All annotation attributes written according to MIRIAM |
|
70 |
-guidlines (either \code{urn:miriam:xxx:xxx} or |
|
71 |
-\code{http://identifiers.org/xxx/xxx}) are etxracted by |
|
72 |
-default. Non-conforming attributes can be extracted by |
|
73 |
-specifying \code{miriam.attr}. |
|
50 |
+All annotation attributes written according to MIRIAM guidlines (either \code{urn:miriam:xxx:xxx} or |
|
51 |
+\code{http://identifiers.org/xxx/xxx}) are etxracted by default. Non-conforming attributes can be extracted |
|
52 |
+by specifying \code{miriam.attr}. |
|
74 | 53 |
|
75 |
-To generate a genome scale network, simply provide a list |
|
76 |
-of files to be parsed, or put all file in a directory, as |
|
77 |
-pass the directory path as \code{filename} |
|
54 |
+To generate a genome scale network, simply provide a list of files to be parsed, or put all |
|
55 |
+file in a directory, as pass the directory path as \code{filename} |
|
78 | 56 |
|
79 |
-Note: This function requires libSBML installed (Please see |
|
80 |
-the installation instructions in the Vignette). Some SBML |
|
81 |
-level-3 files may requires additional libraries also (An |
|
82 |
-infomative error will be displayed when parsing such |
|
83 |
-files). Please visit |
|
84 |
-\url{http://sbml.org/Documents/Specifications/SBML_Level_3/Packages} |
|
85 |
-for more information. |
|
57 |
+Note: This function requires libSBML installed (Please see the installation instructions in the Vignette). |
|
58 |
+Some SBML level-3 files may requires additional libraries also (An infomative error will be displayed when |
|
59 |
+parsing such files). Please visit \url{http://sbml.org/Documents/Specifications/SBML_Level_3/Packages} for |
|
60 |
+more information. |
|
86 | 61 |
} |
87 | 62 |
\examples{ |
88 | 63 |
if(is.loaded("readsbmlfile")){ # This is false if libSBML wasn't available at installation. |
... | ... |
@@ -103,7 +78,7 @@ if(is.loaded("readsbmlfile")){ # This is false if libSBML wasn't available at in |
103 | 78 |
Ahmed Mohamed |
104 | 79 |
} |
105 | 80 |
\seealso{ |
106 |
-Other Database extraction methods: |
|
107 |
-\code{\link{KGML2igraph}}; \code{\link{biopax2igraph}} |
|
81 |
+Other Database extraction methods: \code{\link{KGML2igraph}}; |
|
82 |
+ \code{\link{biopax2igraph}} |
|
108 | 83 |
} |
109 | 84 |
|
... | ... |
@@ -1,3 +1,4 @@ |
1 |
+% Generated by roxygen2 (4.0.1): do not edit by hand |
|
1 | 2 |
\name{assignEdgeWeights} |
2 | 3 |
\alias{assignEdgeWeights} |
3 | 4 |
\title{Assigning weights to network edges} |
... | ... |
@@ -7,68 +8,42 @@ assignEdgeWeights(microarray, graph, use.attr, y, weight.method = "cor", |
7 | 8 |
same.gene.penalty = "median", bootstrap = 100, verbose = TRUE) |
8 | 9 |
} |
9 | 10 |
\arguments{ |
10 |
- \item{microarray}{Microarray should be a Dataframe or a |
|
11 |
- matrix, with genes as rownames, and samples as columns.} |
|
11 |
+\item{microarray}{Microarray should be a Dataframe or a matrix, with genes as rownames, and samples as columns.} |
|
12 | 12 |
|
13 |
- \item{graph}{An annotated igraph object.} |
|
13 |
+\item{graph}{An annotated igraph object.} |
|
14 | 14 |
|
15 |
- \item{use.attr}{An attribute name to map |
|
16 |
- \code{microarray} rows (genes) to graph vertices. The |
|
17 |
- attribute must be annotated in \code{graph}, and the |
|
18 |
- values correspond to \code{rownames} of |
|
19 |
- \code{microarray}. You can check the coverage and if |
|
20 |
- there are complex vertices using |
|
21 |
- \code{\link{getAttrStatus}}. You can eliminate complexes |
|
22 |
- using \code{\link{expandComplexes}}.} |
|
15 |
+\item{use.attr}{An attribute name to map \code{microarray} rows (genes) to graph vertices. The attribute must |
|
16 |
+be annotated in \code{graph}, and the values correspond to \code{rownames} of \code{microarray}. You can check the coverage and |
|
17 |
+if there are complex vertices using \code{\link{getAttrStatus}}. You can eliminate complexes using \code{\link{expandComplexes}}.} |
|
23 | 18 |
|
24 |
- \item{y}{Sample labels, given as a factor or a character |
|
25 |
- vector. This must be the same size as the columns of |
|
26 |
- \code{microarray}} |
|
19 |
+\item{y}{Sample labels, given as a factor or a character vector. This must be the same size as the columns of \code{microarray}} |
|
27 | 20 |
|
28 |
- \item{weight.method}{A function, or a string indicating |
|
29 |
- the name of the function to be used to compute the edge |
|
30 |
- weights. The function is provided with 2 numerical |
|
31 |
- verctors (2 rows from \code{microarray}), and it should |
|
32 |
- return a single numerical value (or \code{NA}). The |
|
33 |
- default computes Pearson's correlation.} |
|
21 |
+\item{weight.method}{A function, or a string indicating the name of the function to be used to compute the edge weights. |
|
22 |
+The function is provided with 2 numerical verctors (2 rows from \code{microarray}), and it should return a single numerical |
|
23 |
+value (or \code{NA}). The default computes Pearson's correlation.} |
|
34 | 24 |
|
35 |
- \item{complex.method}{A function, or a string indicating |
|
36 |
- the name of the function to be used in weighting edges |
|
37 |
- connecting complexes. If a vertex has >1 attribute value, |
|
38 |
- all possible pairwise weights are first computed, and |
|
39 |
- given to \code{complex.method}. The default function is |
|
40 |
- \code{\link[base]{max}}.} |
|
25 |
+\item{complex.method}{A function, or a string indicating the name of the function to be used in weighting edges connecting complexes. |
|
26 |
+If a vertex has >1 attribute value, all possible pairwise weights are first computed, and given to \code{complex.method}. The default |
|
27 |
+function is \code{\link[base]{max}}.} |
|
41 | 28 |
|
42 |
- \item{missing.method}{A function, or a string indicating |
|
43 |
- the name of the function to be used in weighting edges |
|
44 |
- when one of the vertices lack expression data. The |
|
45 |
- function is passed all edge weights on the graph. Default |
|
46 |
- is \code{\link[stats]{median}}.} |
|
29 |
+\item{missing.method}{A function, or a string indicating the name of the function to be used in weighting edges when one of the vertices |
|
30 |
+lack expression data. The function is passed all edge weights on the graph. Default is \code{\link[stats]{median}}.} |
|
47 | 31 |
|
48 |
- \item{same.gene.penalty}{A numerical value to be assigned |
|
49 |
- when 2 adjacent vertices have the same attribute value, |
|
50 |
- since correlation and similarity measure will give |
|
51 |
- perfect scores. Alternatively, \code{same.gene.penalty} |
|
52 |
- can be a function, computing the penalty from all edge |
|
53 |
- weights on the graph (excluding same-gene and missing |
|
54 |
- values). The default is to take the |
|
55 |
- \code{\link[stats]{median}}} |
|
32 |
+\item{same.gene.penalty}{A numerical value to be assigned when 2 adjacent vertices have the same attribute value, since correlation and |
|
33 |
+similarity measure will give perfect scores. Alternatively, \code{same.gene.penalty} can be a function, computing the penalty from all |
|
34 |
+edge weights on the graph (excluding same-gene and missing values). The default is to take the \code{\link[stats]{median}}} |
|
56 | 35 |
|
57 |
- \item{bootstrap}{An integer \code{n}, where the |
|
58 |
- \code{weight.method} is perfomed on \code{n} permutations |
|
59 |
- of the gene profiles, and taking the median value. Set it |
|
60 |
- to \code{NA} to disable bootstrapping.} |
|
36 |
+\item{bootstrap}{An integer \code{n}, where the \code{weight.method} is perfomed on \code{n} permutations of the gene profiles, and taking |
|
37 |
+the median value. Set it to \code{NA} to disable bootstrapping.} |
|
61 | 38 |
|
62 |
- \item{verbose}{Print the progress of the function.} |
|
39 |
+\item{verbose}{Print the progress of the function.} |
|
63 | 40 |
} |
64 | 41 |
\value{ |
65 |
-The input graph with \code{edge.weight} as an edge |
|
66 |
-attribute. The attribute can be a list of weights if |
|
67 |
-\code{y} labels were provided. |
|
42 |
+The input graph with \code{edge.weight} as an edge attribute. The attribute can be a list of weights if \code{y} labels |
|
43 |
+were provided. |
|
68 | 44 |
} |
69 | 45 |
\description{ |
70 |
-This function computes edge weights based on a gene |
|
71 |
-expression profile. |
|
46 |
+This function computes edge weights based on a gene expression profile. |
|
72 | 47 |
} |
73 | 48 |
\examples{ |
74 | 49 |
## Conver a metabolic network to a reaction network. |
... | ... |
@@ -1,3 +1,4 @@ |
1 |
+% Generated by roxygen2 (4.0.1): do not edit by hand |
|
1 | 2 |
\name{biopax2igraph} |
2 | 3 |
\alias{biopax2igraph} |
3 | 4 |
\title{Processes BioPAX objects into igraph objects} |
... | ... |
@@ -6,58 +7,42 @@ biopax2igraph(biopax, parse.as = c("metabolic", "signaling"), |
6 | 7 |
expand.complexes = FALSE, inc.sm.molecules = FALSE, verbose = TRUE) |
7 | 8 |
} |
8 | 9 |
\arguments{ |
9 |
- \item{biopax}{BioPAX object generated by |
|
10 |
- \code{\link[rBiopaxParser]{readBiopax}}.} |
|
10 |
+\item{biopax}{BioPAX object generated by \code{\link[rBiopaxParser]{readBiopax}}.} |
|
11 | 11 |
|
12 |
- \item{parse.as}{Whether to process file into a metabolic |
|
13 |
- or a signaling network.} |
|
12 |
+\item{parse.as}{Whether to process file into a metabolic or a signaling network.} |
|
14 | 13 |
|
15 |
- \item{expand.complexes}{Split protein complexes into |
|
16 |
- individual gene nodes. Ignored if |
|
17 |
- \code{parse.as="metabolic"}.} |
|
14 |
+\item{expand.complexes}{Split protein complexes into individual gene nodes. Ignored if |
|
15 |
+\code{parse.as="metabolic"}.} |
|
18 | 16 |
|
19 |
- \item{inc.sm.molecules}{Include small molecules that are |
|
20 |
- participating in signaling events. Ignored if |
|
21 |
- \code{parse.as="metabolic"}.} |
|
17 |
+\item{inc.sm.molecules}{Include small molecules that are participating in signaling events. Ignored if |
|
18 |
+\code{parse.as="metabolic"}.} |
|
22 | 19 |
|
23 |
- \item{verbose}{Whether to display the progress of the |
|
24 |
- function.} |
|
20 |
+\item{verbose}{Whether to display the progress of the function.} |
|
25 | 21 |
} |
26 | 22 |
\value{ |
27 |
-An igraph object, representing a metbolic or a signaling |
|
28 |
-network. |
|
23 |
+An igraph object, representing a metbolic or a signaling network. |
|
29 | 24 |
} |
30 | 25 |
\description{ |
31 |
-This function takes BioPAX objects (level 2 or 3) as input, |
|
32 |
-and returns either a metabolic or a signaling network as |
|
33 |
-output. |
|
26 |
+This function takes BioPAX objects (level 2 or 3) as input, and returns either a metabolic or a signaling |
|
27 |
+network as output. |
|
34 | 28 |
} |
35 | 29 |
\details{ |
36 | 30 |
This function requires \code{rBiopaxParser} installed. |
37 | 31 |
|
38 |
-Users can specify whether files are processes as metabolic |
|
39 |
-or signaling networks. |
|
32 |
+Users can specify whether files are processes as metabolic or signaling networks. |
|
40 | 33 |
|
41 |
-Metabolic networks are given as bipartite graphs, where |
|
42 |
-metabolites and reactions represent vertex types. Reactions |
|
43 |
-are constructed from \code{Conversion} classes, connecting |
|
44 |
-them to their corresponding \code{Left}s and \code{Right}s. |
|
45 |
-Each reaction vertex has \code{genes} attribute, listing |
|
46 |
-all \code{Catalysis} relationships of this reaction. As a |
|
47 |
-general rule, reactions inherit all annotation attributes |
|
48 |
-of its catalyzig genes. |
|
34 |
+Metabolic networks are given as bipartite graphs, where metabolites and reactions represent |
|
35 |
+vertex types. Reactions are constructed from \code{Conversion} classes, connecting them |
|
36 |
+to their corresponding \code{Left}s and \code{Right}s. Each reaction vertex has \code{genes} attribute, |
|
37 |
+listing all \code{Catalysis} relationships of this reaction. As a general rule, reactions inherit all annotation |
|
38 |
+attributes of its catalyzig genes. |
|
49 | 39 |
|
50 |
-Signaling network have genes as vertices and edges |
|
51 |
-represent interactions, such as activiation / inhibition. |
|
52 |
-Genes participating in successive reactions are also |
|
53 |
-connected. Signaling interactions are constructed from |
|
54 |
-\code{Control} classes, where edges are drawn from |
|
55 |
-\code{controller} to \code{controlled}. |
|
40 |
+Signaling network have genes as vertices and edges represent interactions, such as activiation / inhibition. |
|
41 |
+Genes participating in successive reactions are also connected. Signaling interactions are constructed from |
|
42 |
+\code{Control} classes, where edges are drawn from \code{controller} to \code{controlled}. |
|
56 | 43 |
|
57 |
-All annotation attributes are exracted from \code{XRefs} |
|
58 |
-associated with the vertices, and are stored according to |
|
59 |
-MIRIAM guidelines (\code{miraim.db}, where db is the |
|
60 |
-database name). |
|
44 |
+All annotation attributes are exracted from \code{XRefs} associated with the vertices, and are stored according to |
|
45 |
+MIRIAM guidelines (\code{miraim.db}, where db is the database name). |
|
61 | 46 |
} |
62 | 47 |
\examples{ |
63 | 48 |
if(require(rBiopaxParser)){ |
... | ... |
@@ -74,7 +59,7 @@ if(require(rBiopaxParser)){ |
74 | 59 |
Ahmed Mohamed |
75 | 60 |
} |
76 | 61 |
\seealso{ |
77 |
-Other Database extraction methods: |
|
78 |
-\code{\link{KGML2igraph}}; \code{\link{SBML2igraph}} |
|
62 |
+Other Database extraction methods: \code{\link{KGML2igraph}}; |
|
63 |
+ \code{\link{SBML2igraph}} |
|
79 | 64 |
} |
80 | 65 |
|
... | ... |
@@ -1,3 +1,4 @@ |
1 |
+% Generated by roxygen2 (4.0.1): do not edit by hand |
|
1 | 2 |
\name{colorVertexByAttr} |
2 | 3 |
\alias{colorVertexByAttr} |
3 | 4 |
\title{Computes colors for vertices according to their attributes.} |
... | ... |
@@ -5,22 +6,18 @@ |
5 | 6 |
colorVertexByAttr(graph, attr.name, col.palette = palette()) |
6 | 7 |
} |
7 | 8 |
\arguments{ |
8 |
- \item{graph}{An annotated igraph object.} |
|
9 |
+\item{graph}{An annotated igraph object.} |
|
9 | 10 |
|
10 |
- \item{attr.name}{The attribute name (ex: "pathway") by |
|
11 |
- which vertices will be colored. Complex attributes, where |
|
12 |
- a vertex belongs to more than one group, are supported.} |
|
11 |
+\item{attr.name}{The attribute name (ex: "pathway") by which vertices will be colored. |
|
12 |
+Complex attributes, where a vertex belongs to more than one group, are supported.} |
|
13 | 13 |
|
14 |
- \item{col.palette}{A color palette, or a palette |
|
15 |
- generating function (ex: |
|
16 |
- \preformatted{col.palette=rainbow}).} |
|
14 |
+\item{col.palette}{A color palette, or a palette generating function (ex: \preformatted{col.palette=rainbow}).} |
|
17 | 15 |
} |
18 | 16 |
\value{ |
19 | 17 |
A list of colors (in HEX format) for vertices. |
20 | 18 |
} |
21 | 19 |
\description{ |
22 |
-This function returns a list of colors for vertices, |
|
23 |
-assigned similar colors if they share a common attribute |
|
20 |
+This function returns a list of colors for vertices, assigned similar colors if they share a common attribute |
|
24 | 21 |
(ex: in the same pathway, etc). |
25 | 22 |
} |
26 | 23 |
\examples{ |
... | ... |
@@ -33,11 +30,13 @@ Ahmed Mohamed |
33 | 30 |
} |
34 | 31 |
\seealso{ |
35 | 32 |
Other Plotting methods: \code{\link{layoutVertexByAttr}}; |
36 |
-\code{\link{plotAllNetworks}}; |
|
37 |
-\code{\link{plotClassifierROC}}; |
|
38 |
-\code{\link{plotClusterMatrix}}, |
|
39 |
-\code{\link{plotClusterProbs}}, \code{\link{plotClusters}}; |
|
40 |
-\code{\link{plotCytoscape}}; \code{\link{plotNetwork}}; |
|
41 |
-\code{\link{plotPathClassifier}}; \code{\link{plotPaths}} |
|
33 |
+ \code{\link{plotAllNetworks}}; |
|
34 |
+ \code{\link{plotClassifierROC}}; |
|
35 |
+ \code{\link{plotClusterMatrix}}, |
|
36 |
+ \code{\link{plotClusterProbs}}, |
|
37 |
+ \code{\link{plotClusters}}; \code{\link{plotCytoscape}}, |
|
38 |
+ \code{\link{plotCytoscapeGML}}; |
|
39 |
+ \code{\link{plotNetwork}}; |
|
40 |
+ \code{\link{plotPathClassifier}}; \code{\link{plotPaths}} |
|
42 | 41 |
} |
43 | 42 |
|
... | ... |
@@ -1,10 +1,10 @@ |
1 |
+% Generated by roxygen2 (4.0.1): do not edit by hand |
|
1 | 2 |
\docType{data} |
2 | 3 |
\name{ex_biopax} |
3 | 4 |
\alias{ex_biopax} |
4 | 5 |
\title{Biopax example data} |
5 | 6 |
\description{ |
6 |
-A dataset containing Porphyrin metabolism pathway in Biopax |
|
7 |
-Level 3 and parsed with |
|
7 |
+A dataset containing Porphyrin metabolism pathway in Biopax Level 3 and parsed with |
|
8 | 8 |
\code{\link[rBiopaxParser]{readBiopax}}. |
9 | 9 |
} |
10 | 10 |
\examples{ |
... | ... |
@@ -1,10 +1,11 @@ |
1 |
+% Generated by roxygen2 (4.0.1): do not edit by hand |
|
1 | 2 |
\docType{data} |
2 | 3 |
\name{ex_kgml_sig} |
3 | 4 |
\alias{ex_kgml_sig} |
4 | 5 |
\title{Singaling network from KGML example} |
5 | 6 |
\description{ |
6 |
-An exmaple igraph object representing Ras and chemokine |
|
7 |
-signaling pathways in human extracted from KGML files. |
|
7 |
+An exmaple igraph object representing Ras and chemokine signaling pathways in human |
|
8 |
+extracted from KGML files. |
|
8 | 9 |
} |
9 | 10 |
\examples{ |
10 | 11 |
data(ex_kgml_sig) |
... | ... |
@@ -1,10 +1,10 @@ |
1 |
+% Generated by roxygen2 (4.0.1): do not edit by hand |
|
1 | 2 |
\docType{data} |
2 | 3 |
\name{ex_microarray} |
3 | 4 |
\alias{ex_microarray} |
4 | 5 |
\title{An microarray data example.} |
5 | 6 |
\description{ |
6 |
-An microarray data example. This is part of the ALL |
|
7 |
-dataset, for demonestration purposes. |
|
7 |
+An microarray data example. This is part of the ALL dataset, for demonestration purposes. |
|
8 | 8 |
} |
9 | 9 |
\examples{ |
10 | 10 |
data(ex_microarray) |
... | ... |
@@ -1,11 +1,11 @@ |
1 |
+% Generated by roxygen2 (4.0.1): do not edit by hand |
|
1 | 2 |
\docType{data} |
2 | 3 |
\name{ex_sbml} |
3 | 4 |
\alias{ex_sbml} |
4 | 5 |
\title{Metabolic network from SBML example} |
5 | 6 |
\description{ |
6 |
-An example igraph object representing bipartite metabolic |
|
7 |
-network of Carbohydrate metabolism extracted from SBML file |
|
8 |
-from Reactome database. |
|
7 |
+An example igraph object representing bipartite metabolic network of Carbohydrate |
|
8 |
+metabolism extracted from SBML file from Reactome database. |
|
9 | 9 |
} |
10 | 10 |
\examples{ |
11 | 11 |
data(ex_sbml) |
... | ... |
@@ -1,3 +1,4 @@ |
1 |
+% Generated by roxygen2 (4.0.1): do not edit by hand |
|
1 | 2 |
\name{extractPathNetwork} |
2 | 3 |
\alias{extractPathNetwork} |
3 | 4 |
\title{Creates a subnetwork from a ranked path list} |
... | ... |
@@ -5,19 +6,16 @@ |
5 | 6 |
extractPathNetwork(paths, graph) |
6 | 7 |
} |
7 | 8 |
\arguments{ |
8 |
- \item{paths}{The paths extracted by |
|
9 |
- \code{\link{pathRanker}}.} |
|
9 |
+\item{paths}{The paths extracted by \code{\link{pathRanker}}.} |
|
10 | 10 |
|
11 |
- \item{graph}{A annotated igraph object.} |
|
11 |
+\item{graph}{A annotated igraph object.} |
|
12 | 12 |
} |
13 | 13 |
\value{ |
14 |
-A subnetwork from all paths provided. If paths are computed |
|
15 |
-for several labels (sample categories), a subnetwork is |
|
16 |
-returned for each label. |
|
14 |
+A subnetwork from all paths provided. If paths are computed for several |
|
15 |
+labels (sample categories), a subnetwork is returned for each label. |
|
17 | 16 |
} |
18 | 17 |
\description{ |
19 |
-Creates a subnetwork from a ranked path list generated by |
|
20 |
-\code{\link{pathRanker}}. |
|
18 |
+Creates a subnetwork from a ranked path list generated by \code{\link{pathRanker}}. |
|
21 | 19 |
} |
22 | 20 |
\examples{ |
23 | 21 |
## Prepare a weighted reaction network. |
... | ... |
@@ -47,6 +45,6 @@ Ahmed Mohamed |
47 | 45 |
} |
48 | 46 |
\seealso{ |
49 | 47 |
Other Path ranking methods: \code{\link{getPathsAsEIDs}}; |
50 |
-\code{\link{pathRanker}}; \code{\link{samplePaths}} |
|
48 |
+ \code{\link{pathRanker}}; \code{\link{samplePaths}} |
|
51 | 49 |
} |
52 | 50 |
|
... | ... |
@@ -1,3 +1,4 @@ |
1 |
+% Generated by roxygen2 (4.0.1): do not edit by hand |
|
1 | 2 |
\name{getAttrStatus} |
2 | 3 |
\alias{getAttrNames} |
3 | 4 |
\alias{getAttrStatus} |
... | ... |
@@ -17,46 +18,34 @@ setAttribute(graph, attr.name, attr.value) |
17 | 18 |
rmAttribute(graph, attr.name) |
18 | 19 |
} |
19 | 20 |
\arguments{ |
20 |
- \item{graph}{An annotated igraph object.} |
|
21 |
+\item{graph}{An annotated igraph object.} |
|
21 | 22 |
|
22 |
- \item{pattern}{A \code{\link{regex}} experssion |
|
23 |
- representing attribute name pattern.} |
|
23 |
+\item{pattern}{A \code{\link{regex}} experssion representing attribute name pattern.} |
|
24 | 24 |
|
25 |
- \item{attr.name}{The attribute name} |
|
25 |
+\item{attr.name}{The attribute name} |
|
26 | 26 |
|
27 |
- \item{attr.value}{A list of attribute values. This must |
|
28 |
- be the same size as the number of vertices.} |
|
27 |
+\item{attr.value}{A list of attribute values. This must be the same size as the number of vertices.} |
|
29 | 28 |
} |
30 | 29 |
\value{ |
31 |
-For \code{getAttrStatus}, a dataframe summarizing the |
|
32 |
-number of vertices with no (\code{missing}), one |
|
33 |
-(\code{single}) or more than one (\code{complex}) attribute |
|
34 |
-value. The coverage% is also reported to each attribute. |
|
30 |
+For \code{getAttrStatus}, a dataframe summarizing the number of vertices with no (\code{missing}), one (\code{single}) |
|
31 |
+or more than one (\code{complex}) attribute value. The coverage% is also reported to each attribute. |
|
35 | 32 |
|
36 |
-For \code{getAttrNames}, a character vector of attribute |
|
37 |
-names matching the pattern. |
|
33 |
+For \code{getAttrNames}, a character vector of attribute names matching the pattern. |
|
38 | 34 |
|
39 |
-For \code{getAttribute}, a list of vertex annotation values |
|
40 |
-for the query attribute. |
|
35 |
+For \code{getAttribute}, a list of vertex annotation values for the query attribute. |
|
41 | 36 |
|
42 |
-For \code{setAttribute}, a graph with the new attribute |
|
43 |
-set. |
|
37 |
+For \code{setAttribute}, a graph with the new attribute set. |
|
44 | 38 |
|
45 |
-For \code{rmAttrNames}, a new igraph object with the |
|
46 |
-attibute removed. |
|
39 |
+For \code{rmAttrNames}, a new igraph object with the attibute removed. |
|
47 | 40 |
} |
48 | 41 |
\description{ |
49 |
-These functions report the annotation status of the |
|
50 |
-vertices of a given network, modify or remove certain |
|
51 |
-annotations. |
|
42 |
+These functions report the annotation status of the vertices of a given network, modify |
|
43 |
+or remove certain annotations. |
|
52 | 44 |
} |
53 | 45 |
\details{ |
54 |
-NetPathMiner stores all its vertex annotation attributes in |
|
55 |
-a list, and stores them collectively as a single |
|
56 |
-\code{attr}. This is not to interfer with |
|
57 |
-\code{\link[igraph]{attributes}} from \code{igraph} |
|
58 |
-package. All functions here target NetPathMiner annotations |
|
59 |
-only. |
|
46 |
+NetPathMiner stores all its vertex annotation attributes in a list, and stores them collectively as |
|
47 |
+a single \code{attr}. This is not to interfer with \code{\link[igraph]{attributes}} from \code{igraph} package. |
|
48 |
+All functions here target NetPathMiner annotations only. |
|
60 | 49 |
} |
61 | 50 |
\examples{ |
62 | 51 |
data(ex_kgml_sig) # Ras and chemokine signaling pathways in human |
... | ... |
@@ -77,7 +66,7 @@ data(ex_kgml_sig) # Ras and chemokine signaling pathways in human |
77 | 66 |
Ahmed Mohamed |
78 | 67 |
} |
79 | 68 |
\seealso{ |
80 |
-Other Attribute handling methods: |
|
81 |
-\code{\link{fetchAttribute}}, \code{\link{stdAttrNames}} |
|
69 |
+Other Attribute handling methods: \code{\link{fetchAttribute}}, |
|
70 |
+ \code{\link{stdAttrNames}} |
|
82 | 71 |
} |
83 | 72 |
|
... | ... |
@@ -1,26 +1,47 @@ |
1 |
+% Generated by roxygen2 (4.0.1): do not edit by hand |
|
1 | 2 |
\name{getGeneSetNetworks} |
2 | 3 |
\alias{getGeneSetNetworks} |
3 | 4 |
\title{Generate geneset networks from an annotated network.} |
4 | 5 |
\usage{ |
5 |
-getGeneSetNetworks(graph, use.attr = "pathway") |
|
6 |
+getGeneSetNetworks(graph, use.attr = "pathway", format = c("list", |
|
7 |
+ "pathway-class")) |
|
6 | 8 |
} |
7 | 9 |
\arguments{ |
8 |
- \item{graph}{An annotated igraph object..} |
|
10 |
+\item{graph}{An annotated igraph object..} |
|
9 | 11 |
|
10 |
- \item{use.attr}{The attribute by which vertices are |
|
11 |
- grouped (tepically pathway, or GO)} |
|
12 |
+\item{use.attr}{The attribute by which vertices are grouped (tepically pathway, or GO)} |
|
13 |
+ |
|
14 |
+\item{format}{The output format. If "list" is specified, a list of subgraphs are returned (default). |
|
15 |
+If "pathway-class" is specified, a list of pathway-class objects are returned. \link[graphite]{pathway-class} |
|
16 |
+is used by graphite package to run several methods of topology-based enrichment analyses.} |
|
12 | 17 |
} |
13 | 18 |
\value{ |
14 |
-A list of geneset networks. |
|
19 |
+A list of geneset networks as igraph or \link[graphite]{pathway-class} objects. |
|
15 | 20 |
} |
16 | 21 |
\description{ |
17 |
-This function generates geneset networks based on a given |
|
18 |
-netowrk, by grouping vertices sharing common attributes (in |
|
19 |
-the same pathway or compartment). |
|
22 |
+This function generates geneset networks based on a given netowrk, by grouping vertices sharing |
|
23 |
+common attributes (in the same pathway or compartment). |
|
20 | 24 |
} |
21 | 25 |
\examples{ |
22 | 26 |
data(ex_kgml_sig) # Ras and chemokine signaling pathways in human |
23 | 27 |
genesetnets <- getGeneSetNetworks(ex_kgml_sig, use.attr="pathway") |
28 |
+ |
|
29 |
+ # Integration with graphite package |
|
30 |
+\donttest{ |
|
31 |
+ if(require(graphite) & require(clipper) & require(ALL)){ |
|
32 |
+ genesetnets <- getGeneSetNetworks(ex_kgml_sig, |
|
33 |
+ use.attr="pathway", format="pathway-class") |
|
34 |
+ path <- convertIdentifiers(genesetnets$`Chemokine signaling pathway`, |
|
35 |
+ "entrez") |
|
36 |
+ genes <- nodes(path) |
|
37 |
+ data(ALL) |
|
38 |
+ all <- as.matrix(exprs(ALL[1:length(genes),1:20])) |
|
39 |
+ classes <- c(rep(1,10), rep(2,10)) |
|
40 |
+ rownames(all) <- genes |
|
41 |
+ |
|
42 |
+ runClipper(path, all, classes, "mean", pathThr=0.1) |
|
43 |
+ } |
|
44 |
+} |
|
24 | 45 |
} |
25 | 46 |
\author{ |
26 | 47 |
Ahmed Mohamed |
... | ... |
@@ -1,31 +1,42 @@ |
1 |
+% Generated by roxygen2 (4.0.1): do not edit by hand |
|
1 | 2 |
\name{getGeneSets} |
2 | 3 |
\alias{getGeneSets} |
3 | 4 |
\title{Generate genesets from an annotated network.} |
4 | 5 |
\usage{ |
5 |
-getGeneSets(graph, use.attr = "pathway", gene.attr = "genes") |
|
6 |
+getGeneSets(graph, use.attr = "pathway", gene.attr = "genes", gmt.file) |
|
6 | 7 |
} |
7 | 8 |
\arguments{ |
8 |
- \item{graph}{An annotated igraph object..} |
|
9 |
+\item{graph}{An annotated igraph object..} |
|
9 | 10 |
|
10 |
- \item{use.attr}{The attribute by which vertices are |
|
11 |
- grouped (tepically pathway, or GO)} |
|
11 |
+\item{use.attr}{The attribute by which vertices are grouped (tepically pathway, or GO)} |
|
12 | 12 |
|
13 |
- \item{gene.attr}{The attribute listing genes annotated |
|
14 |
- with each vertex (ex: miriam.ncbigene, miriam.uniprot, |
|
15 |
- ...)} |
|
13 |
+\item{gene.attr}{The attribute listing genes annotated with each vertex (ex: miriam.ncbigene, miriam.uniprot, ...)} |
|
14 |
+ |
|
15 |
+\item{gmt.file}{Optinal. If provided, Results are exported to a GMT file. GMT files are readily used |
|
16 |
+by most gene set analysis packages.} |
|
16 | 17 |
} |
17 | 18 |
\value{ |
18 |
-A list of genesets. |
|
19 |
+A list of genesets or written to gmt file if provided. |
|
19 | 20 |
} |
20 | 21 |
\description{ |
21 |