Browse code

0.99.3

Bioconductor, No errors/warnings.

amfy10 authored on 09/04/2014 09:29:08
Showing 36 changed files

1 1
old mode 100755
2 2
new mode 100644
... ...
@@ -1,5 +1,5 @@
1 1
 Package: NetPathMiner
2
-Version: 0.99.0
2
+Version: 0.99.3
3 3
 Date: 2014 onwards
4 4
 Title: NetPathMiner for Biological Network Construction, Path Mining
5 5
         and Visualization
... ...
@@ -15,12 +15,12 @@ Description: NetPathMiner is a general framework for network path mining using
15 15
     provides static and interactive visualizations of networks and paths to aid
16 16
     manual investigation.
17 17
 Depends: igraph (>= 0.6)
18
-Suggests: rBiopaxParser, RCurl, RCytoscape
18
+Suggests: rBiopaxParser (>= 2.1), RCurl, RCytoscape
19 19
 License: GPL (>= 2)
20 20
 URL: https://github.com/ahmohamed/NetPathMiner
21 21
 NeedsCompilation: yes
22
-SystemRequurements: libxml2, libSBML (>= 5.5)
22
+SystemRequirements: libxml2, libSBML (>= 5.5)
23
+Biarch: TRUE
23 24
 biocViews: GraphAndNetwork, Pathways, Network, Clustering,
24 25
         Classification
25
-Biarch: TRUE
26
-Packaged: 2014-03-10 09:06:56 UTC; mohamedahmed
26
+Packaged: 2014-04-09 08:45:28 UTC; ahmedmohamed
... ...
@@ -66,7 +66,6 @@ check.file <- function(filename, ext=".xml"){
66 66
 #' 
67 67
 #'     # Process KGML file as a signaling network
68 68
 #'     g <- KGML2igraph(filename, parse.as="signaling", expand.complexes=TRUE)
69
-#'     dev.new()
70 69
 #'     plotNetwork(g)
71 70
 #' }
72 71
 #' 
... ...
@@ -97,13 +96,19 @@ KGML2igraph <- function(filename, parse.as=c("metabolic","signaling"), expand.co
97 96
                         function(x) .Call("readkgmlfile", FILENAME = x, VERBOSE=verbose)
98 97
             , USE.NAMES=FALSE), recursive=FALSE)
99 98
         
100
-        #Resolve reactions particiapting in multiple pathways
101
-        dup.rns = lapply(zkgml[duplicated(names(zkgml))], "[[", "miriam.kegg.pathway")
99
+        dup.zkgml <- duplicated(names(zkgml))
100
+        dup.rns <- sapply(zkgml[dup.zkgml], "[[", "miriam.kegg.pathway")
101
+        zkgml <- zkgml[!dup.zkgml] # Remove duplicated reactions.
102
+        
103
+        
102 104
         if(length(dup.rns)>0){
103
-            lapply(1:length(dup.rns), 
104
-                function(x) zkgml[[ names(dup.rns)[x] ]]$miriam.kegg.pathway <<- 
105
-                            unique( c(zkgml[[ names(dup.rns)[x] ]]$miriam.kegg.pathway, dup.rns[[x]] )
106
-                ))            
105
+            dup.rns <- split( unname(dup.rns), names(dup.rns))	# contains pathway info for removed rns.
106
+            zkgml[names(dup.rns)] <- mapply(
107
+                                    function(x, dup){
108
+                                        x$miriam.kegg.pathway <- c(x$miriam.kegg.pathway, dup)
109
+                                        return(x)
110
+                                    }, zkgml[names(dup.rns)], dup.rns, 
111
+                                    SIMPLIFY=FALSE)			
107 112
         }
108 113
     }
109 114
     
... ...
@@ -252,14 +257,21 @@ SBML2igraph <- function(filename, parse.as=c("metabolic","signaling"), miriam.at
252 257
         names(zsbml) <- c("reactions", "species")
253 258
         
254 259
         #Resolve reactions and species particiapting in multiple pathways
255
-        dup.rns = lapply(zsbml$reactions[duplicated(names(zsbml$reactions))], "[[", "pathway")
260
+        dup.zsbml <- duplicated(names(zsbml$reactions))
261
+        dup.rns <- sapply(zsbml$reactions[dup.zsbml], "[[", "pathway")
262
+        zsbml$reactions <- zsbml$reactions[!dup.zsbml] # Remove duplicated reactions.
263
+        
264
+        
256 265
         if(length(dup.rns)>0){
257
-            lapply(1:length(dup.rns), 
258
-                    function(x) zsbml$reactions[[ names(dup.rns)[x] ]]$pathway <<- 
259
-                                unique( c(zsbml$reactions[[ names(dup.rns)[x] ]]$pathway, dup.rns[[x]] )
260
-                                ))            
266
+            dup.rns <- split( unname(dup.rns), names(dup.rns))	# contains pathway info for removed rns.
267
+            zsbml$reactions[names(dup.rns)] <- mapply(
268
+                    function(x, dup){
269
+                        x$pathway <- c(x$pathway, dup)
270
+                        return(x)
271
+                    }, zsbml$reactions[names(dup.rns)], dup.rns, 
272
+                    SIMPLIFY=FALSE)		
261 273
         }
262
-    
274
+            
263 275
         zsbml$species <- zsbml$species[!duplicated(names(zsbml$species))]
264 276
     }
265 277
     if(verbose) message("SBML files processed successfully")
... ...
@@ -384,7 +396,9 @@ biopax2igraph <- function(biopax, parse.as=c("metabolic","signaling"),
384 396
     if (!require(rBiopaxParser))
385 397
         stop("This functions needs the rBiopaxParser library installed. Check out the installation instructions!")
386 398
     if (!("biopax" %in% class(biopax))) 
387
-        stop("Error: pathway2RegulatoryGraph: parameter biopax has to be of class biopax.")
399
+        stop("Error: biopax2igraph: parameter biopax has to be of class biopax.")
400
+    
401
+    biopax$df <- as.data.frame(biopax$dt)
388 402
     if(missing(parse.as) || parse.as=="metabolic"){
389 403
         if(biopax$biopaxlevel == 3)
390 404
             return(bpMetabolicL3(biopax, verbose))
... ...
@@ -400,6 +414,8 @@ biopax2igraph <- function(biopax, parse.as=c("metabolic","signaling"),
400 414
 
401 415
 bpMetabolicL3 <- function(biopax, verbose){
402 416
     if(verbose) message("Processing BioPAX (level 3) object as a metabolic network", appendLF=FALSE) 
417
+    to.df <- function(dt) return(as.data.frame(dt))
418
+    
403 419
     df <- biopax$df
404 420
     df$property = tolower(df$property)
405 421
     
... ...
@@ -413,9 +429,9 @@ bpMetabolicL3 <- function(biopax, verbose){
413 429
     # Metabolic reactions takes only small molecules as substrates/products.
414 430
     # The following lines removes any Biochemical reactions with non-small molecules
415 431
     #   participants.
416
-    classes <- listInstances(biopax,lefts[,1])
432
+    classes <- df[ rBiopaxParser::selectInstances(biopax, lefts[,1], returnValues=FALSE), c("class", "id")]
417 433
     sig.reactions <- lefts[match(classes$id, lefts[,1])[classes$class !="SmallMolecule"],2]
418
-    classes <- listInstances(biopax,rights[,2])
434
+    classes <- df[ rBiopaxParser::selectInstances(biopax, rights[,2], returnValues=FALSE), c("class", "id")]
419 435
     sig.reactions <- unlist(list(sig.reactions, 
420 436
                     rights[ match(classes$id, rights[,2])[classes$class !="SmallMolecule"], 1]))
421 437
     
... ...
@@ -432,13 +448,13 @@ bpMetabolicL3 <- function(biopax, verbose){
432 448
         
433 449
     XRefs <- bpGetReferences(biopax, V(graph)$name)
434 450
     names(XRefs) <- V(graph)$name
435
-    cat.r <- striph(selectInstances(biopax, class="Catalysis", property="controlled")$property_attr_value)
436
-    cat.gene <- striph(selectInstances(biopax, class="Catalysis", property="controller")$property_attr_value)
451
+    cat.r <- striph(to.df(rBiopaxParser::selectInstances(biopax, class="Catalysis", property="controlled"))$property_attr_value)
452
+    cat.gene <- striph(to.df(rBiopaxParser::selectInstances(biopax, class="Catalysis", property="controller"))$property_attr_value)
437 453
     
438 454
     gene.xref <- bpGetReferences(biopax, cat.gene)
439 455
     names(gene.xref) <- cat.r
440
-    lapply(names(gene.xref), function(x) XRefs[[x]] <<- c(XRefs[[x]],gene.xref[[x]]))
441
-    
456
+    XRefs[names(gene.xref)] <- mapply(c, XRefs[names(gene.xref)], gene.xref, SIMPLIFY=FALSE)
457
+
442 458
     ##############################################################
443 459
     # Getting attribute lists (name, compartment, pathway, MIRIAM)
444 460
     # For reactions (name, reactants, reactant.stoichiometry, products, product.stoichiomentry,
... ...
@@ -448,17 +464,17 @@ bpMetabolicL3 <- function(biopax, verbose){
448 464
     attr <- bpGetAnnFromXRef(df, XRefs[V(graph)$name])
449 465
     
450 466
     # Name attributes
451
-    v.names <- listInstances(biopax, id=V(graph)$name)
467
+    v.names <- to.df(rBiopaxParser::listInstances(biopax, id=V(graph)$name))
452 468
     v.names <- v.names[match(V(graph)$name, v.names$id), "name"]
453 469
     
454 470
     # Pathway attributes##########################
455 471
     ## Get Pathway name and annotations
456
-    pw <- listInstances(biopax, class="pathway")
472
+    pw <- to.df(rBiopaxParser::listInstances(biopax, class="pathway"))
457 473
     pwXRef <- bpGetReferences(biopax, pw$id)
458 474
     #pw.ann <- bpGetAnnFromXRef(df, pwXRef)
459 475
     
460 476
     ## Get pathway components (only reactions are returned)
461
-    pwcomp <- lapply(pw$id, function(x)listPathwayComponents(biopax,x, returnIDonly=TRUE))
477
+    pwcomp <- lapply(pw$id, function(x)rBiopaxParser::listPathwayComponents(biopax,x, returnIDonly=TRUE))
462 478
     pwcomp <- do.call("rbind", lapply(1:length(pwcomp), 
463 479
                     function(x)data.frame(id=x, comp=pwcomp[[x]])))
464 480
     
... ...
@@ -485,7 +501,7 @@ bpMetabolicL3 <- function(biopax, verbose){
485 501
     ## while reactions inherit them from their catalysts.
486 502
     
487 503
     ## Get Compartment name and annotations
488
-    comp <- listInstances(biopax, class="cellularLocationvocabulary", returnIDonly=TRUE)
504
+    comp <- rBiopaxParser::listInstances(biopax, class="cellularLocationvocabulary", returnIDonly=TRUE)
489 505
     comp.terms <- as.character(bpGetAttrbyID(df, comp, "term")$property_value)
490 506
     #compXRef <- bpGetReferences(biopax, comp)
491 507
     comp.ann <- bpGetAnnFromXRef(df, bpGetReferences(biopax, comp) )
... ...
@@ -512,7 +528,7 @@ bpMetabolicL3 <- function(biopax, verbose){
512 528
     ##Products
513 529
     products <- split(rights[,2], rights[,1], drop=TRUE)
514 530
     ##Genes
515
-    cat.gene.name <- listInstances(biopax,cat.gene)
531
+    cat.gene.name <- to.df(rBiopaxParser::listInstances(biopax,cat.gene))
516 532
     cat.gene.name <- cat.gene.name[match(cat.gene,cat.gene.name$id),"name"]
517 533
     genes <- split(cat.gene.name, cat.r, drop=TRUE)
518 534
     
... ...
@@ -525,7 +541,9 @@ bpMetabolicL3 <- function(biopax, verbose){
525 541
     
526 542
     edges <- rbind(lefts,rights)
527 543
     edges<- cbind(edges, st=NA)
528
-    apply(st[,c(1,4,5)], 1, function(x) edges[edges$id==x[[1]] & edges$property_attr_value==x[[2]],"st"] <<-x[[3]])
544
+    for(i in 1:nrow(st)){
545
+        edges[ edges[,1]==st[i,4] & edges[,2]==st[i,1], "st"] <- as.character(st[i,5])
546
+    }
529 547
     edges$st <- as.numeric(edges$st)
530 548
     
531 549
     r.stoic <- split(edges[1:nrow(lefts),3], edges[1:nrow(lefts),2], drop=TRUE)
... ...
@@ -594,6 +612,7 @@ bpMetabolicL3 <- function(biopax, verbose){
594 612
 
595 613
 bpMetabolicL2 <- function(biopax, verbose){
596 614
     if(verbose) message("Processing BioPAX (level 2) object as a metabolic network", appendLF=FALSE)
615
+    to.df <- function(dt) return(as.data.frame(dt))
597 616
     
598 617
     df <- biopax$df
599 618
     df$property = tolower(df$property)
... ...
@@ -615,13 +634,13 @@ bpMetabolicL2 <- function(biopax, verbose){
615 634
     
616 635
     XRefs <- bpGetReferences(biopax, V(graph)$name)
617 636
     names(XRefs) <- V(graph)$name
618
-    cat.r <- striph(selectInstances(biopax, class="Control", property="controlled")$property_attr_value)
619
-    cat.gene <- striph(selectInstances(biopax, class="Control", property="controller")$property_attr_value)
637
+    cat.r <- striph(to.df(rBiopaxParser::selectInstances(biopax, class="Control", property="controlled"))$property_attr_value)
638
+    cat.gene <- striph(to.df(rBiopaxParser::selectInstances(biopax, class="Control", property="controller"))$property_attr_value)
620 639
     
621 640
     gene.xref <- bpGetReferences(biopax, cat.gene, followProperties="physical-entity")#
622 641
     names(gene.xref) <- cat.r
623
-    lapply(names(gene.xref), function(x) XRefs[[x]] <<- c(XRefs[[x]],gene.xref[[x]]))
624
-    
642
+    XRefs[names(gene.xref)] <- mapply(c, XRefs[names(gene.xref)], gene.xref, SIMPLIFY=FALSE)
643
+
625 644
     ##############################################################
626 645
     # Getting attribute lists (name, compartment, pathway, MIRIAM)
627 646
     # For reactions (name, reactants, reactant.stoichiometry, products, product.stoichiomentry,
... ...
@@ -631,17 +650,17 @@ bpMetabolicL2 <- function(biopax, verbose){
631 650
     attr <- bpGetAnnFromXRef(df, XRefs[V(graph)$name])
632 651
     
633 652
     # Name attributes
634
-    v.names <- listInstances(biopax, id=V(graph)$name)
653
+    v.names <- to.df(rBiopaxParser::listInstances(biopax, id=V(graph)$name))
635 654
     v.names <- v.names[match(V(graph)$name, v.names$id), "name"]
636 655
     
637 656
     # Pathway attributes##########################
638 657
     ## Get Pathway name and annotations
639
-    pw <- listInstances(biopax, class="pathway")
658
+    pw <- rBiopaxParser::listInstances(biopax, class="pathway")
640 659
     pwXRef <- bpGetReferences(biopax, pw$id)
641 660
     #pw.ann <- bpGetAnnFromXRef(df, pwXRef)
642 661
     
643 662
     ## Get pathway components (only reactions are returned)
644
-    pwcomp <- lapply(pw$id, function(x)listPathwayComponents(biopax,x, returnIDonly=TRUE))
663
+    pwcomp <- lapply(pw$id, function(x)rBiopaxParser::listPathwayComponents(biopax,x, returnIDonly=TRUE))
645 664
     pwcomp <- do.call("rbind", lapply(1:length(pwcomp), 
646 665
                     function(x)data.frame(id=x, comp=pwcomp[[x]])))
647 666
     
... ...
@@ -668,7 +687,7 @@ bpMetabolicL2 <- function(biopax, verbose){
668 687
     ## while reactions inherit them from their catalysts.
669 688
     
670 689
     ## Get Pathway name and annotations
671
-    comp <- listInstances(biopax, class="openControlledVocabulary", returnIDonly=TRUE)#
690
+    comp <- rBiopaxParser::listInstances(biopax, class="openControlledVocabulary", returnIDonly=TRUE)#
672 691
     comp.terms <- as.character(bpGetAttrbyID(df, comp, "term")$property_value)
673 692
     compXRef <- bpGetReferences(biopax, comp)#
674 693
     #comp.ann <- bpGetAnnFromXRef(df, bpGetReferences(biopax, comp) )
... ...
@@ -705,7 +724,7 @@ bpMetabolicL2 <- function(biopax, verbose){
705 724
     products <- split(rights[,2], rights[,1], drop=TRUE)
706 725
     ##Genes ##totally different from level3 function
707 726
     cat.gene.ref <- bpGetAttrbyID(df,cat.gene, "physical-entity", "property_attr_value")
708
-    cat.gene.name <- listInstances(biopax, cat.gene.ref[,3])
727
+    cat.gene.name <- to.df(rBiopaxParser::listInstances(biopax, cat.gene.ref[,3]))
709 728
     cat.gene.ref$name <- cat.gene.name$name[match(striph(cat.gene.ref[,3]), cat.gene.name$id)]
710 729
     
711 730
     cat.gene.ref <- cat.gene.ref[match(cat.gene,cat.gene.ref$id),"name"]    
... ...
@@ -790,6 +809,7 @@ bpMetabolicL2 <- function(biopax, verbose){
790 809
 # TODO: edge attributes in signaling networks
791 810
 bpSignalingL3 <- function(biopax, expand.complexes=FALSE, inc.sm.molecules=FALSE, verbose=TRUE){
792 811
     if(verbose) message("Processing BioPAX (level 3) object as a signaling network", appendLF=FALSE) 
812
+    to.df <- function(dt) return(as.data.frame(dt))
793 813
     df <- biopax$df
794 814
     df$property = tolower(df$property)
795 815
     
... ...
@@ -803,15 +823,15 @@ bpSignalingL3 <- function(biopax, expand.complexes=FALSE, inc.sm.molecules=FALSE
803 823
     # Identifying Metabolic and signaling reactions.
804 824
     # Metabolic reactions takes only small molecules as substrates/products.
805 825
     # Signaling reactions have at least one non-small-molecule participant.  
806
-    classes.left <- listInstances(biopax,lefts[,1])
826
+    classes.left <- df[ rBiopaxParser::selectInstances(biopax, lefts[,1], returnValues=FALSE), c("class", "id")]
807 827
     sig.reactions <- lefts[match(classes.left$id, lefts[,1])[classes.left$class !="SmallMolecule"],2]
808
-    classes.right <- listInstances(biopax,rights[,2])
828
+    classes.right <- df[ rBiopaxParser::selectInstances(biopax, rights[,2], returnValues=FALSE), c("class", "id")]
809 829
     sig.reactions <- unlist(list(sig.reactions, 
810 830
                     rights[ match(classes.right$id, rights[,2])[classes.right$class !="SmallMolecule"], 1]))
811 831
     
812 832
     
813
-    controlled <- striph(selectInstances(biopax, class="Catalysis", property="controlled")$property_attr_value)
814
-    controller <- striph(selectInstances(biopax, class="Catalysis", property="controller")$property_attr_value)
833
+    controlled <- striph(to.df(rBiopaxParser::selectInstances(biopax, class="Catalysis", property="controlled"))$property_attr_value)
834
+    controller <- striph(to.df(rBiopaxParser::selectInstances(biopax, class="Catalysis", property="controller"))$property_attr_value)
815 835
     
816 836
     
817 837
     # Metabolic reactions are represented in signaling networks by their "Controller"
... ...
@@ -865,7 +885,7 @@ bpSignalingL3 <- function(biopax, expand.complexes=FALSE, inc.sm.molecules=FALSE
865 885
     sig.vertices <- unique(all.sig)
866 886
     
867 887
     # Combining the signaling reactions with the metabolic one.
868
-    graph <- graph + vertices(sig.vertices[!sig.vertices %in% V(graph)$name]) + igraph::edges(all.sig) 
888
+    graph <- graph + vertices(sig.vertices[!sig.vertices %in% V(graph)$name], attr=list(list())) + igraph::edges(all.sig) 
869 889
     
870 890
     if(expand.complexes){
871 891
         comsp <- bpSplitComplex(biopax,V(graph)$name, inc.sm.molecules)
... ...
@@ -887,22 +907,22 @@ bpSignalingL3 <- function(biopax, expand.complexes=FALSE, inc.sm.molecules=FALSE
887 907
     attr <- bpGetAnnFromXRef(df, XRefs[V(graph)$name])
888 908
     
889 909
     # Name attributes
890
-    v.names <- listInstances(biopax, id=V(graph)$name)
910
+    v.names <- to.df(rBiopaxParser::listInstances(biopax, id=V(graph)$name))
891 911
     v.names <- v.names[match(V(graph)$name, v.names$id), "name"]
892 912
     
893 913
     ## Get Pathway name and annotations
894
-    pw <- listInstances(biopax, class="pathway")
914
+    pw <- to.df(rBiopaxParser::listInstances(biopax, class="pathway"))
895 915
     pwXRef <- bpGetReferences(biopax, pw$id)
896 916
     
897 917
     ## Get pathway components (only reactions are returned)
898
-    pwcomp <- lapply(pw$id, function(x)listPathwayComponents(biopax,x, returnIDonly=FALSE))
918
+    pwcomp <- lapply(pw$id, function(x) rBiopaxParser::listPathwayComponents(biopax,x, returnIDonly=TRUE))
899 919
     pwcomp <- do.call("rbind", lapply(1:length(pwcomp), 
900 920
                     function(x)data.frame(id=x, comp=pwcomp[[x]])))
901 921
     
902 922
     ## Restrict Pathway components to Conversion reactions (Removing PathwayStep, Control).
903
-    pwcomp <- pwcomp[pwcomp$comp.class %in% c("Conversion", getSubClasses("Conversion", biopaxlevel=3)) ,]
923
+    pwcomp <- pwcomp[pwcomp$comp %in% rBiopaxParser::listInstances(biopax, class="Conversion", includeSubClasses=TRUE, returnIDonly=TRUE),]
904 924
     
905
-    pwcomp <- split(pwcomp$id, pwcomp$comp.id, drop=TRUE)
925
+    pwcomp <- split(pwcomp$id, pwcomp$comp, drop=TRUE)
906 926
     
907 927
     ## Since Conversions (reactions) are no longer present in the network 
908 928
     #   (either their controllers or substrate/products are retained), vertices inherit
... ...
@@ -922,7 +942,7 @@ bpSignalingL3 <- function(biopax, expand.complexes=FALSE, inc.sm.molecules=FALSE
922 942
     
923 943
     ## Compartment attributes #######################
924 944
     ### Get Compartment name and annotations
925
-    comp <- listInstances(biopax, class="cellularLocationvocabulary", returnIDonly=TRUE)
945
+    comp <- rBiopaxParser::listInstances(biopax, class="cellularLocationvocabulary", returnIDonly=TRUE)
926 946
     comp.terms <- as.character(bpGetAttrbyID(df, comp, "term")$property_value)
927 947
     comp.ann <- bpGetAnnFromXRef(df, bpGetReferences(biopax, comp) )
928 948
     
... ...
@@ -1005,7 +1025,7 @@ bpSplitComplex<-function (biopax, complexid, inc.sm.molecules)
1005 1025
         return(NULL)
1006 1026
     
1007 1027
     ref = do.call("rbind", lapply( na.omit(names(ref)), function(x) cbind( x, striph(ref[[x]]) ) ) )
1008
-    referenced = listInstances(biopax, id = unique(ref[,2]))
1028
+    referenced = biopax$df[rBiopaxParser::selectInstances(biopax, id = unique(ref[,2]), returnValues=FALSE), c("class", "id")]
1009 1029
     sel = referenced[ tolower(referenced$class) %in% classes, "id"]
1010 1030
     if (length(sel)==0) 
1011 1031
         return(NULL)
... ...
@@ -246,7 +246,7 @@ vertexDeleteReconnect <- function(graph, vids, reconnect.threshold=vcount(graph)
246 246
     #Get Actual shortest paths for vertices that passed the threshold, to copy edge attributes.
247 247
     attr <- NULL
248 248
     if(!is.null(copy.attr)){
249
-        paths <- mapply(function(from, to) get.shortest.paths(graph.sub, from, to, output="both",mode="out")$vpath,
249
+        paths <- mapply(function(from, to) igraph::get.shortest.paths(graph.sub, from, to, output="both",mode="out")$vpath,
250 250
                         new.edges[1,], new.edges[2,])
251 251
         
252 252
         if(!is.list(copy.attr)) copy.attr <- sapply(list.edge.attributes(graph.sub), function(x)copy.attr)
... ...
@@ -374,7 +374,9 @@ expandComplexes <- function(graph, v.attr,
374 374
     }
375 375
 
376 376
     gout <- setAttribute(gout, v.attr, V(gout)$name)
377
-    lapply(list.edge.attributes(graph), function(x) gout<<-set.edge.attribute(gout, x, value=get.edge.attribute(graph, x)[z$e.parents] ))
377
+    for(i in list.edge.attributes(graph)){
378
+        gout <- set.edge.attribute(gout, i, value=get.edge.attribute(graph, i)[z$e.parents] )
379
+    }
378 380
     return(gout);
379 381
 }
380 382
 
... ...
@@ -98,7 +98,9 @@ setAttribute <- function(graph, attr.name, attr.value){
98 98
     if(is.null(attr))
99 99
         attr<-rep(list(list()), vcount(graph))    #initialize the attr as lists.
100 100
     
101
-    lapply(1:vcount(graph), function(i) attr[[i]][attr.name] <<- attr.value[i])
101
+    attr <- mapply(function(attr_, attr_val){
102
+                        attr_[[attr.name]] <- attr_val; return(attr_);
103
+                    }, attr, attr.value, SIMPLIFY=FALSE)
102 104
     V(graph)$attr <- attr
103 105
     return(graph)
104 106
 }
... ...
@@ -113,8 +115,8 @@ setAttribute <- function(graph, attr.name, attr.value){
113 115
 rmAttribute <- function(graph, attr.name){
114 116
     if(is.null(V(graph)$attr))
115 117
         stop("Graph is not annotated.")
116
-
117
-    lapply(1:vcount(graph), function(i) V(graph)$attr[[i]][attr.name] <<- NULL)
118
+    
119
+    V(graph)$attr <- lapply(V(graph)$attr, function(x) {x[[attr.name]] <- NULL; return(x);})
118 120
     return(graph)
119 121
 }
120 122
 
... ...
@@ -188,7 +190,7 @@ stdAttrNames <- function(graph, return.value=c("matches", "graph")){
188 190
 fetchAttribute <- function(graph, organism="Homo sapiens", target.attr, source.attr, bridge.web=NPMdefaults("bridge.web")){
189 191
     if(!require(RCurl))
190 192
         stop("This function uses RCurl package. Required package not installed.")
191
-    if(!url.exists(bridge.web))
193
+    if(!RCurl::url.exists(bridge.web))
192 194
         stop("Couldn't access BridgeDB webservice.\nThere may be a internet connection problem, or the server is down.")    
193 195
     if(!organism %in% NPMdefaults("bridge.organisms"))
194 196
         stop(organism, " is not supported. Here are supported organisms:\n",
... ...
@@ -228,7 +230,7 @@ fetchAttribute <- function(graph, organism="Homo sapiens", target.attr, source.a
228 230
                         ))
229 231
         
230 232
         uris = paste(base.urls[i],"/", unique(s.attr[,2]), "?dataSource=", t.code,sep="")
231
-        query = lapply(getURI(uris, async=TRUE, verbose=TRUE), 
233
+        query = lapply(RCurl::getURI(uris, async=TRUE, verbose=TRUE), 
232 234
                     function(x) if(x!="") as.character(read.table(text=x)$V1) )
233 235
         
234 236
         s.attr[,2] <- match(s.attr[,2], unique(s.attr[,2]))
... ...
@@ -422,7 +424,7 @@ assignEdgeWeights <- function(microarray, graph, use.attr, y, weight.method="com
422 424
         # Add missing values.
423 425
         if(length(missing)>0){
424 426
             missing.val <- ms.func(na.omit(edge.weights[!samegenes,1]))
425
-            edge.weight <- rbind(edge.weights,cbind(edge.weights=NA, id=missing))            
427
+            edge.weights <- rbind(edge.weights,cbind(edge.weights=missing.val, id=missing))            
426 428
         }
427 429
         
428 430
         # Complexes
... ...
@@ -577,7 +579,10 @@ toGraphNEL<- function(graph, export.attr=""){
577 579
     attr.names  <- grep(export.attr, attr.names, value=TRUE)
578 580
     
579 581
     new.graph <- remove.vertex.attribute(graph, "attr")
580
-    lapply(attr.names, function(x) new.graph <<- set.vertex.attribute(new.graph, x, value=getAttribute(graph, x)))
582
+    
583
+    for(i in attr.names){
584
+        new.graph <- set.vertex.attribute(new.graph, i, value=getAttribute(graph, i))
585
+    }
581 586
     
582 587
     return(igraph.to.graphNEL(new.graph))
583 588
 }
... ...
@@ -47,6 +47,9 @@
47 47
 pathsToBinary <- function(ypaths) {
48 48
   makeBin <- function(pathGenes,allGenes) return(as.numeric(allGenes %in% pathGenes$genes))
49 49
 
50
+  if(length(ypaths$path)==0){
51
+    stop("ypaths is a an empty list. Please rerun pathRanker with different parameters.")
52
+  }
50 53
   # if there are response labels
51 54
   if (!is.null(names(ypaths$paths))) { 
52 55
     all.genes <- c()
... ...
@@ -56,6 +59,8 @@ pathsToBinary <- function(ypaths) {
56 59
     
57 60
     resp <- c()
58 61
     for (p in 1:length(ypaths$paths)) {
62
+      if(length(ypaths$paths[[p]])==0) next;
63
+      
59 64
       binpaths <- data.frame(t(sapply(ypaths$paths[[p]],makeBin,allGenes = all.genes)))
60 65
       names(binpaths) <- all.genes
61 66
 
... ...
@@ -48,11 +48,11 @@
48 48
 #' 
49 49
 #' 	## Get ranked paths using probabilistic shortest paths.
50 50
 #'  ranked.p <- pathRanker(rgraph, method="prob.shortest.path", 
51
-#' 					K=20, minPathSize=6)
51
+#' 					K=20, minPathSize=8)
52 52
 #' 	
53 53
 #' 	## Convert paths to binary matrix. 
54 54
 #' 	ybinpaths <- pathsToBinary(ranked.p)
55
-#' 	p.cluster <- pathCluster(ybinpaths, M=3)
55
+#' 	p.cluster <- pathCluster(ybinpaths, M=2)
56 56
 #' 	plotClusters(ybinpaths, p.cluster)
57 57
 #'  
58 58
 pathCluster <- function(ybinpaths, M, iter=1000) {
... ...
@@ -149,11 +149,11 @@ pathCluster <- function(ybinpaths, M, iter=1000) {
149 149
 #' 
150 150
 #' 	## Get ranked paths using probabilistic shortest paths.
151 151
 #'  ranked.p <- pathRanker(rgraph, method="prob.shortest.path", 
152
-#' 					K=20, minPathSize=6)
152
+#' 					K=20, minPathSize=8)
153 153
 #' 	
154 154
 #' 	## Convert paths to binary matrix. 
155 155
 #' 	ybinpaths <- pathsToBinary(ranked.p)
156
-#' 	p.cluster <- pathCluster(ybinpaths, M=3)
156
+#' 	p.cluster <- pathCluster(ybinpaths, M=2)
157 157
 #' 
158 158
 #' 	## just an example of how to predict cluster membership.
159 159
 #' 	pclust.pred <- predictPathCluster(p.cluster,ybinpaths$paths)
... ...
@@ -217,11 +217,11 @@ predictPathCluster <- function(pfit,newdata) {
217 217
 #' 
218 218
 #' 	## Get ranked paths using probabilistic shortest paths.
219 219
 #'  ranked.p <- pathRanker(rgraph, method="prob.shortest.path", 
220
-#' 					K=20, minPathSize=6)
220
+#' 					K=20, minPathSize=8)
221 221
 #' 	
222 222
 #' 	## Convert paths to binary matrix. 
223 223
 #' 	ybinpaths <- pathsToBinary(ranked.p)
224
-#' 	p.cluster <- pathCluster(ybinpaths, M=3)
224
+#' 	p.cluster <- pathCluster(ybinpaths, M=2)
225 225
 #' 	plotPathCluster(ybinpaths, p.cluster, m=2, tol=0.05)
226 226
 #'  
227 227
 plotPathCluster <- function(ybinpaths, clusters, m, tol = NULL) {
... ...
@@ -377,12 +377,12 @@ plotClusterProbs <- function(clusters, col=rainbow(clusters$params$M)){
377 377
 #' 
378 378
 #' 	## Get ranked paths using probabilistic shortest paths.
379 379
 #'  ranked.p <- pathRanker(rgraph, method="prob.shortest.path", 
380
-#' 					K=20, minPathSize=6)
380
+#' 					K=20, minPathSize=8)
381 381
 #' 	
382 382
 #' 	## Convert paths to binary matrix. 
383 383
 #' 	ybinpaths <- pathsToBinary(ranked.p)
384
-#' 	p.cluster <- pathCluster(ybinpaths, M=3)
385
-#' 	plotClusters(ybinpaths, p.cluster, col=c("red", "green", "blue") )
384
+#' 	p.cluster <- pathCluster(ybinpaths, M=2)
385
+#' 	plotClusters(ybinpaths, p.cluster, col=c("red", "blue") )
386 386
 #'  
387 387
 plotClusters <- function(ybinpaths, clusters, col,...){
388 388
 	if(missing(col)) 
... ...
@@ -97,17 +97,19 @@ extractPathNetwork <- function(paths, graph){
97 97
 #' 
98 98
 getPathsAsEIDs <- function(paths, graph){
99 99
     if(length(paths$y.labels)>1){
100
-        eids = lapply(paths$paths, getPaths, graph, paths$source.net)            
100
+        eids <- lapply(paths$paths, getPaths, graph, paths$source.net)            
101 101
         names(eids) = paths$y.labels
102 102
         
103 103
     }else{
104
-        eids = getPaths(paths$paths, graph, paths$source.net)        
104
+        eids <- getPaths(paths$paths, graph, paths$source.net)        
105 105
     }
106 106
     return(eids)
107 107
 }        
108 108
 
109 109
 
110 110
 getPaths <- function(paths, graph, source.net){
111
+    if(length(paths)==0) return(list())
112
+
111 113
     # graph source unknown
112 114
     if(is.null(graph$type) || is.null(source.net))
113 115
         return(lapply(paths, function(x) E(graph,path=x$genes)))
... ...
@@ -138,7 +140,7 @@ getPaths <- function(paths, graph, source.net){
138 140
     # It must be MR.graph
139 141
     eid <- list()
140 142
     for(i in 1:length(paths)){
141
-        deleted.edges = unlist(lapply(lapply(grep("->",paths[[i]]$compounds),
143
+        deleted.edges <- unlist(lapply(lapply(grep("->",paths[[i]]$compounds),
142 144
                                 function(x) unlist(strsplit(paths[[i]]$compounds[[x]], "->"))), 
143 145
                         function(y) mapply(
144 146
                                     function(from,to)get.shortest.paths(graph, from, to, mode="out", output="epath"), 
... ...
@@ -289,15 +291,24 @@ rankShortestPaths <- function(graph, K=10, minPathSize=1, start, end, normalize
289 291
                 K=K,minpathsize = minPathSize+2)    #add 2 nodes to min path length ("s" & "t")
290 292
         
291 293
         
294
+                
292 295
         idx <- which(sapply(ps,is.null))        
293 296
         if (length(idx)>0) ps <- ps[-idx]
297
+        if(length(ps)==0){
298
+            if(ncol(pg$weights) > 1)
299
+                message("  Warning:Counldn't find paths matching the criteria for ",graph$y.labels[i])
300
+            else message("  Warning:Counldn't find paths matching the criteria.")
301
+        }
294 302
         
295 303
         ps <- ps[order(sapply(ps,"[[", "distance"))] #order paths by distance
296 304
         
297
-        if (ncol(pg$weights) > 1) zret[[i]] <- ps
298
-        else zret <- ps
305
+        if (ncol(pg$weights) > 1){
306
+            zret[[i]] <- ps
307
+        }else zret <- ps
299 308
     }
300 309
     
310
+    if(length(zret)==0)return(NULL)
311
+    
301 312
     if (ncol(pg$weights) > 1) {
302 313
         names(zret) <- graph$y.labels
303 314
         colnames(pg$weights) <- paste("prob",graph$y.labels,sep = ":")
... ...
@@ -472,9 +483,12 @@ processNetwork <- function(graph, start, end, scale=c("ecdf", "rescale"), normal
472 483
     edge.weights <- do.call("rbind", as.list(E(graph)$edge.weights))
473 484
     if(sum(!is.finite(edge.weights))>0){
474 485
         warning("Edge weights contain non-finite numbers. Setting them to the minimum edge weight")
475
-        lapply(1:ncol(edge.weights), function(x) 
476
-                    edge.weights[,x][!is.finite(edge.weights[,x])] <<- min(edge.weights[,x][is.finite(edge.weights[,x])])
477
-            )        
486
+        
487
+        edge.weights <- apply(edge.weights, 2, 
488
+                            function(x){
489
+                                x[ !is.finite(x) ] <- min( x[ is.finite(x) ] )
490
+                                return(x)
491
+                            })        
478 492
     }
479 493
         
480 494
     if(scale=="ecdf")
... ...
@@ -277,19 +277,20 @@ layoutVertexByAttr <- function(graph, attr.name, cluster.strength = 1,layout=lay
277 277
 colorVertexByAttr <- function(graph, attr.name, col.palette = palette()){
278 278
     attr <- getAttribute(graph, attr.name)
279 279
     attr <- do.call("rbind", lapply(1:length(attr), 
280
-                    function(i) cbind(id=i, val=if(length(attr[[i]])==0) NA else attr[[i]] )))
280
+                    function(i) data.frame(id=i, val=if(length(attr[[i]])==0) NA else attr[[i]] )))
281
+    
282
+    attr$val <- as.factor(attr$val)
281 283
     
282
-    rownames(attr) <- as.character(attr[,2]) 
283
-    attr.vals <- na.omit(unique(attr[,2]))
284 284
     if(!is.function(col.palette))
285 285
         col.palette <- colorRampPalette(col.palette)
286 286
     
287
-    col <- col.palette(length(attr.vals) + 1)
288
-    
287
+    col <- col.palette(nlevels(attr$val) + 1)
288
+    names(col) <- c(levels(attr$val), "NA_value_color")
289
+
290
+    col.vector <- col[attr$val]
291
+    col.vector[is.na(col.vector)] <- col[["NA_value_color"]] 
289 292
     
290
-    lapply(1:length(attr.vals), function(i) attr[attr[,2]==attr.vals[[i]] ,2] <<- col[[i]])
291
-    attr[is.na(attr[,2]), 2] <- col[[length(attr.vals) + 1]]
292
-    return(split(attr[,2], as.numeric(attr[,1])))
293
+    return( split(col.vector, as.numeric(attr$id)) )
293 294
 }
294 295
 
295 296
 #' Plots an annotated igraph object in Cytoscape.
... ...
@@ -335,23 +336,27 @@ plotCytoscape <- function(graph, title, layout=layout.auto,
335 336
         V(graph)$color <- vertex.color
336 337
     
337 338
     nel <- igraph.to.graphNEL(graph)
338
-    nel <- initEdgeAttribute(nel, "weight", "numeric", 1)
339
+    nel <- RCytoscape::initEdgeAttribute(nel, "weight", "numeric", 1)
339 340
     
340 341
     ## Initializing vertex attributes
341 342
     v.attrs <- sapply(list.vertex.attributes(graph), function(x) is.numeric(get.vertex.attribute(graph,x)))
342
-    mapply(function(...) nel<<-initNodeAttribute(nel,...), names(v.attrs), 
343
-            ifelse(v.attrs, "numeric", "char"), 
344
-            ifelse(v.attrs, 1, ""))
343
+    for(i in 1:length(v.attrs)){
344
+        nel <- RCytoscape::initNodeAttribute(nel, names(v.attrs)[[i]],
345
+                                ifelse(v.attrs[[i]], "numeric", "char"),
346
+                                ifelse(v.attrs, 1, ""))
347
+    }
345 348
     
346 349
     e.attrs <- sapply(list.edge.attributes(graph), function(x) is.numeric(get.edge.attribute(graph,x)))
347
-    mapply(function(...) nel<<-initEdgeAttribute(nel,...), names(e.attrs), 
348
-            ifelse(e.attrs, "numeric", "char"), 
349
-            ifelse(e.attrs, 1, ""))
350
-    
351
-    cw <- new.CytoscapeWindow (title, graph=nel)
352
-    displayGraph(cw)
353
-    setNodePosition(cw, V(graph)$name, layout[,1], layout[,2])
354
-    redraw(cw)
350
+    for(i in 1:length(e.attrs)){
351
+        nel <- RCytoscape::initEdgeAttribute(nel, names(e.attrs)[[i]],
352
+                ifelse(e.attrs[[i]], "numeric", "char"),
353
+                ifelse(e.attrs, 1, ""))
354
+    }
355
+    
356
+    cw <- RCytoscape::new.CytoscapeWindow (title, graph=nel)
357
+    RCytoscape::displayGraph(cw)
358
+    RCytoscape::setNodePosition(cw, V(graph)$name, layout[,1], layout[,2])
359
+    RCytoscape::redraw(cw)
355 360
     #v.size
356 361
     if(!missing(vertex.size)){
357 362
         if(length(vertex.size)==1)
... ...
@@ -359,24 +364,24 @@ plotCytoscape <- function(graph, title, layout=layout.auto,
359 364
         
360 365
         vertex.size <- as.integer(vertex.size)
361 366
         if(length(vertex.size) == vcount(graph)){
362
-            setNodeSizeDirect(cw, as.character(V(graph)$name), vertex.size)
367
+            RCytoscape::setNodeSizeDirect(cw, as.character(V(graph)$name), vertex.size)
363 368
         }else
364 369
             warning("Vertex sizes length and number of vertices don't match")
365 370
         
366 371
     }else if(!is.null(V(graph)$size)){
367
-        setNodeSizeDirect(cw, as.character(V(graph)$name), as.integer(V(graph)$size))
372
+        RCytoscape::setNodeSizeDirect(cw, as.character(V(graph)$name), as.integer(V(graph)$size))
368 373
     }
369 374
     
370 375
     #v.label
371 376
     if(!missing(vertex.label)){
372 377
         vertex.label <- as.character(vertex.label)
373 378
         if(length(vertex.label) == vcount(graph)){
374
-            setNodeLabelDirect(cw, as.character(V(graph)$name), vertex.label)
379
+            RCytoscape::setNodeLabelDirect(cw, as.character(V(graph)$name), vertex.label)
375 380
         }else
376 381
             warning("Vertex lebels length and number of vertices don't match")
377 382
         
378 383
     }else if(!is.null(V(graph)$label)){
379
-        setNodeLabelDirect(cw, as.character(V(graph)$name),as.character(V(graph)$label))
384
+        RCytoscape::setNodeLabelDirect(cw, as.character(V(graph)$name),as.character(V(graph)$label))
380 385
     }
381 386
     
382 387
     #v.shape
... ...
@@ -391,12 +396,12 @@ plotCytoscape <- function(graph, title, layout=layout.auto,
391 396
             vertex.shape <- rep(vertex.shape, vcount(graph))
392 397
         
393 398
         if(length(vertex.shape) == vcount(graph)){
394
-            setNodeShapeDirect(cw, as.character(V(graph)$name), vertex.shape)
399
+            RCytoscape::setNodeShapeDirect(cw, as.character(V(graph)$name), vertex.shape)
395 400
         }else
396 401
             warning("Vertex shapes length and number of vertices don't match")
397 402
         
398 403
     }else if(!is.null(V(graph)$shape)){
399
-        setNodeShapeDirect(cw, as.character(V(graph)$name),igraphShape2Cyto(V(graph)$shape))
404
+        RCytoscape::setNodeShapeDirect(cw, as.character(V(graph)$name),igraphShape2Cyto(V(graph)$shape))
400 405
     }
401 406
     
402 407
     #v.color
... ...
@@ -409,15 +414,15 @@ plotCytoscape <- function(graph, title, layout=layout.auto,
409 414
         if(length(vertex.color) == vcount(graph)){
410 415
             vertex.color <- split(V(graph)$name, vertex.color)
411 416
             names(vertex.color) <- col2hex(names(vertex.color))            
412
-            lapply(names(vertex.color), function(x) setNodeColorDirect(cw, as.character(vertex.color[[x]]), x))
413
-        }else
417
+            lapply(names(vertex.color), function(x) RCytoscape::setNodeColorDirect(cw, as.character(vertex.color[[x]]), x))
418
+        }else{
414 419
             warning("Vertex colors length and number of vertices don't match")
415
-        
420
+        }
416 421
     }else if(!is.null(V(graph)$color)){
417 422
         vertex.color <- split(V(graph)$name, V(graph)$color)
418 423
         names(vertex.color) <- col2hex(names(vertex.color))
419 424
         
420
-        lapply(names(vertex.color), function(x) setNodeColorDirect(cw, as.character(vertex.color[[x]]), x))
425
+        lapply(names(vertex.color), function(x) RCytoscape::setNodeColorDirect(cw, as.character(vertex.color[[x]]), x))
421 426
     }
422 427
     
423 428
     #e.color
... ...
@@ -427,16 +432,16 @@ plotCytoscape <- function(graph, title, layout=layout.auto,
427 432
             edge.color <- rep(edge.color, ecount(graph))
428 433
         
429 434
         if(length(edge.color) == ecount(graph)){
430
-            setEdgeAttributesDirect(cw, "color", "char", cy2.edge.names(cw@graph), edge.color)
431
-            setEdgeColorRule(cw, "color", unique(edge.color),unique(edge.color), mode="lookup")
435
+            RCytoscape::setEdgeAttributesDirect(cw, "color", "char", cy2.edge.names(cw@graph), edge.color)
436
+            RCytoscape::setEdgeColorRule(cw, "color", unique(edge.color),unique(edge.color), mode="lookup")
432 437
         }else
433 438
             warning("Edge colors length and number of vertices don't match")
434 439
         
435 440
     }else if(!is.null(E(graph)$color)){
436
-        setEdgeColorRule(cw, "color", unique(E(graph)$color),unique(col2hex(E(graph)$color)), mode="lookup")
441
+        RCytoscape::setEdgeColorRule(cw, "color", unique(E(graph)$color),unique(col2hex(E(graph)$color)), mode="lookup")
437 442
     }
438 443
     
439
-    redraw(cw)    
444
+    RCytoscape::redraw(cw)    
440 445
     return(cw)
441 446
 }
442 447
 
... ...
@@ -27,7 +27,7 @@ may be missing. To install libxml2 and the headers:
27 27
 
28 28
 ##### Installing libSBML 
29 29
 Installing libSBML for Unix users is optional. However, NetPathMiner will not be able to process SBML
30
-files. If you will not use them, you can skip this part. 
30
+files. If you will not use SBML functions, you can skip this part. 
31 31
 
32 32
 From the website of libSBML http://sbml.org/Software/libSBML, you can directly download the
33 33
 binaries suitable for your system from ``Download libSBML'' link. You can follow the installation instructions
... ...
@@ -36,7 +36,7 @@ on the website.
36 36
 #### Prerequisites for Windows users
37 37
 Since installing libxml2 and libSBML under Windows is challenging, we have prepared all dependencies in 
38 38
 a tar file, downloadable from https://github.com/ahmohamed/NPM_dependencies . Please download the file
39
-and place in in the home directory of R (type <code>R HOME</code> in command prompt to locate it). Unless
39
+and place in in the home directory of R (type <code>R RHOME</code> in command prompt to locate it). Unless
40 40
 you want to use customized libraries, you can skip the rest of this section.
41 41
 
42 42
 To use customized libraries, you have to compile them and provide them to R at the time of installation.
... ...
@@ -66,7 +66,7 @@ Add `mingw/bin` to your PATH, by editing eviroment variables.
66 66
 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".
67 67
 
68 68
 After finishing the CMake step, use the MinGW's `make.exe` to compile libSBML. Copy the dependencies you used
69
-during the cimpilation to the `bin` directory. Set the enviroment variable `LIBSBML` to point the installation 
69
+during the compilation to the `bin` directory. Set the enviroment variable `LIB_SBML` to point the installation 
70 70
 directory, which should now contain dll files inder `bin` and header files under `include`
71 71
 
72 72
 
... ...
@@ -95,10 +95,12 @@ To install R package devtools call:
95 95
 
96 96
 ##### RCurl
97 97
 For Unix users, make sure your Linux has library libcurl installed. Check out:
98
+
98 99
 <code>
99
-    locate libcurl
100
+    locate libcurl   
100 101
     locate curl-config
101 102
 </code>
103
+
102 104
 If these are not found (usually the developer version is missing), most Linux
103 105
 users will be able to fix this by running:
104 106
 <code>
... ...
@@ -124,20 +126,22 @@ call:
124 126
 to install it right away.
125 127
 
126 128
 ##### RCytoscape
127
-Package RCytoscapeis available on Bioconductor. For installation instructions check 
128
-out http://www.bioconductor.org/packages/release/bioc/html/RCytoscape.html or
129
-call:
129
+Package RCytoscape is available on Bioconductor. For installation instructions check 
130
+out http://www.bioconductor.org/packages/release/bioc/html/RCytoscape.html . Please note 
131
+that RCytoscape requires Cytoscape 2.8 installed with XMLRPC plugin. Cytoscape 3 is not yet 
132
+supported. After installing Cytoscape, call:
133
+
130 134
 <code>
131
-    source("http://bioconductor.org/biocLite.R")
135
+    source("http://bioconductor.org/biocLite.R")   
132 136
     biocLite("RCytoscape")
133 137
 </code>
134
-to install it right away.
138
+to install RCytoscape.
135 139
 
136 140
 ### NetPathMiner InstallationS
137 141
 If everything went well you will be able to install the NetPathMiner package from GitHub using devtools:
138 142
 
139 143
 <code>
140
-    library(devtools)
144
+    library(devtools)   
141 145
     install_github(repo="NetPathMiner", username="ahmohamed")
142 146
 </code>
143 147
 
... ...
@@ -2,21 +2,9 @@
2 2
 echo "removing boost headers..."
3 3
 cd src; rm -rf boost
4 4
 
5
-if test -f kgml_interface.c__;
6
-	then mv kgml_interface.c__ kgml_interface.cpp; 
7
-fi;
8
-
9
-if test -f sbml_interface.c__;
10
-	then mv sbml_interface.c__ sbml_interface.cpp; 
11
-fi;
12
-
13
-if test -f sbml_interface.h__;
14
-	then mv sbml_interface.h__ sbml_interface.h; 
15
-fi;
16
-
17 5
 echo "restoring Makevars.in file..."
18 6
 mv _Makevars.in_ Makevars.in; 
19 7
 rm Makevars
20 8
 
21 9
 echo "removing compiled code..."
22
-rm *.o
23 10
\ No newline at end of file
11
+rm *.o
24 12
old mode 100644
25 13
new mode 100755
... ...
@@ -3,29 +3,12 @@ cd src;
3 3
 echo "removing boost headers..."
4 4
 rm -rf boost
5 5
 
6
-if test -f kgml_interface.c__;
7
-	then mv kgml_interface.c__ kgml_interface.cpp; 
8
-fi;
9
-
10
-if test -f sbml_interface.c__;
11
-	then mv sbml_interface.c__ sbml_interface.cpp; 
12
-fi;
13
-
14
-if test -f sbml_interface.h__;
15
-	then mv sbml_interface.h__ sbml_interface.h; 
16
-fi;
17
-
18 6
 echo "restoring handelsegfault file..."
19 7
 
20
-if test -f handlesegfault.c__;
21
-	then 
22
-		mv handlesegfault.c handlesegfault.cwin;
23
-		mv handlesegfault.c__ handlesegfault.c; 
24
-fi;
25 8
 
26
-if test -f Makevars.win_;
9
+if test -f Makevars.win;
27 10
 	then 
28
-		mv Makevars.win_ Makevars.win;
11
+		rm Makevars.win;
29 12
 fi;
30 13
 
31 14
 
... ...
@@ -2905,17 +2905,18 @@ fi
2905 2905
 		if test -n "${SBMLPC}"
2906 2906
 			then
2907 2907
 				echo "libsbml.pc found. Using pkg-config to extract it."
2908
-				SBML_INCDIR=`${PKG_CONFIG} --cflags ${SBMLPC}`
2908
+				SBML_INCDIR="-DHAVE_SBML `${PKG_CONFIG} --cflags ${SBMLPC}`"
2909 2909
 				SBML_LIBS=`${PKG_CONFIG} --libs ${SBMLPC}`
2910 2910
 			else
2911 2911
 				echo "Couldn't find libsbml.pc. Searching for libsbml in candidate directories."
2912 2912
 				if test -d /usr/include/sbml
2913
-					then SBML_INCDIR="-I/usr/include/"
2913
+					then SBML_INCDIR="-DHAVE_SBML -I/usr/include/"
2914 2914
 					else
2915 2915
 						if test -d /usr/local/include/sbml
2916
-							then SBML_INCDIR="-I/usr/local/include/"
2916
+							then SBML_INCDIR="-DHAVE_SBML -I/usr/local/include/"
2917 2917
 						fi;
2918 2918
 				fi;
2919
+		fi;
2919 2920
 
2920 2921
 	for ac_prog in xml2-config
2921 2922
 do
... ...
@@ -2962,12 +2963,11 @@ fi
2962 2963
   test -n "$XML_CONFIG" && break
2963 2964
 done
2964 2965
 
2965
-	LIBXML_INCDIR=`${XML_CONFIG} --cflags`
2966
+	LIBXML_INCDIR="-DHAVE_XML `${XML_CONFIG} --cflags`"
2966 2967
 	XML_LIBS=`${XML_CONFIG} --libs`
2967 2968
 
2968
-				SBML_INCDIR="$LIBXML_INCDIR $SBML_INCDIR"
2969
-				SBML_LIBS="$XML_LIBS"
2970
-		fi;
2969
+        SBML_INCDIR="$LIBXML_INCDIR $SBML_INCDIR"
2970
+        SBML_LIBS="$XML_LIBS"
2971 2971
 		CPPFLAGS="${CPPFLAGS} ${SBML_INCDIR}"
2972 2972
 		PKG_LIBS="${PKG_LIBS} ${SBML_LIBS} -lsbml"
2973 2973
 
... ...
@@ -3024,11 +3024,9 @@ fi
3024 3024
   test -n "$XML_CONFIG" && break
3025 3025
 done
3026 3026
 
3027
-	LIBXML_INCDIR=`${XML_CONFIG} --cflags`
3027
+	LIBXML_INCDIR="-DHAVE_XML `${XML_CONFIG} --cflags`"
3028 3028
 	XML_LIBS=`${XML_CONFIG} --libs`
3029 3029
 
3030
-			CPPFLAGS="${CPPFLAGS} ${LIBXML_INCDIR}"
3031
-			PKG_LIBS="${PKG_LIBS} ${XML_LIBS} -lxml2"
3032 3030
 		else
3033 3031
 			echo 'XML not found.'; cd src;
3034 3032
 			mv kgml_interface.cpp kgml_interface.c__;  cd ..;
... ...
@@ -4208,7 +4206,6 @@ if test -n "$ac_unrecognized_opts" && test "$enable_option_checking" != no; then
4208 4206
 $as_echo "$as_me: WARNING: unrecognized options: $ac_unrecognized_opts" >&2;}
4209 4207
 fi
4210 4208
 
4211
-chmod +x cleanup
4212 4209
 
4213 4210
 mv src/Makevars.in src/_Makevars.in_;
4214 4211
 rm config.*
... ...
@@ -35,7 +35,7 @@ fi;
35 35
 
36 36
 AC_DEFUN([CHECK_XML],[
37 37
 	AC_PATH_PROGS(XML_CONFIG, xml2-config)
38
-	LIBXML_INCDIR=`${XML_CONFIG} --cflags`
38
+	LIBXML_INCDIR="-DHAVE_XML `${XML_CONFIG} --cflags`"
39 39
 	XML_LIBS=`${XML_CONFIG} --libs`
40 40
 ])
41 41
 
... ...
@@ -62,37 +62,33 @@ if ${SBML}
62 62
 		if test -n "${SBMLPC}"
63 63
 			then
64 64
 				echo "libsbml.pc found. Using pkg-config to extract it."				
65
-				SBML_INCDIR=`${PKG_CONFIG} --cflags ${SBMLPC}`
65
+				SBML_INCDIR="-DHAVE_SBML `${PKG_CONFIG} --cflags ${SBMLPC}`"
66 66
 				SBML_LIBS=`${PKG_CONFIG} --libs ${SBMLPC}`
67 67
 			else
68 68
 				echo "Couldn't find libsbml.pc. Searching for libsbml in candidate directories."
69 69
 				if test -d /usr/include/sbml
70
-					then SBML_INCDIR="-I/usr/include/"
70
+					then SBML_INCDIR="-DHAVE_SBML -I/usr/include/"
71 71
 					else 
72 72
 						if test -d /usr/local/include/sbml
73
-							then SBML_INCDIR="-I/usr/local/include/"
73
+							then SBML_INCDIR="-DHAVE_SBML -I/usr/local/include/"
74 74
 						fi;
75
-				fi;
76
-				CHECK_XML()				
77
-				SBML_INCDIR="$LIBXML_INCDIR $SBML_INCDIR"
78
-				SBML_LIBS="$XML_LIBS"
75
+				fi;				
79 76
 		fi;
77
+		CHECK_XML()               
78
+        SBML_INCDIR="$LIBXML_INCDIR $SBML_INCDIR"
79
+        SBML_LIBS="$XML_LIBS"
80 80
 		CPPFLAGS="${CPPFLAGS} ${SBML_INCDIR}"
81 81
 		PKG_LIBS="${PKG_LIBS} ${SBML_LIBS} -lsbml"
82 82
 			
83 83
 	else
84
-		echo 'SBML not found.'; cd src; mv sbml_interface.cpp sbml_interface.c__;
85
-		mv sbml_interface.h sbml_interface.h__; cd ..;
84
+		echo 'SBML not found.';
86 85
 
87 86
 	if ${XML}
88 87
 		then
89 88
 			echo 'libXML2 found'
90
-			CHECK_XML()
91
-			CPPFLAGS="${CPPFLAGS} ${LIBXML_INCDIR}"
92
-			PKG_LIBS="${PKG_LIBS} ${XML_LIBS} -lxml2"
89
+			CHECK_XML()			
93 90
 		else
94
-			echo 'XML not found.'; cd src; 
95
-			mv kgml_interface.cpp kgml_interface.c__;  cd ..;
91
+			echo 'XML not found.';
96 92
 	fi;
97 93
 fi;
98 94
 
... ...
@@ -102,7 +98,6 @@ AC_SUBST(CPPFLAGS)
102 98
 AC_SUBST(PKG_LIBS)
103 99
 
104 100
 AC_OUTPUT(src/Makevars)
105
-chmod +x cleanup
106 101
 
107 102
 dnl cleanup after configure
108 103
 mv src/Makevars.in src/_Makevars.in_;
... ...
@@ -1,39 +1,320 @@
1 1
 #!/bin/sh
2
+test_xml_function(){
3
+echo '
4
+#include <stdio.h>
5
+#include <libxml/xmlreader.h>
6
+
7
+int main(){
8
+    xmlParseFile("nofile");
9
+    return 0;
10
+}
11
+'>xml_test.cpp
12
+
13
+${CPP_COMPILER} -o xml_test.out xml_test.cpp ${pkg_cppflags} ${XML_INCDIR} ${XML_LIBS} ${pkg_libs} >/dev/null 2>&1
14
+
15
+echo -n "* testing xmlParseFile in libxml2 ... "
16
+if test -f xml_test.out
17
+    then
18
+        echo "success"
19
+		pkg_cppflags="${pkg_cppflags} -DHAVE_XML ${XML_INCDIR}"
20
+		pkg_libs="${XML_LIBS} ${pkg_libs}"
21
+        HAVE_XML=true
22
+    else
23
+        echo "failed"
24
+		echo -n "** Error Message: "
25
+		echo `${CPP_COMPILER} -o xml_test.out xml_test.cpp ${pkg_cppflags} ${XML_INCDIR} ${XML_LIBS} ${pkg_libs}`
26
+		echo "** Although libxml2 headers and binaries were found, compiler failed.
27
+	This may be due to incomplete headers or corrupt library."
28
+fi;
29
+
30
+rm xml_test.*
31
+}
32
+
33
+test_sbml_function(){
34
+echo '
35
+#include <stdio.h>
36
+#include <sbml/SBMLTypes.h>
37
+
38
+int main(){
39
+    readSBML("nofile")->getModel();
40
+    return 0;
41
+}
42
+'>sbml_test.cpp
43
+
44
+${CPP_COMPILER} -o sbml_test.out sbml_test.cpp ${pkg_cppflags} ${SBML_INCDIR} ${SBML_LIBS} ${pkg_libs} >/dev/null 2>&1
45
+
46
+echo -n "* testing readSBML, SBMLDocument::getModel in libSBML ... "
47
+if test -f sbml_test.out
48
+    then
49
+        echo "success"
50
+		pkg_cppflags="${pkg_cppflags} -DHAVE_SBML ${SBML_INCDIR}"
51
+		pkg_libs="${SBML_LIBS} ${pkg_libs}"
52
+        HAVE_SBML=true
53
+    else
54
+        echo "failed"
55
+        echo -n "** Error Message: "
56
+		echo `${CPP_COMPILER} -o sbml_test.out sbml_test.cpp ${pkg_cppflags} ${SBML_INCDIR} ${SBML_LIBS} ${pkg_libs}`
57
+		echo "** Although libSBML headers and binaries were found, compiler failed.
58
+	Please ensure that libSBML is built using GCC compiler."
59
+	    
60
+fi;
61
+
62
+rm sbml_test.*
63
+}
64
+
65
+makevars_dependencies(){
66
+echo 'PKG_CPPFLAGS=-DWIN_COMPILE -DHAVE_XML -DHAVE_SBML -I. -I"./libs/include/" -I"./libs/include/libxml2"
67
+PKG_LIBS = -L"libs$(R_ARCH)" -lsbml -lxml2 -liconv -lstdc++ $(LAPACK_LIBS) $(BLAS_LIBS) $(FLIBS)
68
+
69
+all:$(SHLIB)
70
+	mkdir -p "$(R_PACKAGE_DIR)/libs$(R_ARCH)"
71
+	cp libs$(R_ARCH)/*.dll "${R_PACKAGE_DIR}/libs${R_ARCH}"
72
+'> Makevars.win;
73
+
74
+}
75
+
76
+makevars_bioC(){
77
+pkg_cppflags="-DWIN_COMPILE -I. -I${R_HOME}/include"
78
+pkg_libs=""
79
+
80
+if ${HAVE_XML}
81
+	then
82
+		pkg_cppflags="${pkg_cppflags} -DHAVE_XML -I${LIB_XML2}/\${R_ARCH}/include/libxml2"
83
+		pkg_libs="-L${LIB_XML2}/\${R_ARCH}/lib -lxml2 -lws2_32 ${pkg_libs}"
84
+fi;
85
+
86
+if ${HAVE_SBML}
87
+	then
88
+		pkg_cppflags="${pkg_cppflags} -DHAVE_SBML -I${LIBSBML_PATH}/\${R_ARCH}/include"
89
+		pkg_libs="-L${LIBSBML_PATH}/\${R_ARCH}/bin -lsbml ${pkg_libs}"
90
+fi;
91
+
92
+echo "PKG_CPPFLAGS=${pkg_cppflags}
93
+PKG_LIBS = ${pkg_libs} \$(LAPACK_LIBS) \$(BLAS_LIBS) \$(FLIBS)
94
+"> Makevars.win;
95
+
96
+}
97
+
98
+xml_check_header(){
99
+echo "XML folder";
100
+echo `find ${lib_xml_location} | tr '\n' ' '`;
101
+echo -n "* searching for libxml2 headers under ${lib_xml_location} ... ";
102
+if test -f ${lib_xml_location}/libxml/xmlreader.h
103
+	then
104
+		echo "found"
105
+		XML_INCDIR="-I${lib_xml_location}"
106
+		return
107
+fi;
108
+
109
+if test -f ${lib_xml_location}/include/libxml/xmlreader.h
110
+	then
111
+		echo "found"
112
+		XML_INCDIR="-I${lib_xml_location}/include"
113
+		return
114
+fi;
115
+
116
+if test -f ${lib_xml_location}/include/libxml2/libxml/xmlreader.h
117
+	then
118
+		echo "found"
119
+		XML_INCDIR="-I${lib_xml_location}/include/libxml2"
120
+		return
121
+fi;
122
+
123
+# Search also in sbml installation directory.
124
+if test -f ${lib_sbml_location}/include/libxml/xmlreader.h
125
+	then
126
+		echo "found"
127
+		XML_INCDIR="-I${lib_sbml_location}/include/"
128
+		return
129
+fi;
130
+
131
+echo "failed"
132
+}
133
+
134
+sbml_check_header(){
135
+echo "SBML folder";
136
+echo `find ${lib_sbml_location} | tr '\n' ' '`;
137
+echo -n "* searching for libSBML headers under ${lib_sbml_location} ... ";
138
+if test -f ${lib_sbml_location}/sbml/SBMLTypes.h
139
+	then
140
+		echo "found"
141
+		SBML_INCDIR="-I${lib_sbml_location}"
142
+		return
143
+fi;
144
+
145
+if test -f ${lib_sbml_location}/include/sbml/SBMLTypes.h
146
+	then
147
+		echo "found"
148
+		SBML_INCDIR="-I${lib_sbml_location}/include"
149
+		return
150
+fi;
151
+
152
+echo "failed"
153
+}
154
+
155
+xml_check_libs(){
156
+echo -n "* searching for libxml2 binaries under ${lib_xml_location} ... ";
157
+if test -f ${lib_xml_location}/bin/*xml*
158
+	then
159
+		echo "found"
160
+		XML_LIBS="-L${lib_xml_location}/bin -lxml2"
161
+		return
162
+fi;
163
+
164
+if test -f ${lib_xml_location}/lib/*xml*
165
+	then
166
+		echo "found"
167
+		XML_LIBS="-L${lib_xml_location}/lib -lxml2"
168
+		return
169
+fi;
170
+
171
+echo "failed"
172
+}
173
+
174
+sbml_check_libs(){
175
+echo -n "* searching for libSBML binaries under ${lib_sbml_location} ... ";
176
+if test -f ${lib_sbml_location}/bin/*sbml*
177
+	then
178
+		echo "found"
179
+		SBML_LIBS="-L${lib_sbml_location}/bin -lsbml"
180
+		return
181
+fi;
182
+
183
+if test -f ${lib_sbml_location}/lib/*sbml*
184
+	then
185
+		echo "found"
186
+		SBML_LIBS="-L${lib_sbml_location}/lib -lsbml"
187
+		return
188
+fi;
189
+
190
+echo "failed"
191
+}
192
+CPP_COMPILER=`R CMD config CXX`
193
+
2 194
 cd src;
195
+echo -n '* searching for boost headers ... '
3 196
 if test -d ./boost;
4 197
 	then 
5
-		echo 'found boostIncl header sources and tar archive;\n using what is there.'
198
+		echo 'found.'
6 199
 	else
7
-		echo "untarring boost include tree...";
200
+		echo "not found. Untarring boost.tar.gz";
8 201
 		tar zxf boost.tar.gz;
9 202
 fi;
10 203
 
204
+echo -n '* searching for NPM_dependencies file ... '
11 205
 if test -f ${R_HOME}/NPM_dependencies.tar.gz;
12 206
 	then
13
-		echo 'found dependencies files. untarring...'
207
+		echo 'found. untarring ...'
14 208
 		tar zxf ${R_HOME}/NPM_dependencies.tar.gz;
15
-		cp Makevars.win Makevars.win_;
16
-		echo 'PKG_CPPFLAGS=-D_R_=1 -DUSE_R=1 -I. -I"./libs/include/" -I"./libs/include/libxml2"
17
-PKG_LIBS = -L"libs$(R_ARCH)" -lsbml -lxml2 -liconv -lstdc++ $(LAPACK_LIBS) $(BLAS_LIBS) $(FLIBS)
209
+		makevars_dependencies;
210
+		cd ..; exit;
211
+	else
212
+	    echo 'not found.'
213
+fi;
18 214
 
19
-all:$(SHLIB)
20
-	mkdir -p "$(R_PACKAGE_DIR)/libs$(R_ARCH)"
21
-	cp libs$(R_ARCH)/*.dll "${R_PACKAGE_DIR}/libs${R_ARCH}"' >> Makevars.win;
215
+echo "* Searching for libxml2 and libSBML ... "
216
+pkg_cppflags="-DWIN_COMPILE -I. -I${R_HOME}/include"
217
+pkg_libs=""
218
+HAVE_XML=false
219
+HAVE_SBML=false
22 220
 
23
-	else
24
-		echo "Dependecies not found. SBML file processing disabled."
25
-		cp Makevars.win Makevars.win_;
26
-		echo 'PKG_LIBS = -L${LIB_XML}/lib -L${LIB_XML2}/lib -lxml2 -liconv -lz -lws2_32 $(LAPACK_LIBS) $(BLAS_LIBS) $(FLIBS)' >> Makevars.win
27
-		mv sbml_interface.cpp sbml_interface.c__;
28
-		mv sbml_interface.h sbml_interface.h__;
221
+if test -n "${LIB_XML2}" && test -n "${LIBSBML_PATH}"
222
+	then
223
+		echo "* compiling on Bioconductor machines..."
224
+		XML_INCDIR="-I${LIB_XML2}/${R_ARCH}/include/libxml2"
225
+		XML_LIBS="-L${LIB_XML2}/${R_ARCH}/lib -lxml2 -lws2_32"
226
+		SBML_INCDIR="-I${LIBSBML_PATH}/${R_ARCH}/include"
227
+		SBML_LIBS="-L${LIBSBML_PATH}/${R_ARCH}/bin -lsbml"
228
+		test_xml_function;
229
+		test_sbml_function;
230
+		makevars_bioC;
231
+		exit;
29 232
 fi;
30 233
 
234
+if test -n "${LIB_XML}"
235
+	then
236
+		echo "** LIB_XML variable is defined. Searching for libxml2 there."
237
+		lib_xml_location="${LIB_XML}"
238
+fi;
239
+
240
+if test -n "${LIB_XML2}"
241
+	then
242
+		echo "** LIB_XML2 variable is defined. Searching for libxml2 there."
243
+		lib_xml_location="${LIB_XML2}"
244
+fi;
245
+
246
+if test -n "${LIB_SBML}"
247
+	then
248
+		echo "** LIB_SBML variable is defined. Searching for libSBML there."
249
+		lib_sbml_location="${LIB_SBML}"
250
+		
251
+		if test -d ${LIB_SBML}/win32
252
+			then
253
+				lib_sbml_location="${LIB_SBML}/win32"
254
+		fi;
255
+		
256
+		if test -d ${LIB_SBML}/win64
257
+			then
258
+				lib_sbml_location="${LIB_SBML}/win64"
259
+		fi;		
260
+fi;
261
+
262
+if test -n "${LIBSBML_PATH}"
263
+	then
264
+		echo "** LIBSBML_PATH variable is defined. Searching for libSBML there."
265
+		lib_sbml_location="${LIBSBML_PATH}"
266
+		if test -d ${LIBSBML_PATH}/win32
267
+			then
268
+				lib_sbml_location="${LIBSBML_PATH}/win32"
269
+		fi;
270
+		
271
+		if test -d ${LIBSBML_PATH}/win64
272
+			then
273
+				lib_sbml_location="${LIBSBML_PATH}/win64"
274
+		fi;
275
+fi;
31 276
 
32
-if test -f handlesegfault.cwin;
277
+if test -z "${lib_xml_location}"
33 278
 	then
34
-		echo "Modifying segfault handling for Windows"	
35
-		mv handlesegfault.c handlesegfault.c__;
36
-		mv handlesegfault.cwin handlesegfault.c;
279
+		echo "** Cannot find libxml2. Neither LIB_XML nor LIB_XML2 variables are defined."
280
+	else
281
+		xml_check_header;
282
+		xml_check_libs;
283
+		if test -n "${XML_INCDIR}" && test -n "${XML_LIBS}"
284
+			then
285
+				test_xml_function;
286
+		fi;
287
+fi;	
288
+
289
+if test -z "${lib_sbml_location}"
290
+	then
291
+		echo "** Cannot find libSBML. Neither LIB_SBML nor LIBSBML_PATH variables are defined."
292
+	else
293
+		sbml_check_header;
294
+		sbml_check_libs;
295
+		if test -n "${SBML_INCDIR}" && test -n "${SBML_LIBS}"
296
+			then
297
+				test_sbml_function;
298
+		fi;
299
+fi;	
300
+
301
+if ${HAVE_XML}
302
+	then
303
+	else
304
+		echo "NOTE: The package failed to find libxml2. KGML file processing disabled."
305
+fi;
306
+
307
+if ${HAVE_SBML}
308
+	then
309
+	else
310
+		echo "NOTE: The package failed to find libSBML. SBML file processing disabled."
37 311
 fi;
38 312
 
39
-cd ..;
313
+echo "ifeq \"\${R_ARCH}\" \"${R_ARCH}\"
314
+PKG_CPPFLAGS=${pkg_cppflags}
315
+PKG_LIBS=${pkg_libs} \$(LAPACK_LIBS) \$(BLAS_LIBS) \$(FLIBS)
316
+else
317
+PKG_CPPFLAGS=-DWIN_COMPILE -I. -I${R_HOME}/include
318
+PKG_LIBS=\$(LAPACK_LIBS) \$(BLAS_LIBS) \$(FLIBS)
319
+endif
320
+">Makevars.win
40 321
Binary files a/data/ex_biopax.rda and b/data/ex_biopax.rda differ
... ...
@@ -14,14 +14,14 @@ library(NetPathMiner)
14 14
 
15 15
 
16 16
 ###################################################
17
-### code chunk number 3: NPMVignette.Rnw:209-211 (eval = FALSE)
17
+### code chunk number 3: NPMVignette.Rnw:235-237 (eval = FALSE)
18 18
 ###################################################
19 19
 ## graph <- KGML2igraph(filename = file)
20 20
 ## graph <- SBML2igraph(filename = file)
21 21
 
22 22
 
23 23
 ###################################################
24
-### code chunk number 4: NPMVignette.Rnw:217-220 (eval = FALSE)
24
+### code chunk number 4: NPMVignette.Rnw:243-246 (eval = FALSE)
25 25
 ###################################################
26 26
 ## require(rBiopaxParser)
27 27
 ## biopax = readBiopax(file)
... ...
@@ -29,19 +29,19 @@ library(NetPathMiner)
29 29
 
30 30
 
31 31
 ###################################################
32
-### code chunk number 5: NPMVignette.Rnw:226-227 (eval = FALSE)
32
+### code chunk number 5: NPMVignette.Rnw:252-253 (eval = FALSE)
33 33
 ###################################################
34 34
 ## graph <- KGML2igraph(filename = c(file1, file2))
35 35
 
36 36
 
37 37
 ###################################################
38
-### code chunk number 6: NPMVignette.Rnw:231-232 (eval = FALSE)
38
+### code chunk number 6: NPMVignette.Rnw:257-258 (eval = FALSE)
39 39
 ###################################################
40 40
 ## graph <- KGML2igraph(filename = ".")
41 41
 
42 42
 
43 43
 ###################################################
44
-### code chunk number 7: NPMVignette.Rnw:237-242 (eval = FALSE)
44
+### code chunk number 7: NPMVignette.Rnw:263-268 (eval = FALSE)
45 45
 ###################################################
46 46
 ## # Extract all MIRIAM identifiers from an SBML file.
47 47
 ## graph <- SBML2igraph(filename = file, miriam = "all")
... ...
@@ -51,22 +51,22 @@ library(NetPathMiner)
51 51
 
52 52
 
53 53
 ###################################################
54
-### code chunk number 8: NPMVignette.Rnw:249-250
54
+### code chunk number 8: NPMVignette.Rnw:275-276
55 55
 ###################################################
56 56
 file <- file.path(find.package("NetPathMiner"), "extdata", "hsa00860.xml")
57 57
 
58 58
 
59 59
 ###################################################
60
-### code chunk number 9: NPMVignette.Rnw:252-256
60
+### code chunk number 9: NPMVignette.Rnw:278-282 (eval = FALSE)
61 61
 ###################################################
62
-graph <- KGML2igraph(filename = file, parse.as = "signaling")
63
-
64
-graph <- KGML2igraph(filename = file, parse.as = "signaling", 
65
-	expand.complexes = TRUE)
62
+## graph <- KGML2igraph(filename = file, parse.as = "signaling")
63
+## 
64
+## graph <- KGML2igraph(filename = file, parse.as = "signaling", 
65
+## 	expand.complexes = TRUE)
66 66
 
67 67
 
68 68
 ###################################################
69
-### code chunk number 10: NPMVignette.Rnw:262-265
69
+### code chunk number 10: NPMVignette.Rnw:288-291
70 70
 ###################################################
71 71
 data("ex_sbml")
72 72
 graph <- ex_sbml
... ...
@@ -74,43 +74,43 @@ graph
74 74
 
75 75
 
76 76
 ###################################################
77
-### code chunk number 11: NPMVignette.Rnw:274-275
77
+### code chunk number 11: NPMVignette.Rnw:300-301
78 78
 ###################################################
79 79
 head( V(graph) )
80 80
 
81 81
 
82 82
 ###################################################
83
-### code chunk number 12: NPMVignette.Rnw:278-279
83