Browse code

Switch to Rmd vignette

Ahmed Mohamed authored on 02/03/2019 09:00:17
Showing 5 changed files

... ...
@@ -22,7 +22,9 @@ Depends:
22 22
 Suggests:
23 23
     rBiopaxParser (>= 2.1),
24 24
     RCurl,
25
-    graph
25
+    graph,
26
+    knitr, rmarkdown, BiocStyle
27
+VignetteBuilder: knitr
26 28
 License: GPL (>= 2)
27 29
 URL: https://github.com/ahmohamed/NetPathMiner
28 30
 NeedsCompilation: yes
29 31
new file mode 100644
... ...
@@ -0,0 +1,485 @@
1
+---
2
+title: Annotating Genomic Variants
3
+author:
4
+–name: Ahmed Mohamed
5
+  affiliation: QIMR Berghofer Medical Research Institute, 300 Herston Road, Herston QLD 4006, Australia
6
+  date: "`r Sys.Date()`"
7
+vignette: >
8
+  %\VignetteIndexEntry{NetPathMiner Vignette}
9
+  %\VignetteEngine{knitr::rmarkdown}
10
+  %\VignetteKeywords{Network, igraph, KGML, SBML, BioPAX, Path Mining}
11
+output:
12
+    BiocStyle::html_document
13
+---
14
+
15
+
16
+# Version Info
17
+```{r, echo=FALSE, results="hide", warning=FALSE}
18
+suppressPackageStartupMessages({library('NetPathMiner')})
19
+```
20
+<p>
21
+**R version**: `r R.version.string`
22
+<br />
23
+**Bioconductor version**: `r BiocManager::version()`
24
+<br />
25
+**Package version**: `r packageVersion("NetPathMiner")`
26
+</p>
27
+
28
+# Introduction
29
+
30
+NetPathMiner implements a flexible module-based process flow for network path mining and visualization, which can be fully integrated with user-customized functions. It supports construction of various types of genome scale networks from three different pathway file formats, enabling its utility to most common pathway databases. In addition, NetPathMiner provides different visualization techniques to facilitate the analysis of even thousands of output paths.
31
+
32
+This document provides a general overview of the functionalities presented in NetPathMiner (NPM) package. Below, we provide a step-by-step tutorial starting by installation instructions followed by a guide on how to use the package functions perform different network analyses.
33
+
34
+To report bugs and arising issues, please visit https://github.com/ahmohamed/NetPathMiner
35
+
36
+# Installation Instructions
37
+
38
+## System Prerequisites
39
+NPM depends on libxml2 and libSBML to process pathway files.Installation or running certain functions MIGHT fail if these prerequisite libraries are not available. Please read through the following instructions.
40
+
41
+#### Prerequisites for Unix users (Linux and Mac OS)
42
+##### Installing libxml2
43
+Make sure your system has library libxml2 installed. In Mac OSX 10.6 or later, libxml2
44
+are built in. For Linux users also, this is almost always the case, however, developing headers
45
+may be missing. To install libxml2 and the headers:
46
+
47
+```Shell
48
+    sudo apt-get install libxml2
49
+    sudo apt-get install libxml2-dev
50
+```
51
+
52
+##### Installing libSBML
53
+Installing libSBML for Unix users is optional. However, NetPathMiner will not be able to process SBML
54
+files. If you will not use SBML functions, you can skip this part.
55
+
56
+From the website of libSBML http://sbml.org/Software/libSBML, you can directly download the
57
+binaries suitable for your system from `Download libSBML` link. You can follow the installation instructions
58
+on the website.
59
+
60
+#### Prerequisites for Windows users
61
+If you are installing the package through Bioconductor, you don't have to install external libraries. However, currently the Bioconductor version for Windows doesn't support SBML processing. Alternatively, we have prepared all dependencies in a tar file, downloadable from https://github.com/ahmohamed/NPM_dependencies . Please download the file and place in in the home directory of R (type <code>R RHOME</code> in command prompt to locate it), before installation.
62
+
63
+Unless you want to use customized libraries, you can skip the rest of this section.To use customized libraries, you have to compile them and provide them to R at the time of installation. This is not a trivial task, please be sure you really need these custom libraries.
64
+
65
+##### Installing libxml2
66
+NetPathMiner expects an enviroment variable `LIB_XML` or `LIB_XML2` pointing to directory where
67
+libxml2 is installed. This directory should have both the compiled library (DLL file) and the header files.
68
+
69
+You can download libxml2.dll from http://sourceforge.net/projects/gnuwin32/files/libxml/ among other sources.
70
+Please, place it in a `bin` folder under the installation directory.
71
+
72
+You will need also the header files, which can be obtained from NPM_dependecies.tar file. After extracing it, copy
73
+the include directory to the installation directory.
74
+
75
+Finally, set the `LIB_XML2` variable to point to the installation directory, which should now contain dll files inder `bin`
76
+and header files under `include`.
77
+
78
+##### Installing libSBML
79
+Since libSBML is a C++ libraries, it needs to be compiled using GCC compiler. Unforturantely, there is no binary
80
+version for Windows comipled with GCC. To use libSBML, you need to build it from source.
81
+
82
+First, dowload source package from http://sourceforge.net/projects/sbml/files/libsbml/ , extract it. You will
83
+need also MinGW http://www.mingw.org/ or the 64-bit version http://mingw-w64.sourceforge.net/ depending on your system.
84
+Add `mingw/bin` to your PATH, by editing eviroment variables.
85
+
86
+Second, you need CMake http://www.cmake.org/ . You can follow the instructions at http://sbml.org/Software/libSBML/docs/java-api/libsbml-installation.html#windows-configuring , however, choose "MinGW Makefiles" instead of "Visual Studio 10".
87
+
88
+After finishing the CMake step, use the MinGW's `make.exe` to compile libSBML. Copy the dependencies you used
89
+during the compilation to the `bin` directory. Set the enviroment variable `LIB_SBML` to point the installation
90
+directory, which should now contain dll files inder `bin` and header files under `include`
91
+
92
+
93
+### R Package dependencies
94
+NetPathMiner depends on package igraph to represent network objects. Installing igraph is required for the package
95
+to work. You will also need devtools package to install directly from github.
96
+NetPathMiner suggests package rBiopaxParser to process BioPAX files and RCurl to download annotations from the web. NetPathMiner can still work without installing the suggested packages, but you will not be able to use the aforementioned functionalities.
97
+
98
+##### igraph
99
+Package igraph is available at CRAN. To install it call:
100
+```r
101
+    install.packages("igraph")
102
+```
103
+
104
+##### devtools
105
+Package devtools is available at CRAN. For Windows, this seems to depend on
106
+having Rtools for Windows installed. You can download and install this from:
107
+http://cran.r-project.org/bin/windows/Rtools/
108
+
109
+To install R package devtools call:
110
+```r
111
+    install.packages("devtools")
112
+```
113
+
114
+##### RCurl
115
+For Unix users, make sure your Linux has library libcurl installed. Check out:
116
+
117
+```Shell
118
+    locate libcurl
119
+    locate curl-config
120
+```
121
+
122
+If these are not found (usually the developer version is missing), most Linux
123
+users will be able to fix this by running:
124
+
125
+```Shell
126
+    sudo apt-get install libcurl4-openssl-dev
127
+```
128
+
129
+You will now be able to install R package RCurl. In R console:
130
+```r
131
+    install.packages("RCurl")
132
+```
133
+
134
+If you encounter other problems check out http://www.omegahat.org/RCurl/FAQ.html
135
+
136
+##### rBiopaxParser
137
+Package rBiopaxParser is available on Bioconductor. For installation instructions check
138
+out http://www.bioconductor.org/packages/release/bioc/html/rBiopaxParser.html or
139
+call:
140
+
141
+```r
142
+    if (!requireNamespace("BiocManager", quietly=TRUE))
143
+        install.packages("BiocManager")
144
+    BiocManager::install("rBiopaxParser")
145
+```
146
+
147
+to install it right away.
148
+
149
+### NetPathMiner Installation
150
+If everything went well you will be able to install the NetPathMiner package.
151
+
152
+#### From Bioconductor:
153
+In R console, type:
154
+
155
+```r
156
+    if (!requireNamespace("BiocManager", quietly=TRUE))
157
+        install.packages("BiocManager")
158
+    BiocManager::install("NetPathMiner")
159
+```
160
+
161
+
162
+#### From GitHub using devtools:
163
+In R console, type:
164
+
165
+```r
166
+    library(devtools)
167
+    install_github(repo="NetPathMiner", username="ahmohamed")
168
+```
169
+
170
+# Getting Started
171
+First, let's load the library and the example data set.
172
+
173
+```{r Load_package, echo=TRUE, eval=TRUE, results="hide"}
174
+library(NetPathMiner)
175
+```
176
+
177
+# Database Extraction
178
+Here we create a network from a pathway file. Pathway files can be downloaded from a verity of databases, like (KEGG)[http://www.kegg.jp/kegg/pathway.html], (Reactome)[http://www.reactome.org/], (Pathway Interaction Database (PID))[http://pid.nci.nih.gov/] and (BioModels)[http://www.ebi.ac.uk/biomodels-main/].
179
+
180
+NPM supports processing KGML, SBML and BioPAX. Different databases export pathway information in different formats. Depending on the format you are using, you can choose the corresponding NPM function.
181
+
182
+```{r, echo=TRUE, eval=FALSE}
183
+graph <- KGML2igraph(filename = file)
184
+graph <- SBML2igraph(filename = file)
185
+```
186
+
187
+Note that SBML2igraph will not work unless you had libSBML during installation. For BioPAX format,
188
+`rBiopaxParser` package is needed.
189
+
190
+```{r, echo=TRUE, eval=FALSE}
191
+library(rBiopaxParser)
192
+biopax = readBiopax(file)
193
+graph <- BioPAX2igraph(biopax = biopax)
194
+```
195
+
196
+If you want to create a genome-scale network, you may want to process multiple files into a single network. To do that, you can either provide a list of files.
197
+
198
+```{r, echo=TRUE, eval=FALSE}
199
+graph <- KGML2igraph(filename = c(file1, file2))
200
+```
201
+
202
+or input the directory containing the files.
203
+```{r, echo=TRUE, eval=FALSE}
204
+graph <- KGML2igraph(filename = ".")
205
+```
206
+
207
+If you are processing SBML or BioPAX files, you can specify which annotation attributes to extract.
208
+
209
+```{r, echo=TRUE, eval=FALSE}
210
+# Extract all MIRIAM identifiers from an SBML file.
211
+graph <- SBML2igraph(filename = file, miriam = "all")
212
+
213
+# Extract only miram.go identifiers from a BioPAX file.
214
+graph <- BioPAX2igraph(biopax = biopax, miriam = "go")
215
+```
216
+
217
+The above command gives us a bipartite metabolic network. You may be interested in protein-protein interaction, and you would like to get a network in which genes are vertices, and edges represent relationships. In NPM, you can do that by:
218
+
219
+```{r, echo=FALSE, eval=TRUE, results="hide"}
220
+file <- file.path(find.package("NetPathMiner"), "extdata", "hsa00860.xml")
221
+```
222
+```{r, echo=TRUE, eval=FALSE, results="hide"}
223
+graph <- KGML2igraph(filename = file, parse.as = "signaling")
224
+
225
+graph <- KGML2igraph(filename = file, parse.as = "signaling",
226
+	expand.complexes = TRUE)
227
+```
228
+
229
+For this tutorial, we will use an An example metabolic network of Carbohydrate metabolism
230
+extracted from SBML file from Reactome database.
231
+
232
+```{r, echo=TRUE, eval=TRUE}
233
+data("ex_sbml")
234
+graph <- ex_sbml
235
+graph
236
+```
237
+
238
+# Handling Annotation Attributes
239
+Once we have our network, we can use igraph functions to explore it. First, we view vertices and edges using V() and E() functions respectively.
240
+
241
+Network vertices:
242
+
243
+```{r, echo=TRUE, eval=TRUE}
244
+head( V(graph) )
245
+```
246
+
247
+Edge Vertices:
248
+
249
+```{r, echo=TRUE, eval=TRUE}
250
+head( E(graph) )
251
+```
252
+
253
+Reaction vertices only:
254
+
255
+```{r, echo=TRUE, eval=TRUE}
256
+head( V(graph)[ reactions ] )
257
+```
258
+
259
+All vertex annotation attributes are stored in "attr" attribute. To view the annotation for a certain vertex, you can index it by name.
260
+
261
+```{r, echo=TRUE, eval=TRUE}
262
+V(graph)[ "reaction_71850" ]$attr
263
+```
264
+
265
+Here, our reaction vertex annotations describing the chemical transition. You can also notice annotations starting with "miriam" key word. MIRIAM is a standard format for writing biological identifiers. You can explore the details of this annotation system on http://www.ebi.ac.uk/miriam/main/collections. To list all vertex attributes:
266
+
267
+```{r, echo=TRUE, eval=TRUE}
268
+getAttrNames(graph)
269
+```
270
+
271
+Since annotations tend to be incomplete, NPM provides a function to check the coverage of each attribute. The function also list the number of vertices having multiple attribute values. For example, vertices with multiple `miriam.kegg.genes` annotations can be view as protein complexes.
272
+
273
+```{r, echo=TRUE, eval=TRUE}
274
+getAttrStatus(graph, pattern = "^miriam.")
275
+```
276
+
277
+NPM also implements an Attribute Fetcher, where you can convert one annotation to another. The Attribute Fetcher requires RCurl installed, because it uses the online web service of BridgeDb http://www.bridgedb.org/.
278
+
279
+```{r, echo=TRUE, eval=FALSE}
280
+require("RCurl")
281
+# Fetch uniprot annotation
282
+graph <- fetchAttribute(graph, organism = "Homo sapiens", target.attr = "miriam.ncbigene" , source.attr = "miriam.uniprot")
283
+
284
+# Fetch ChEBI annotation.
285
+graph <- fetchAttribute(graph, target.attr = "miriam.chebi", source.attr = "miriam.kegg.compound")
286
+```
287
+
288
+You can also use the Attribute Fetcher to obtain Affymetrix annotation needed for microarray analysis.
289
+
290
+# Network Processing
291
+NetPathMiner can convert between different network representations. Given a bipartite metabolic network, reaction network is created by removing metabolite vertices and keeping them as edge attributes. This is useful to get adjacent vertices (now reactions) to have gene annotations needed for gene expression mapping.
292
+
293
+```{r, echo=TRUE, eval=TRUE}
294
+rgraph <- makeReactionNetwork(graph, simplify=FALSE)
295
+rgraph
296
+```
297
+
298
+Since gene annotations are rarely complete, we can further remove reaction vertices that are missing gene annotations. This is particularly meaningful when reactions are translocation or spontaneous reactions, which are not catalysed by genes. We can then remove such reactions by:
299
+
300
+```{r, echo=TRUE, eval=FALSE}
301
+rgraph <- simplifyReactionNetwork(rgraph)
302
+rgraph <- makeReactionNetwork(graph, simplify=TRUE)
303
+```
304
+
305
+Some reaction vertices will be catalysed by more than one enzyme. We can `expand` these vertices to get the gene network.
306
+
307
+```{r, echo=TRUE, eval=TRUE}
308
+# Expand complexes of gene network.
309
+ggraph <- expandComplexes(rgraph, v.attr = "miriam.uniprot",
310
+		keep.parent.attr= c("^pathway", "^compartment"))
311
+
312
+# Convert reaction network to gene network.
313
+ggraph <- makeGeneNetwork(rgraph)
314
+```
315
+
316
+`expandComplexes` offers manipulation of network vertices by their attributes, that includes handling missing annotations and annotation inheritance. Refer to the manual for for details.
317
+
318
+# Weighting Network
319
+Now that we have our network, we can use gene expression data to weight the network edges. For this example we use an subset of data provided by `ALL` data package. The data consist of microarrays from 128 different individuals with acute lymphoblastic leukemia (ALL).
320
+
321
+The gene expression is present as Affymetrix IDs. Since we don't have these annotations in out network, we can use Attribute Fetcher to get them.
322
+
323
+```{r, echo=TRUE, eval=TRUE}
324
+data(ex_microarray)
325
+
326
+```
327
+```{r, echo=TRUE, eval=FALSE}
328
+# Assign weights to edges.
329
+if(require("RCurl") && url.exists( NPMdefaults("bridge.web") ))
330
+	rgraph <- fetchAttribute(rgraph, organism = "Homo sapiens",
331
+						target.attr = "miriam.affy.probeset",
332
+						source.attr = "miriam.uniprot")
333
+```
334
+
335
+Now that we checked that we have `affy.probeset` annotations, we can use the weight function. The default weight function assigns edge weights based on Pearson's correlation of expression profiles of adjacent genes. You can also provide you own function as a `weight.method`. You can refer to the manual of this function for details.
336
+
337
+We can also provide sample categories as `y` labels. In that case, edge weights are computed for each label separately. Here we use Leukaemia molecular subtypes as categories.
338
+
339
+
340
+```{r, echo=TRUE, eval=FALSE}
341
+# This requires an internet connection, and RCurl and ALL packages to be present.
342
+# Instead, we will actually use a processed ALL data, where features are converted
343
+# to miriam.uniprot annotation. (Next chunk)
344
+
345
+library(ALL)
346
+data(ALL)
347
+rgraph <- assignEdgeWeights(microarray = exprs(ALL), graph = rgraph,
348
+weight.method = "cor", use.attr="miriam.affy.probeset", y=ALL$mol.bio, bootstrap = FALSE)
349
+```
350
+
351
+
352
+```{r, echo=FALSE, eval=TRUE}
353
+# This is what is evaluated.
354
+data(ex_microarray)
355
+rgraph <- assignEdgeWeights(microarray = ex_microarray, graph = rgraph,
356
+weight.method = "cor", use.attr="miriam.uniprot", y=colnames(ex_microarray), bootstrap = FALSE)
357
+```
358
+
359
+```{r, echo=TRUE, eval=TRUE}
360
+rgraph$y.labels
361
+head( E(rgraph)$edge.weights )
362
+```
363
+
364
+# Path Ranking
365
+Edges are now weighted by the correlation of connected genes. We can find highly correlated paths within the network by maximising the edge weight.
366
+
367
+NetPathMiner provides two methods to accomplish that. First, `probabilistic.shortest.path` formulates the problem as finding shortest paths in a network by transforming edge weights by their empirical cumulative distribution function (ECDF). Finding the shortest path is equivalent to finding the least probable path given this empirical distribution. The code below gets the 100-shortest paths.
368
+
369
+```{r, echo=TRUE, eval=TRUE}
370
+ranked.p <- pathRanker(rgraph, method = "prob.shortest.path",
371
+	K = 25, minPathSize = 6)
372
+```
373
+
374
+Second, `value` method finds paths where the sum of edge weights are significantly higher than random paths of similar length. The distribution of random path scores can be estimated by `samplePaths` which uses Metropolis sampling technique. The path sample can be then provided to the path ranking function. If path sample is not provided, random edge sampling is used to estimate the distribution.
375
+
376
+```{r, echo=TRUE, eval=FALSE}
377
+pathsample <- samplePaths(rgraph, max.path.length = vcount(rgraph),
378
+num.samples = 1000, num.warmup = 10)
379
+
380
+ranked.p <- pathRanker(rgraph, method = "pvalue",
381
+sampledpaths = pathsample ,alpha=0.1)
382
+```
383
+
384
+We can get our path set as lists of edge IDs instead.
385
+
386
+```{r, echo=TRUE, eval=TRUE}
387
+# Get paths as edge IDs.
388
+eids <- getPathsAsEIDs(paths = ranked.p, graph = rgraph)
389
+```
390
+
391
+We can also get paths as edge IDs on another network representation. In this example, we extracted paths from a reaction network. We can get the equivalent paths on the gene network by supplying the corresponding igraph object.
392
+
393
+```{r, echo=TRUE, eval=TRUE, results="hide"}
394
+# Convert paths to other networks.
395
+eids <- getPathsAsEIDs(paths = ranked.p, graph = ggraph)
396
+```
397
+
398
+# Clustering and classification of paths
399
+The size of the ranked path can be very large, making their analysis challenging. NetPathMiner offers clustering functions to group the ranked path list into few path clusters that can be investigated easily.
400
+
401
+```{r, echo=TRUE, eval=TRUE}
402
+# Clustering.
403
+ybinpaths <- pathsToBinary(ranked.p)
404
+p.cluster <- pathCluster(ybinpaths, M = 2)
405
+```
406
+```{r, fig=TRUE, pdf=TRUE, echo=TRUE, eval=TRUE}
407
+plotClusters(ybinpaths, p.cluster)
408
+```
409
+
410
+We can also identify a set of paths that best classify a sample category (as a form of biomarker for example). The code below creates a classifier for `BCR/ABL` subtype. Since our network is very small, we are not able to create an accurate classifier.
411
+
412
+```{r, echo=TRUE, eval=TRUE}
413
+p.class <- pathClassifier(ybinpaths, target.class = "BCR/ABL", M = 2)
414
+```
415
+
416
+```{r, echo=TRUE, eval=FALSE}
417
+plotClassifierROC(p.class)
418
+```
419
+![alt text](ROCplot.png "Logo Title Text 1")
420
+
421
+
422
+```{r, fig=TRUE, pdf=TRUE, echo=TRUE, eval=TRUE}
423
+plotClusters(ybinpaths, p.class)
424
+```
425
+
426
+
427
+# Plotting
428
+NetPathMiner offers several plotting options for networks and ranked paths. First, we can plot our network colouring vertices by their cellular compartment.
429
+
430
+```{r, echo=TRUE, eval=TRUE}
431
+plotNetwork(rgraph, vertex.color="compartment.name")
432
+```
433
+
434
+NetPathMiner's plotPaths function can be used to view ranked paths on the network structure. Cluster information can also be provided, so that paths belonging to the same cluster will have the same colour.
435
+
436
+```{r, fig=TRUE, pdf=TRUE, echo=TRUE, eval=FALSE}
437
+plotPaths(ranked.p, rgraph)
438
+
439
+# With clusters
440
+plotPaths(ranked.p, graph, path.clusters=p.class)
441
+```
442
+
443
+To view paths on different network representations, you can pass the networks as parameters to plotPaths, and it will do the job.
444
+
445
+```{r, fig=TRUE, pdf=TRUE, echo=TRUE, eval=TRUE}
446
+plotAllNetworks(ranked.p, metabolic.net = graph, reaction.net = rgraph,
447
+		path.clusters=p.class, vertex.label = "", vertex.size = 4)
448
+```
449
+
450
+To make use of the annotation attributes, NetPathMiner can layout vertices such that those sharing a common attribute value are plotted close to each other, and using similar colors.
451
+
452
+```{r, echo=TRUE, eval=FALSE}
453
+layout.c <- clusterVertexByAttr(rgraph, "pathway", cluster.strength = 3)
454
+v.color <- colorVertexByAttr(rgraph, "pathway")
455
+plotPaths(ranked.p , rgraph, clusters=p.class,
456
+	layout = layout.c, vertex.color = v.color)
457
+```
458
+
459
+Finally, for interactive visualization using Cytoscape, plotCytoscapeGML can export the graph, attributes and layout as a GML file, which can be imported directly into Cytoscape. For example:
460
+
461
+```{r, echo=TRUE, eval=FALSE}
462
+plotCytoscapeGML(graph, file="example.gml", layout = layout.c,
463
+				vertex.size = 5, vertex.color = v.color)
464
+```
465
+
466
+# Additional functions
467
+## Genesets and geneset subnetworks
468
+NetPathMiner provides functions to extract genesets utilizing annotation attributes in the network. To get genesets as lists of genes for geneset enrichment analyses:
469
+
470
+```{r, echo=TRUE, eval=TRUE, results="hide"}
471
+getGeneSets(graph, use.attr="compartment", gene.attr="miriam.uniprot")
472
+```
473
+
474
+Alternatively, genesets can be obtained as network structures.
475
+
476
+```{r, echo=TRUE, eval=TRUE, results="hide"}
477
+getGeneSetNetworks(graph, use.attr="compartment")
478
+```
479
+
480
+## Integration with graph package
481
+All networks constructed in NetPathMiner are represented as igraph object. Users can convert these networks to Bioconductor's graphNEL object using `toGraphNEL` function
482
+
483
+```{r, echo=TRUE, eval=FALSE}
484
+graphNEL <- toGraphNEL(graph, export.attr="^miriam.")
485
+```
0 486
deleted file mode 100755
... ...
@@ -1,563 +0,0 @@
1
-%\VignetteIndexEntry{NetPathMiner Vignette}
2
-%\VignetteDepends{igraph}
3
-%\VignetteKeywords{Network, igraph, KGML, SBML, BioPAX, Path Mining}
4
-%\VignettePackage{NetPathMiner}
5
-
6
-
7
-\documentclass[11pt,a4paper]{article}
8
-
9
-\usepackage{tocloft}
10
-\usepackage{hyperref}
11
-\usepackage{float}
12
-
13
-%\usepackage[round]{natbib}
14
-\usepackage{amsmath}
15
-\usepackage{amsfonts}
16
-\usepackage{graphicx}
17
-%\usepackage[latin1]{inputenc}
18
-\usepackage[utf8]{inputenc}
19
-
20
-\newcommand{\gene}[1]{\emph{#1}}
21
-
22
-\setlength{\parskip}{1.5ex}
23
-\setlength{\parindent}{0cm}
24
-
25
-% NEW COMMANDS
26
-% ------------------------------------------------
27
-\newcommand{\Robject}[1]{\texttt{#1}}
28
-\newcommand{\Rpackage}[1]{\textit{#1}}
29
-\newcommand{\Rclass}[1]{\textit{#1}}
30
-\newcommand{\Rfunction}[1]{{\small\texttt{#1}}}
31
-
32
-\newcommand{\myincfig}[4]{
33
-  \setkeys{Gin}{width=#1\textwidth}
34
-  \begin{figure}[htbp]
35
-    \begin{center}
36
-      #2
37
-      \caption{\label{#3}#4}
38
-    \end{center}
39
-  \end{figure}
40
-  \setkeys{Gin}{width=.8\textwidth}
41
-}
42
-
43
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
44
-\begin{document}
45
-% options(useFancyQuotes="UTF-8")?
46
-<<no.nonsense,echo=FALSE,results=hide>>=
47
-rm(list=ls())
48
-@
49
-
50
-\title{NetPathMiner Vignette}
51
-\author{ Ahmed Mohamed \footnote{Bioinformatics Center, Institute for Chemical Research, Kyoto University, Gokasho, Uji, Kyoto 611-0011, Japan.
52
-Email: mohamed@kuicr.kyoto-u.ac.jp}}
53
-\date{\today}
54
-\maketitle
55
-
56
-%\renewcommand{\baselinestretch}{0.5}\normalsize
57
-\setlength\cftparskip{-2pt}
58
-\setlength\cftbeforesecskip{1pt}
59
-\setlength\cftaftertoctitleskip{2pt}
60
-\tableofcontents
61
-\newpage
62
-%\renewcommand{\baselinestretch}{1.00}\normalsize
63
-
64
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
65
-%\begin{abstract}
66
-%\end{abstract}
67
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
68
-
69
-\section{Introduction}
70
-\label{sec:introduction}
71
-NetPathMiner implements a flexible module-based process flow for network path mining and visualization,
72
-which can be fully integrated with user-customized functions.
73
-It supports construction of various types of genome scale networks from three different pathway
74
-file formats, enabling its utility to most common pathway databases.
75
-In addition, NetPathMiner provides different visualization techniques to facilitate the analysis of even
76
-thousands of output paths.
77
-
78
-This document provides a general overview of the functionalities presented in NetPathMiner (NPM) package .
79
-Below, we provide a step-by-step tutorial starting by installation
80
-instructions followed by a guide on how to use the package functions perform different network analyses.
81
-
82
-To report bugs and arising issues, please visit \url{https://github.com/ahmohamed/NetPathMiner}
83
-
84
-\section{Installation Instructions}
85
-\label{sec:installation}
86
-
87
-\subsection{System Prerequisites}
88
-NPM depends on libxml2 and libSBML to process pathway files.Installation or running
89
-certain functions MIGHT fail if these prerequisite libraries are
90
-not available. Please read through the following instructions.
91
-
92
-\subsubsection{Prerequisites for Unix users (Linux and Mac OS)}
93
-\paragraph{Installing libxml2}
94
-Make sure your system has library libxml2 installed. In Mac OSX 10.6 or later, libxml2
95
-are built in. For Linux users also, this is almost always the case, however, developing headers
96
-may be missing. To install libxml2 and the headers:
97
-
98
-\begin{verbatim}
99
-    sudo apt-get install libxml2
100
-    sudo apt-get install libxml2-dev
101
-\end{verbatim}
102
-
103
-\paragraph{Installing libSBML}
104
-Installing libSBML for Unix users is optional. However, NPM will not be able to process SBML
105
-files. If you will not use SBML functions, you can skip this part.
106
-
107
-From the website of libSBML \url{http://sbml.org/Software/libSBML}, you can directly download the
108
-binaries suitable for your system from ``Download libSBML'' link. You can follow the installation instructions
109
-on the website.
110
-
111
-\subsubsection{Prerequisites for Windows users}
112
-If you are installing the package through Bioconductor, you don't have to install external libraries. However, currently the Bioconductor version for Windows doesn't support SBML processing. Alternatively, we have prepared all dependencies in  a tar file, downloadable from \url{https://github.com/ahmohamed/NPM_dependencies} . Please download the file and place in in the home directory of R
113
-(type "R RHOME" in command prompt to locate it).
114
-
115
-Unless you want to use customized libraries, you can skip the rest of this section.
116
-To use customized libraries, you have to compile them and provide them to R at the time of installation.
117
-This is not a trivial task, please be sure you really need these custom libraries.
118
-
119
-\paragraph{Installing libxml2}
120
-NetPathMiner expects an enviroment variable \texttt{LIB\_XML} or \texttt{LIB\_XML2} pointing to directory where
121
-libxml2 is installed. This directory should have both the compiled library (DLL file) and the header files.
122
-
123
-You can download libxml2.dll from \url{http://sourceforge.net/projects/gnuwin/files/libxml/} among other sources.
124
-Please, place it in a `bin` folder under the installation directory.
125
-
126
-You will need also the header files, which can be obtained from NPM\_dependecies.tar file. After extracing it, copy
127
-the include directory to the installation directory.
128
-
129
-Finally, set the \texttt{LIB\_XML2} variable to point to the installation directory, which should now contain dll files inder \texttt{bin}
130
-and header files under `include`.
131
-
132
-\paragraph{Installing libSBML}
133
-Since libSBML is a C++ libraries, it needs to be compiled using GCC compiler. Unforturantely, there is no binary
134
-version for Windows comipled with GCC. To use libSBML, you need to build it from source.
135
-
136
-First, dowload source package from \url{http://sourceforge.net/projects/sbml/files/libsbml/} , extract it. You will
137
-need also MinGW \url{http://www.mingw.org/} or the 64-bit version \url{http://mingw-w64.sourceforge.net/} depending on your system.
138
-Add `mingw/bin` to your PATH, by editing eviroment variables.
139
-
140
-Second, you need CMake \url{http://www.cmake.org/} . You can follow the instructions at \url{http://sbml.org/Software/libSBML/docs/java-api/libsbml-installation.html#windows-configuring} , however, choose "MinGW Makefiles" instead of "Visual Studio 10".
141
-
142
-After finishing the CMake step, use the MinGW's \texttt{make.exe} to compile libSBML. Copy the dependencies you used
143
-during the compilation to the `bin` directory. Set the enviroment variable \texttt{LIB\_SBML} to point the installation
144
-directory, which should now contain dll files inder `bin` and header files under `include`
145
-
146
-\subsection{R Package dependencies}
147
-NPM depends on package igraph to represent network objects. Installing igraph is required for the package
148
-to work. You will also need devtools package to install directly from github.
149
-NPM suggests package rBiopaxParser to process BioPAX files and RCurl to download annotations from the web. NPM can still work without installing the suggested packages, but you will not be able to use the aforementioned functionalities.
150
-
151
-\paragraph{igraph}
152
-Package igraph is available at CRAN. To install it call:
153
-\begin{verbatim}
154
-    install.packages("igraph")
155
-\end{verbatim}
156
-
157
-\paragraph{RCurl}
158
-For Unix users, make sure your Linux has library libcurl installed. Check out:
159
-\begin{verbatim}
160
-    locate libcurl
161
-    locate curl-config
162
-\end{verbatim}
163
-If these are not found (usually the developer version is missing), most Linux
164
-users will be able to fix this by running:
165
-\begin{verbatim}
166
-    sudo apt-get install libcurl4-openssl-dev
167
-\end{verbatim}
168
-
169
-You will now be able to install R package RCurl. In R console:
170
-\begin{verbatim}
171
-    install.packages("RCurl")
172
-\end{verbatim}
173
-If you encounter other problems check out \url{http://www.omegahat.org/RCurl/FAQ.html}
174
-
175
-\paragraph{rBiopaxParser}
176
-Package rBiopaxParser is available on Bioconductor. For installation instructions check
177
-out \url{http://www.bioconductor.org/packages/release/bioc/html/rBiopaxParser.html} or
178
-call:
179
-\begin{verbatim}
180
-    if (!requireNamespace("BiocManager", quietly=TRUE))
181
-        install.packages("BiocManager")
182
-    BiocManager::install("rBiopaxParser")
183
-\end{verbatim}
184
-to install it right away.
185
-
186
-\subsection{NetPathMiner Installation}
187
-If everything went well you will be able to install the NetPathMiner package.
188
-
189
-\subsubsection{From Bioconductor:}
190
-In R console, type:
191
-
192
-\begin{verbatim}
193
-    if (!requireNamespace("BiocManager", quietly=TRUE))
194
-        install.packages("BiocManager")
195
-    BiocManager::install("NetPathMiner")
196
-\end{verbatim}
197
-
198
-\subsubsection{From GitHub using devtools:}
199
-To install the package from Github, you need devtools R package.
200
-
201
-\paragraph{devtools}
202
-Package devtools is available at CRAN. For Windows this seems to depend on
203
-having Rtools for Windows installed. You can download and install this from:
204
-\url{http://cran.r-project.org/bin/windows/Rtools/}
205
-
206
-To install R package devtools call:
207
-\begin{verbatim}
208
-    install.packages("devtools")
209
-\end{verbatim}
210
-
211
-Finally, in R console:
212
-
213
-\begin{verbatim}
214
-    library(devtools)
215
-    install_github(repo="NetPathMiner", username="ahmohamed")
216
-\end{verbatim}
217
-
218
-\section{Getting Started}
219
-\label{sec:gettingstarted}
220
-First, let's load the library and the example data set.
221
-
222
-<<label=Load_package,echo=TRUE, eval=TRUE, results=hide>>=
223
-library(NetPathMiner)
224
-@
225
-
226
-\section{Database Extraction}
227
-\label{sec:dbExtract}
228
-Here we create a network from a pathway file. Pathway files can be downloaded from
229
-a verity of databases, like \href{http://www.kegg.jp/kegg/pathway.html}{KEGG},
230
-\href{http://www.reactome.org/}{Reactome}, \href{http://pid.nci.nih.gov/}{Pathway Interaction
231
-Database (PID)} and \href{http://www.ebi.ac.uk/biomodels-main/}{BioModels}.
232
-
233
-NPM supports processing KGML, SBML and BioPAX. Different databases export pathway information
234
-in different formats. Depending on the format you are using, you can choose the corresponding NPM
235
-function.
236
-
237
-<<echo=TRUE, eval=FALSE>>=
238
-graph <- KGML2igraph(filename = file)
239
-graph <- SBML2igraph(filename = file)
240
-@
241
-
242
-Note that SBML2igraph will not work unless you had libSBML during installation. For BioPAX format,
243
-rBiopaxParser package is needed.
244
-
245
-<<echo=TRUE, eval=FALSE>>=
246
-require(rBiopaxParser)
247
-biopax = readBiopax(file)
248
-graph <- BioPAX2igraph(biopax = biopax)
249
-@
250
-
251
-If you want to create a genome-scale network, you may want to process multiple files into a single
252
-network. To do that, you can either provide a list of files.
253
-
254
-<<echo=TRUE, eval=FALSE>>=
255
-graph <- KGML2igraph(filename = c(file1, file2))
256
-@
257
-
258
-or input the directory containing the files.
259
-<<echo=TRUE, eval=FALSE>>=
260
-graph <- KGML2igraph(filename = ".")
261
-@
262
-
263
-If you are processing SBML or BioPAX files, you can specify which annotation attributes to extract.
264
-
265
-<<echo=TRUE, eval=FALSE>>=
266
-# Extract all MIRIAM identifiers from an SBML file.
267
-graph <- SBML2igraph(filename = file, miriam = "all")
268
-
269
-# Extract all MIRIAM identifiers from an SBML file.
270
-graph <- BioPAX2igraph(biopax = biopax, miriam = "go")
271
-@
272
-
273
-The above command gives us a bipartite metabolic network. You may be interested in protein-protein
274
-interaction, and you would like to get a network in which genes are vertices, and edges represent relationships.
275
-In NPM, you can do that by:
276
-
277
-<<echo=FALSE, eval=TRUE, results=hide>>=
278
-file <- file.path(find.package("NetPathMiner"), "extdata", "hsa00860.xml")
279
-@
280
-<<echo=TRUE, eval=FALSE, results=hide>>=
281
-graph <- KGML2igraph(filename = file, parse.as = "signaling")
282
-
283
-graph <- KGML2igraph(filename = file, parse.as = "signaling",
284
-	expand.complexes = TRUE)
285
-@
286
-
287
-For this tutorial, we will use an An example metabolic network of Carbohydrate metabolism
288
-extracted from SBML file from Reactome database.
289
-
290
-<<echo=TRUE, eval=TRUE>>=
291
-data("ex_sbml")
292
-graph <- ex_sbml
293
-graph
294
-@
295
-
296
-\section{Handling Annotation Attributes}
297
-\label{sec:attr}
298
-Once we have our network, we can use igraph functions to explore it. First, we view vertices and edges using
299
-V() and E() functions respectively.
300
-
301
-Network vertices:
302
-<<echo=TRUE, eval=TRUE>>=
303
-head( V(graph) )
304
-@
305
-Edge Vertices
306
-<<echo=TRUE, eval=TRUE>>=
307
-head( E(graph) )
308
-@
309
-Reaction vertices only:
310
-<<echo=TRUE, eval=TRUE>>=
311
-head( V(graph)[ reactions ] )
312
-@
313
-
314
-All vertex annotation attributes are stored in "attr" attribute. To view the annotation for a certain vertex,
315
-you can index it by name.
316
-<<echo=TRUE, eval=TRUE>>=
317
-V(graph)[ "reaction_71850" ]$attr
318
-@
319
-
320
-Here, our reaction vertex annotations describing the chemical transition. You can also notice annotations
321
-starting with "miriam" key word. MIRIAM is a standard format for writing biological identifiers. You can explore the details of
322
-this annotation system on \url{http://www.ebi.ac.uk/miriam/main/collections}. To list all vertex attributes:
323
-
324
-<<echo=TRUE, eval=TRUE>>=
325
-getAttrNames(graph)
326
-@
327
-
328
-Since annotations tend to be incomplete, NPM provides a function to check the coverage of each attribute.
329
-The function also list the number of vertices having multiple attribute values. For example, vertices with multiple
330
-miriam.kegg.genes annotations can be view as protein complexes.
331
-
332
-<<echo=TRUE, eval=TRUE>>=
333
-getAttrStatus(graph, pattern = "^miriam.")
334
-@
335
-
336
-NPM also implements an Attribute Fetcher, where you can convert one annotation to another. The Attribute
337
-Fetcher requires RCurl installed, because it uses the online web service of BridgeDb \url{http://www.bridgedb.org/}.
338
-
339
-<<echo=TRUE, eval=FALSE>>=
340
-require("RCurl")
341
-# Fetch uniprot annotation
342
-graph <- fetchAttribute(graph, organism = "Homo sapiens",
343
-target.attr = "miriam.ncbigene" , source.attr = "miriam.uniprot")
344
-
345
-# Fetch ChEBI annotation.
346
-graph <- fetchAttribute(graph, target.attr = "miriam.chebi",
347
-source.attr = "miriam.kegg.compound")
348
-@
349
-
350
-You can also use the Attribute Fetcher to obtain Affymetrix annotation needed for
351
-microarray analysis.
352
-
353
-\section{Network Processing}
354
-\label{sec:netProcess}
355
-NetPathMiner can convert between different network representations. Given a bipartite metabolic network, reaction network is created by removing metabolite vertices and keeping them as edge attributes. This is useful to get adjacent vertices (now reactions) to have gene annotations needed for gene expression mapping.
356
-
357
-<<echo=TRUE, eval=TRUE>>=
358
-rgraph <- makeReactionNetwork(graph, simplify=FALSE)
359
-rgraph
360
-@
361
-
362
-Since gene annotations are rarely complete, we can further remove reaction vertices that are missing gene annotations. This is particularly meaningful when reactions are translocation or spontaneous reactions, which are not catalysed by genes. We can then remove such reactions by:
363
-
364
-<<echo=TRUE, eval=FALSE>>=
365
-rgraph <- simplifyReactionNetwork(rgraph)
366
-rgraph <- makeReactionNetwork(graph, simplify=TRUE)
367
-@
368
-
369
-Some reaction vertices will be catalysed by more than one enzyme. We can ``expand'' these vertices to get the gene network.
370
-
371
-<<echo=TRUE, eval=TRUE>>=
372
-# Expand complexes of gene network.
373
-ggraph <- expandComplexes(rgraph, v.attr = "miriam.uniprot",
374
-		keep.parent.attr= c("^pathway", "^compartment"))
375
-
376
-# Convert reaction network to gene network.
377
-ggraph <- makeGeneNetwork(rgraph)
378
-@
379
-
380
-\texttt{expandComplexes} offers manipulation of network vertices by their attributes, that includes handling missing annotations
381
-and annotation inheritance. Refer to the manual for for details.
382
-
383
-\section{Weighting Network}
384
-\label{sec:netWeight}
385
-Now that we have our network, we can use gene expression data to weight the network edges. For this example we use an subset of data provided by ``ALL'' data package. The data consist of microarrays from 128 different individuals with acute lymphoblastic leukemia (ALL).
386
-
387
-The gene expression is present as Affymetrix IDs. Since we don't have these annotations in out network, we can use Attribute Fetcher to get them.
388
-
389
-<<echo=TRUE, eval=TRUE>>=
390
-data(ex_microarray)
391
-
392
-<<echo=TRUE, eval=FALSE>>=
393
-# Assign weights to edges.
394
-if(require("RCurl") && url.exists( NPMdefaults("bridge.web") ))
395
-	rgraph <- fetchAttribute(rgraph, organism = "Homo sapiens",
396
-						target.attr = "miriam.affy.probeset",
397
-						source.attr = "miriam.uniprot")
398
-@
399
-
400
-Now that we checked that we have affy.probeset annotations, we can use the weight function. The default weight function assigns edge weights based on Pearson's correlation of expression profiles of adjacent genes. You can also provide you own function as a ``weight.method''. You can refer to the manual of this function for details.
401
-
402
-We can also provide sample categories as ``y'' labels. In that case, edge weights are computed for each label separately. Here we use Leukaemia molecular subtypes as categories.
403
-
404
-% This requires an internet connection, and RCurl and ALL packages to be present.
405
-% Instead, we will actually use a processed ALL data, where features are converted
406
-% to miriam.uniprot annotation.
407
-<<echo=TRUE, eval=FALSE>>=
408
-library(ALL)
409
-data(ALL)
410
-rgraph <- assignEdgeWeights(microarray = exprs(ALL), graph = rgraph,
411
-weight.method = "cor", use.attr="miriam.affy.probeset", y=ALL$mol.bio, bootstrap = FALSE)
412
-@
413
-
414
-% This is what is evaluated.
415
-<<echo=TRUE, eval=TRUE>>=
416
-data(ex_microarray)
417
-rgraph <- assignEdgeWeights(microarray = ex_microarray, graph = rgraph,
418
-weight.method = "cor", use.attr="miriam.uniprot", y=colnames(ex_microarray), bootstrap = FALSE)
419
-@
420
-
421
-
422
-<<echo=TRUE, eval=TRUE>>=
423
-rgraph$y.labels
424
-head( E(rgraph)$edge.weights )
425
-@
426
-
427
-\section{Path Ranking}
428
-\label{sec:rankPath}
429
-Edges are now weighted by the correlation of connected genes. We can find highly correlated paths within the network by maximising the edge weight.
430
-
431
-NetPathMiner provides two methods to accomplish that. First, ``probabilistic.shortest.path'' formulates the problem as finding shortest paths in a network by transforming edge weights by their empirical cumulative distribution function (ECDF). Finding the shortest path is equivalent to finding the least probable path given this empirical distribution. The code below gets the 100-shortest paths.
432
-
433
-<<echo=TRUE, eval=TRUE>>=
434
-ranked.p <- pathRanker(rgraph, method = "prob.shortest.path",
435
-	K = 25, minPathSize = 6)
436
-@
437
-
438
-Second, ``value'' method finds paths where the sum of edge weights are significantly higher than random paths of similar length. The distribution of random path scores can be estimated by ``samplePaths'' which uses Metropolis sampling technique. The path sample can be then provided to the path ranking function. If path sample is not provided, random edge sampling is used to estimate the distribution.
439
-
440
-<<echo=TRUE, eval=FALSE>>=
441
-pathsample <- samplePaths(rgraph, max.path.length = vcount(rgraph),
442
-num.samples = 1000, num.warmup = 10)
443
-
444
-ranked.p <- pathRanker(rgraph, method = "pvalue",
445
-sampledpaths = pathsample ,alpha=0.1)
446
-@
447
-
448
-We can get our path set as lists of edge IDs instead.
449
-
450
-<<echo=TRUE, eval=TRUE>>=
451
-# Get paths as edge IDs.
452
-eids <- getPathsAsEIDs(paths = ranked.p, graph = rgraph)
453
-@
454
-
455
-We can also get paths as edge IDs on another network representation. In this example, we extracted paths from a reaction network. We can get the equivalent paths on the gene network by supplying the corresponding igraph object.
456
-
457
-<<echo=TRUE, eval=TRUE, results=hide>>=
458
-# Convert paths to other networks.
459
-eids <- getPathsAsEIDs(paths = ranked.p, graph = ggraph)
460
-@
461
-
462
-\section{Clustering and classification of paths}
463
-\label{sec:clusterPath}
464
-The size of the ranked path can be very large, making their analysis challenging. NetPathMiner offers clustering functions to group the ranked path list into few path clusters that can be investigated easily.
465
-
466
-<<echo=TRUE, eval=TRUE>>=
467
-# Clustering.
468
-ybinpaths <- pathsToBinary(ranked.p)
469
-p.cluster <- pathCluster(ybinpaths, M = 2)
470
-@
471
-<<fig=TRUE, pdf=TRUE, echo=TRUE, eval=TRUE>>=
472
-plotClusters(ybinpaths, p.cluster)
473
-@
474
-
475
-We can also identify a set of paths that best classify a sample category (as a form of biomarker for example). The code below creates a classifier for ``BCR/ABL'' subtype. Since our network is very small, we are not able to create an accurate classifier.
476
-
477
-<<echo=TRUE, eval=TRUE>>=
478
-p.class <- pathClassifier(ybinpaths, target.class = "BCR/ABL", M = 2)
479
-@
480
-<<echo=TRUE, eval=FALSE>>=
481
-plotClassifierROC(p.class)
482
-@
483
-
484
-\begin{figure}[h]%figure1
485
-\centerline{\includegraphics[width=\textwidth]{ROCplot.pdf}}
486
-\label{plotpclass}
487
-\end{figure}
488
-
489
-<<fig=TRUE, pdf=TRUE, echo=TRUE, eval=TRUE>>=
490
-plotClusters(ybinpaths, p.class)
491
-@
492
-
493
-
494
-\section{Plotting}
495
-\label{sec:plotPath}
496
-NetPathMiner offers several plotting options for networks and ranked paths. First, we can plot our network colouring vertices by their cellular compartment.
497
-
498
-<<echo=TRUE, eval=TRUE>>=
499
-plotNetwork(rgraph, vertex.color="compartment.name")
500
-@
501
-
502
-NetPathMiner's plotPaths function can be used to view ranked paths on the network structure. Cluster information can also be provided, so that paths belonging to the same cluster will have the same colour.
503
-
504
-<<fig=TRUE, pdf=TRUE, echo=TRUE, eval=FALSE>>=
505
-plotPaths(ranked.p, rgraph)
506
-
507
-# With clusters
508
-plotPaths(ranked.p, graph, path.clusters=p.class)
509
-@
510
-
511
-To view paths on different network representations, you can pass the networks as parameters to plotPaths, and it will do the job.
512
-
513
-<<fig=TRUE, pdf=TRUE, echo=TRUE, eval=TRUE>>=
514
-plotAllNetworks(ranked.p, metabolic.net = graph, reaction.net = rgraph,
515
-		path.clusters=p.class, vertex.label = "", vertex.size = 4)
516
-@
517
-
518
-To make use of the annotation attributes, NetPathMiner can layout vertices such that those sharing a common attribute value are plotted close to each other, and using similar colors.
519
-
520
-<<echo=TRUE, eval=FALSE>>=
521
-layout.c <- clusterVertexByAttr(rgraph, "pathway", cluster.strength = 3)
522
-v.color <- colorVertexByAttr(rgraph, "pathway")
523
-plotPaths(ranked.p , rgraph, clusters=p.class,
524
-	layout = layout.c, vertex.color = v.color)
525
-@
526
-
527
-Finally, for interactive visualization using Cytoscape, plotCytoscapeGML can export the graph, attributes and layout as a GML file, which can be imported directly into Cytoscape. For example:
528
-
529
-<<echo=TRUE, eval=FALSE>>=
530
-plotCytoscapeGML(graph, file="example.gml", layout = layout.c,
531
-				vertex.size = 5, vertex.color = v.color)
532
-@
533
-
534
-\section{Additional functions}
535
-\subsection{Genesets and geneset subnetworks}
536
-NetPathMiner provides functions to extract genesets utilizing annotation attributes in the network. To get genesets as lists of genes for geneset enrichment analyses:
537
-
538
-<<echo=TRUE, eval=TRUE, results=hide>>=
539
-getGeneSets(graph, use.attr="compartment", gene.attr="miriam.uniprot")
540
-@
541
-
542
-Alternatively, genesets can be obtained as network structures.
543
-
544
-<<echo=TRUE, eval=TRUE, results=hide>>=
545
-getGeneSetNetworks(graph, use.attr="compartment")
546
-@
547
-
548
-\subsection{Integration with graph package}
549
-All networks constructed in NetPathMiner are represented as igraph object. Users can convert these networks to Bioconductor's graphNEL object using ``toGraphNEL'' function
550
-
551
-<<echo=TRUE, eval=FALSE>>=
552
-graphNEL <- toGraphNEL(graph, export.attr="^miriam.")
553
-@
554
-
555
-
556
-\bibliographystyle{plain}  % Style BST file
557
-%\bibliography{references}     % Bibliography file (usually '*.bib' )
558
-\end{document}
559
-
560
-%
561
-%   end of file
562
-%
563
-%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
564 0
deleted file mode 100755
565 1
Binary files a/vignettes/ROCplot.pdf and /dev/null differ
566 2
new file mode 100644
567 3
Binary files /dev/null and b/vignettes/ROCplot.png differ