diff --git a/.Rbuildignore b/.Rbuildignore index 3e82400..58566c0 100644 --- a/.Rbuildignore +++ b/.Rbuildignore @@ -17,3 +17,4 @@ demo/gexfplot\.R ^README-.*\.png$ ^\.travis\.yml$ ^appveyor\.yml$ +^codecov\.yml$ diff --git a/ChangeLog b/ChangeLog index 86fbf97..d1e8a4d 100644 --- a/ChangeLog +++ b/ChangeLog @@ -1,3 +1,9 @@ +2016-11-10 George G. Vega Yon + * R/bugs.r: Creating a more generic method for checking viz attrs. + * R/rgexf.r: Started moving from write.gexf to gexf. In the 2.0 + version write.gexf should be for exporting gexf graphs only. + * demo/*.R: Replaced write.gexf with gexf. + 2016-11-09 George G. Vega Yon * Added ChangeLog * Change Depends to Imports and added namespace calls diff --git a/DESCRIPTION b/DESCRIPTION index a1f625d..03f4141 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -26,5 +26,7 @@ License: MIT + file LICENSE LazyLoad: yes RoxygenNote: 5.0.1 Suggests: knitr, - rmarkdown + rmarkdown, + testthat, + covr VignetteBuilder: knitr diff --git a/NAMESPACE b/NAMESPACE index e9f8e94..8502f0c 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -10,6 +10,7 @@ export(add.node.spell) export(check.dpl.edges) export(checkTimes) export(edge.list) +export(gexf) export(gexf.to.igraph) export(igraph.to.gexf) export(new.gexf.graph) diff --git a/R/bugs.r b/R/bugs.r index 8ff42d5..79109cc 100644 --- a/R/bugs.r +++ b/R/bugs.r @@ -48,58 +48,49 @@ checkTimes <- function(x, format='date') { #checkTimes(test, format='dateTime') #checkTimes('2012-02-01T00:00:00', 'dateTime') -.parseNodesVizAtt <- function(nodesVizAtt, nodes) { -################################################################################ -# Parses nodes viz attributes checking dimentions, classes and names -################################################################################ - if (any(lapply(nodesVizAtt, length) > 0)) { - supportedNodesVizAtt <- c("color", "position", "size", "shape", "image") - if (all(names(nodesVizAtt) %in% supportedNodesVizAtt)) { - if (all(lapply(nodesVizAtt, NROW) == NROW(nodes))) { - return(length(nodesVizAtt)) - } - else { - nodesVizAtt <- lapply(nodesVizAtt, NROW) - nodesVizAtt <- nodesVizAtt[nodesVizAtt != NROW(nodes)] - stop("Insuficient number of \"nodeVizAtt\" rows: The atts ", - paste(names(nodesVizAtt), unlist(nodesVizAtt), sep=" (", collapse=" rows), "),")\n", - "Every att should have the same number of rows than nodes there are (",NROW(nodes),")") - } - } - else { - noviz <- names(nodesVizAtt) - noviz <- noviz[!(noviz %in% supportedNodesVizAtt)] - stop("Invalid \"nodeVizAtt\": ",noviz,"\nOnly \"color\", \"position\", \"size\", \"shape\" and \"image\" are supported") - } - } - else return(0) -} +vizAttsSpecs <- list( + color = function(x) { + if (is.vector(x) || ncol(x) == 1) { + warning("Trying to coerce colors into RGBA") + return( cbind(t(col2rgb(x)), 1) ) + } else if (ncol(x) != 4) # Must be 4-columns + stop("the color attribute must have 4 columns (RGBA).") + + # Must have the right range + if (max(x[,-4]) > 255 || min(x[,-4]) < 0) + stop("The RGB colors must be in the range [0,255].") + + if (max(x[,4]) > 1 | min(x[,4]) < 0) + stop("The alpha part of the colors (4th column) must be within [0,1].") + + return(x) + + }, + position = function(x) x, + size = function(x) x, + shape = function(x) x, + image = function(x) x +) -.parseEdgesVizAtt <- function(edgesVizAtt, edges) { -################################################################################ -# Parses edges viz attributes checking dimentions, classes and names -################################################################################ - if (any(lapply(edgesVizAtt, length) > 0)) { - supportedEdgeVizAtt <- c("color", "size", "shape") - if (all(names(edgesVizAtt) %in% supportedEdgeVizAtt)) { - if (all(lapply(edgesVizAtt, NROW) == NROW(edges))) { - return(length(edgesVizAtt)) - } - else { - edgesVizAtt <- lapply(edgesVizAtt, NROW) - edgesVizAtt <- edgesVizAtt[edgesVizAtt != NROW(edges)] - stop("Insuficient number of \"edgeVizAtt\" rows: The atts ", - paste(names(edgesVizAtt), unlist(edgesVizAtt), sep=" (", collapse=" rows), "),")\n", - "Every att should have the same number of rows than edges there are (",NROW(edges),")") - } - } - else { - noviz <- names(edgesVizAtt) - noviz <- noviz[!(noviz %in% supportedEdgeVizAtt)] - stop("Invalid \"edgesVizAtt\": ",noviz,"\nOnly \"color\", \"size\" and \"shape\" are supported") - } - } - else return(0) +parseVizAtt <- function(att, dat, n, type=c("nodes", "edges")) { + # Generic checks + if (is.vector(dat)) { + if (length(dat) < n) + stop("The attribute -",att,"- has incorrect length (has ",length(dat), + ", and must have ",n,").") + } else if (inherits(dat, c("data.frame", "matrix"))) { + if (nrow(dat) != n) + stop("The attribute -",att,"- has incorrect number of rows (has ", + nrow(dat)," and it must have ",n,").") + } else stop("The attribute -",att,"- of class -",class(dat),"- is not supported.") + + # What list of attrs + checks <- if (type=="nodes") c("color", "position", "size", "shape", "image") + else if (type=="edges") c("color", "size", "shape") + + if (att %in% checks) vizAttsSpecs[[att]](dat) + else stop("The attribute -", att,"- is not supported for -", type,"-. Only '", + paste(checks, collapse="', '"), " are currently supported.") } .parseEdgesWeight <- function(edgesWeight, edges) { diff --git a/R/rgexf-package.r b/R/rgexf-package.r index d5ed156..dcce025 100644 --- a/R/rgexf-package.r +++ b/R/rgexf-package.r @@ -108,7 +108,7 @@ NULL #' target=c(4,2,3,3,4,2,4,1,1)) #' #' # Building gexf graph -#' mygraph <- write.gexf(nodes=people, edges=relations) +#' mygraph <- gexf(nodes=people, edges=relations) #' #' # Summary and pring #' summary(mygraph) @@ -148,7 +148,7 @@ NULL #' #' #' @name rgexf-package -#' @aliases rgexf-package rgexf gexf gephi +#' @aliases rgexf-package rgexf gephi #' @docType package #' @note See the GEXF primer for details on the GEXF graph format: #' \url{https://gephi.org/gexf/1.2draft/gexf-12draft-primer.pdf} diff --git a/R/rgexf.r b/R/rgexf.r index 6b1d7b0..b2da609 100644 --- a/R/rgexf.r +++ b/R/rgexf.r @@ -29,26 +29,23 @@ edge.list <- function(x) { # Translate a edgelist to two objects list (nodes + edges) ################################################################################ objClass <- class(x) - nEdges <- NROW(x) - nCols <- NCOL(x) == 2 + k <- ncol(x) == 2 - if (objClass %in% c("matrix", "data.frame")) { + if (any(c("matrix", "data.frame") %in% objClass)) { - if (nCols) { + if (k == 2) { # If it is not a factor if (!is.factor(x)) x <- factor(c(x[,1], x[,2])) edges <- matrix(unclass(x), byrow=FALSE, ncol=2) colnames(edges) <- c("source","target") - nodes <- data.frame(id=1:nlevels(x), label=levels(x), stringsAsFactors=F) + nodes <- data.frame(id=1:nlevels(x), label=levels(x), stringsAsFactors=FALSE) - edgelist <- list(nodes=nodes, edges=edges) - - return(edgelist) + return(list(nodes=nodes, edges=edges)) } - else stop("Insuficcient number of columns (", nCols,")") + else stop("Insufficient number of columns (", k,")") } - else stop(objClass, - " class not allowed, try with a \"matrix\" or a \"data.frame\"") + else stop("-", objClass, + "- class not supported, try with a \"matrix\" or a \"data.frame\"") } .defAtt <- function(x, parent) { @@ -71,7 +68,7 @@ edge.list <- function(x) { ) for (i in attvec) - tmpdoc <- c(tmpdoc, .writeXMLLine("attvalue", tmpatt[i, ]) , sep="") + tmpdoc <- c(tmpdoc, .writeXMLLine("attvalue", tmpatt[i,,drop=FALSE ]) , sep="") paste(c("", tmpdoc, ""), sep="", collapse="") } @@ -151,7 +148,7 @@ edge.list <- function(x) { # Loop if there are not any attributes if (!attributes && !vizattributes) { for (i in vec) { - XML::parseXMLAndAdd(.writeXMLLine(type, datasetnoatt[i,]),parent=PAR) + XML::parseXMLAndAdd(.writeXMLLine(type, datasetnoatt[i,,drop=FALSE]),parent=PAR) } return(NULL) } @@ -162,7 +159,7 @@ edge.list <- function(x) { for (i in vec) { # Adding directly XML::parseXMLAndAdd( - paste(.writeXMLLine(type, datasetnoatt[i,], finalizer=FALSE), + paste(.writeXMLLine(type, datasetnoatt[i,,drop=FALSE], finalizer=FALSE), .addAtts(att[i,], attvec), # Builds atts definition "",sep=""), parent=PAR) @@ -175,20 +172,20 @@ edge.list <- function(x) { # Node/Edge + Atts if (attributes) { tempnode0 <- paste( - .writeXMLLine(type, datasetnoatt[i,], finalizer=FALSE), + .writeXMLLine(type, datasetnoatt[i,,drop=FALSE], finalizer=FALSE), .addAtts(att[i,], attvec), sep="") } - else tempnode0 <- .writeXMLLine(type, datasetnoatt[i,], finalizer=FALSE) + else tempnode0 <- .writeXMLLine(type, datasetnoatt[i,,drop=FALSE], finalizer=FALSE) # Viz Att printing # Colors if (vizcolors) { - tempnode0 <- paste(tempnode0, .writeXMLLine("color", vizcol.df[i,]), + tempnode0 <- paste(tempnode0, .writeXMLLine("color", vizcol.df[i,,drop=FALSE]), sep="") } # Position if (vizposition) { - tempnode0 <- paste(tempnode0, .writeXMLLine("position", vizpos.df[i,]), + tempnode0 <- paste(tempnode0, .writeXMLLine("position", vizpos.df[i,,drop=FALSE]), sep="") } # Size @@ -203,7 +200,7 @@ edge.list <- function(x) { } # Image if (vizimage) { - tempnode0 <- paste(tempnode0, .writeXMLLine("shape", vizimg.df[i,]), + tempnode0 <- paste(tempnode0, .writeXMLLine("shape", vizimg.df[i,,drop=FALSE]), sep="") } XML::parseXMLAndAdd(sprintf("%s",tempnode0, type), parent=PAR) @@ -213,12 +210,13 @@ edge.list <- function(x) { -#' Builds a graph of \code{gexf} class +#' Creates an object of class \code{gexf} #' -#' \code{write.gexf} takes a \code{node} matrix (or dataframe) and an +#' Takes a \code{node} matrix (or dataframe) and an #' \code{edge} matrix (or dataframe) and creates a \code{gexf} object #' containing a data-frame representation and a gexf representation of a graph. #' +#' @details #' Just like \code{nodesVizAtt} and \code{edgesVizAtt}, \code{nodesAtt} and #' \code{edgesAtt} must have the same number of rows as nodes and edges, #' respectively. Using data frames is necessary as in this way data types are @@ -286,6 +284,7 @@ edge.list <- function(x) { #' @param encoding Encoding of the graph. #' @param vers Character scalar. Version of the GEXF format to generate. #' By default \code{"1.3"}. +#' @param ... Passed to \code{gexf}. #' @return A \code{gexf} class object (list). Contains the following: \itemize{ #' \item \code{meta} : (list) Meta data describing the graph. \item #' \code{mode} : (list) Sets the default edge type and the graph mode. \item @@ -317,8 +316,12 @@ edge.list <- function(x) { #' demo(gexfbuildfromscratch) # Example building a net from scratch. #' } #' +#' @name gexf-class +NULL + #' @export -write.gexf <- function( +#' @rdname gexf-class +gexf <- function( ################################################################################ # Prints the gexf file ################################################################################ @@ -346,21 +349,23 @@ write.gexf <- function( ############################################################################## # CLASS CHECKS AND OTHERS CHECKS - # version - vers <- gexf_version(vers) - # Nodes - if (is.data.frame(nodes) | is.matrix(nodes)) { + if (inherits(nodes, c("data.frame", "matrix"))) { if (NCOL(nodes) != 2) stop("-nodes- should have two columns not ", NCOL(nodes)) } else stop("Invalid object type: -nodes- should be a two column data.frame or a matrix") # Edges - if (is.data.frame(edges) | is.matrix(edges)) { + if (inherits(edges, c("data.frame", "matrix"))) { if (NCOL(edges) != 2) stop("-edges- should have two columns not ", NCOL(edges)) } else stop("Invalid object type: -edges- should be a two column data.frame or a matrix") + # version + vers <- gexf_version(vers) + n <- nrow(nodes) + m <- nrow(edges) + # Edges Label .parseEdgesLabel(edgesLabel, edges) @@ -374,13 +379,24 @@ write.gexf <- function( .parseEdgesWeight(edgesWeight, edges) # Parsing edges Viz Att - nEdgesVizAtt <- .parseEdgesVizAtt(edgesVizAtt, edges) + edgesVizAtt <- if (length(unlist(edgesVizAtt))) { + Map(function(a, b) parseVizAtt(a, b, m, "edges"), a=names(edgesVizAtt), + b=edgesVizAtt) + } else NULL + + nEdgesVizAtt <- length(edgesVizAtt) + # nEdgesVizAtt <- .parseEdgesVizAtt(edgesVizAtt, edges) # Nodes Att nNodesAtt <- .parseNodesAtt(nodesAtt, nodes) # Parsing nodes Viz Atts - nNodesVizAtt <- .parseNodesVizAtt(nodesVizAtt, nodes) + nodesVizAtt <- if (length(unlist(nodesVizAtt))) { + Map(function(a, b) parseVizAtt(a, b, n, "nodes"), a=names(nodesVizAtt), + b=nodesVizAtt) + } else NULL + + nNodesVizAtt <- length(nodesVizAtt) # Checking the number of digits if (!is.integer(digits)) stop("Invalid number of digits ",digits, @@ -393,14 +409,16 @@ write.gexf <- function( if (length(nodeDynamic) > 0) { if (is.data.frame(nodeDynamic) | is.matrix(nodeDynamic)) { if (NROW(nodeDynamic) == NROW(nodes)) dynamic[1] <- TRUE - else stop("Insuficient number of rows: -nodeDynamic- (",NROW(nodeDynamic), " rows) should have the same number of rows than nodes there are (", NROW(nodes),")") + else stop("Insufficient number of rows: -nodeDynamic- (",NROW(nodeDynamic), + " rows) should have the same number of rows than nodes there are (", + NROW(nodes),")") } else stop("Invalid object type: -nodeDynamic- should be a two columns data.frame or a matrix") } if (length(edgeDynamic) > 0) { if (is.data.frame(edgeDynamic) | is.matrix(edgeDynamic)) { if (NROW(edgeDynamic) == NROW(edges)) dynamic[2] <- TRUE - else stop("Insuficient number of rows: -edgeDynamic- (",NROW(edgeDynamic), " rows) should have the same number of rows than edges there are (", NROW(edges),")") + else stop("Insufficient number of rows: -edgeDynamic- (",NROW(edgeDynamic), " rows) should have the same number of rows than edges there are (", NROW(edges),")") } else stop("Invalid object type: -edgeDynamic- should be a two columns data.frame or a matrix") } @@ -702,8 +720,8 @@ write.gexf <- function( atts.definitions=list(nodes = nodesAttDf, edges = edgesAttDf), nodesVizAtt=nodesVizAtt, edgesVizAtt=edgesVizAtt, - nodes=nodes, - edges=cbind(edges,edgesLabel), + nodes=as.data.frame(nodes), + edges=as.data.frame(cbind(edges,edgesLabel)), graph=XML::saveXML(xmlFile, encoding=encoding) ) @@ -723,3 +741,12 @@ write.gexf <- function( print(results, file=output, replace=TRUE) } } + + +#' @export +#' @rdname gexf-class +write.gexf <- function(...) { + warning("In future versions, rgexf 2.0, this function will be", + " the equivalent of -print(..., file=)-, and replaced by -gexf-") + gexf(...) +} diff --git a/README.Rmd b/README.Rmd index e42ce72..6c38bf7 100644 --- a/README.Rmd +++ b/README.Rmd @@ -6,21 +6,28 @@ output: github_document [![Downloads](https://cranlogs.r-pkg.org/badges/grand-total/rgexf)](http://cran.rstudio.com/package=rgexf) [![Travis-CI Build Status](https://travis-ci.org/gvegayon/rgexf.svg?branch=master)](https://travis-ci.org/gvegayon/rgexf) [![AppVeyor Build Status](https://ci.appveyor.com/api/projects/status/github/gvegayon/rgexf?branch=master&svg=true)](https://ci.appveyor.com/project/gvegayon/rgexf) +[![Coverage Status](https://img.shields.io/codecov/c/github/gvegayon/rgexf/master.svg)](https://codecov.io/github/gvegayon/rgexf?branch=master) # rgexf: Build, Import and Export GEXF Graph Files The first R package to work with GEXF graph files (used in Gephi and others). Using XML library, it allows the user to easily build/read graph files including attributes, GEXF viz attributes (such as colour, size, and position), network dynamics (for both edges and nodes, including spells) and edges weighting. Users can build/handle graphs element-by-element or massively through data-frames, visualize the graph on a web browser through sigmajs javascript library and interact with the igraph package. ## News ## -[2016-11-08] Restarting the project. -[2015-02-03] Version 0.15.2.3 of rgexf is on CRAN. Just updating emails... -[2014-03-10] Version 0.14.9 of rgexf is on CRAN! solves issues 15-18. Thanks =). -[2013-08-07] Version 0.13.8 of rgexf is on CRAN! New plot.gexf method and igraph integration working =). -[2013-05-09] Version 0.13.05 of rgexf (transitory) solves issues N 9 & 10. Looking forward for the next CRAN version. -[2013-03-14] Version 0.13.03 of rgexf is on its way to CRAN. It now supports working with spells! -[2013-01-04] Version 0.13.01 of rgexf is on its way to CRAN. Significant improvements and new features! -[2012-06-19] Version 0.12.06 of rgexf is on CRAN! Now it can be directly download from R. -[2012-03-29] Version 0.12.03.29 of rgexf has been released including many bug fixes. Please download the lastest version to check it out. +- [2016-11-08] Restarting the project. +- [2015-02-03] Version 0.15.2.3 of rgexf is on CRAN. Just updating emails... +- [2014-03-10] Version 0.14.9 of rgexf is on CRAN! solves issues 15-18. Thanks =). +- [2013-08-07] Version 0.13.8 of rgexf is on CRAN! New plot.gexf method and igraph + integration working =). +- [2013-05-09] Version 0.13.05 of rgexf (transitory) solves issues N 9 & 10. Looking + forward for the next CRAN version. +- [2013-03-14] Version 0.13.03 of rgexf is on its way to CRAN. It now supports + working with spells! +- [2013-01-04] Version 0.13.01 of rgexf is on its way to CRAN. Significant + improvements and new features! +- [2012-06-19] Version 0.12.06 of rgexf is on CRAN! Now it can be directly download + from R. +- [2012-03-29] Version 0.12.03.29 of rgexf has been released including many bug + fixes. Please download the lastest version to check it out. ## Example 1: Static net ## ```{r} diff --git a/build_rgexf.sh b/build_rgexf.sh deleted file mode 100644 index 6edb4f7..0000000 --- a/build_rgexf.sh +++ /dev/null @@ -1,8 +0,0 @@ -cd .. -R CMD REMOVE rgexf -rm -f rgexf_* -R CMD build rgexf -R CMD check --as-cran rgexf_* -R CMD INSTALL rgexf_* -cd rgexf -# Rscript test.rgexf.R diff --git a/codecov.yml b/codecov.yml new file mode 100644 index 0000000..69cb760 --- /dev/null +++ b/codecov.yml @@ -0,0 +1 @@ +comment: false diff --git a/demo/gexf.R b/demo/gexf.R index b538152..84f60d6 100644 --- a/demo/gexf.R +++ b/demo/gexf.R @@ -42,32 +42,32 @@ edge.att ################################################################################ # First example: a simple net pause() -write.gexf(nodes=people, edges=relations) +gexf(nodes=people, edges=relations) ################################################################################ # Second example: a simple net with nodes attributes pause() -write.gexf(nodes=people, edges=relations, nodesAtt=node.att) +gexf(nodes=people, edges=relations, nodesAtt=node.att) ################################################################################ # Third example: a simple net with dynamic nodes pause() -write.gexf(nodes=people, edges=relations, nodeDynamic=time.nodes) +gexf(nodes=people, edges=relations, nodeDynamic=time.nodes) ################################################################################ # Fourth example: a simple net with dynamic nodes with attributes pause() -write.gexf(nodes=people, edges=relations, nodeDynamic=time.nodes, nodesAtt=node.att) +gexf(nodes=people, edges=relations, nodeDynamic=time.nodes, nodesAtt=node.att) ################################################################################ # Fifth example: a simple net with dynamic edges with attributes pause() -write.gexf(nodes=people, edges=relations, edgeDynamic=time.edges, edgesAtt=edge.att) +gexf(nodes=people, edges=relations, edgeDynamic=time.edges, edgesAtt=edge.att) ################################################################################ # Sixth example: a simple net with dynamic edges and nodes with attributes pause() -write.gexf(nodes=people, edges=relations, edgeDynamic=time.edges, edgesAtt=edge.att, +gexf(nodes=people, edges=relations, edgeDynamic=time.edges, edgesAtt=edge.att, nodeDynamic=time.nodes, nodesAtt=node.att) ################################################################################ @@ -90,7 +90,7 @@ colnames(edgecolors) <- c("r", "b", "g", "a") nodetruefalse <- data.frame(nodetrue=rnorm(NROW(people)) > 0) edgetruefalse <- data.frame(edgetrue=rnorm(NROW(relations)) > 0) -grafo <- write.gexf(nodes=people, edges=relations, +grafo <- gexf(nodes=people, edges=relations, nodesAtt=cbind(imagee,nodetruefalse), nodesVizAtt=list( shape=c("rectangle", "square", "triangle", "diamond"), @@ -105,4 +105,4 @@ grafo <- write.gexf(nodes=people, edges=relations, ), edgesAtt=edgetruefalse) -print(grafo) \ No newline at end of file +print(grafo) diff --git a/demo/gexfattributes.R b/demo/gexfattributes.R index 112f46f..0f80a74 100644 --- a/demo/gexfattributes.R +++ b/demo/gexfattributes.R @@ -38,6 +38,6 @@ edge.att # before the last closing # parenthesis in the following function -write.gexf(nodes=people, edges=relations, nodesAtt=node.att, edgesAtt=edge.att) +gexf(nodes=people, edges=relations, nodesAtt=node.att, edgesAtt=edge.att) -################################################################################ \ No newline at end of file +################################################################################ diff --git a/demo/gexfbasic.R b/demo/gexfbasic.R index e768d06..d713956 100644 --- a/demo/gexfbasic.R +++ b/demo/gexfbasic.R @@ -33,6 +33,6 @@ pause() # before the last closing # parenthesis in the following function -write.gexf(nodes=people, edges=relations) +gexf(nodes=people, edges=relations) -################################################################################ \ No newline at end of file +################################################################################ diff --git a/demo/gexfdynamic.R b/demo/gexfdynamic.R index 27f381e..c34021f 100644 --- a/demo/gexfdynamic.R +++ b/demo/gexfdynamic.R @@ -42,4 +42,4 @@ time.edges # parenthesis in the following function pause() -write.gexf(nodes=people, edges=relations, nodeDynamic=time.nodes) \ No newline at end of file +gexf(nodes=people, edges=relations, nodeDynamic=time.nodes) diff --git a/demo/gexfdynamicandatt.R b/demo/gexfdynamicandatt.R index dc55c49..63a9e71 100644 --- a/demo/gexfdynamicandatt.R +++ b/demo/gexfdynamicandatt.R @@ -52,5 +52,5 @@ time.edges # parenthesis in the following function pause() -write.gexf(nodes=people, edges=relations, edgeDynamic=time.edges, edgesAtt=edge.att, - nodeDynamic=time.nodes, nodesAtt=node.att) \ No newline at end of file +gexf(nodes=people, edges=relations, edgeDynamic=time.edges, edgesAtt=edge.att, + nodeDynamic=time.nodes, nodesAtt=node.att) diff --git a/demo/gexffull.R b/demo/gexffull.R index 2bc4605..da311f3 100644 --- a/demo/gexffull.R +++ b/demo/gexffull.R @@ -77,7 +77,7 @@ thick<-1:9 pause() -write.gexf(nodes=people, edgesWeight=thick, edges=relations, +gexf(nodes=people, edgesWeight=thick, edges=relations, edgeDynamic=time.edges, edgesAtt=edge.att, nodeDynamic=time.nodes, nodesAtt=node.att, nodesVizAtt = list( diff --git a/demo/gexfplot.R b/demo/gexfplot.R index 2d06525..b2d9be0 100644 --- a/demo/gexfplot.R +++ b/demo/gexfplot.R @@ -7,7 +7,7 @@ relations <- data.frame(source = c(1,1,1,2,3,4), target = c(4,2,3,3,4,2)) node.att <- data.frame(letrafavorita=letters[1:4], numbers=1:4) # No position arguments, so it will be random. -simple.gexf <- write.gexf(nodes=people, edges=relations, nodesAtt=node.att) +simple.gexf <- gexf(nodes=people, edges=relations, nodesAtt=node.att) gexf(simple.gexf) #### 'Les Miserable's example of Sigmajs #### @@ -75,7 +75,7 @@ positions <- cbind(positions, 0) # needs a z axis -graph <- write.gexf(nodes=nodes, +graph <- gexf(nodes=nodes, edges=relations, nodesVizAtt=list( color=nodecolors, diff --git a/demo/gexfrandom.R b/demo/gexfrandom.R index 6fe4919..5b00559 100644 --- a/demo/gexfrandom.R +++ b/demo/gexfrandom.R @@ -68,7 +68,7 @@ pos3[,1] <- pos3[,1] + max(pos2[,1])-min(pos[,1]) pause() # Plotting -graph <- write.gexf( +graph <- gexf( rbind(vertex1,vertex2,vertex3), rbind(edges1, edges2,edges3), nodesVizAtt=list( diff --git a/demo/gexftwitter.R b/demo/gexftwitter.R index fb898a5..510121a 100644 --- a/demo/gexftwitter.R +++ b/demo/gexftwitter.R @@ -31,6 +31,6 @@ relations<- subset(followers, select=c(source, target)) # Creating the follower-following network in gexf format with some nodes' attribute pause() -x1 <- write.gexf(nodos, relations, keepFactors=F, nodesAtt=nodos.att) +x1 <- gexf(nodos, relations, keepFactors=F, nodesAtt=nodos.att) summary(x1) diff --git a/man/write.gexf.Rd b/man/gexf-class.Rd similarity index 88% rename from man/write.gexf.Rd rename to man/gexf-class.Rd index 44a85e0..a1206e1 100644 --- a/man/write.gexf.Rd +++ b/man/gexf-class.Rd @@ -1,19 +1,22 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/rgexf.r -\name{write.gexf} +\name{gexf-class} +\alias{gexf} +\alias{gexf-class} \alias{write.gexf} -\title{Builds a graph of \code{gexf} class} +\title{Creates an object of class \code{gexf}} \usage{ -write.gexf(nodes, edges, edgesLabel = NULL, edgesId = NULL, - edgesAtt = NULL, edgesWeight = NULL, edgesVizAtt = list(color = NULL, - size = NULL, shape = NULL), nodesAtt = NULL, nodesVizAtt = list(color = - NULL, position = NULL, size = NULL, shape = NULL, image = NULL), - nodeDynamic = NULL, edgeDynamic = NULL, digits = getOption("digits"), - output = NA, tFormat = "double", defaultedgetype = "undirected", - meta = list(creator = "NodosChile", description = - "A graph file writing in R using \\"rgexf\\"", keywords = - "gexf graph, NodosChile, R, rgexf"), keepFactors = FALSE, +gexf(nodes, edges, edgesLabel = NULL, edgesId = NULL, edgesAtt = NULL, + edgesWeight = NULL, edgesVizAtt = list(color = NULL, size = NULL, shape = + NULL), nodesAtt = NULL, nodesVizAtt = list(color = NULL, position = NULL, + size = NULL, shape = NULL, image = NULL), nodeDynamic = NULL, + edgeDynamic = NULL, digits = getOption("digits"), output = NA, + tFormat = "double", defaultedgetype = "undirected", meta = list(creator + = "NodosChile", description = "A graph file writing in R using \\"rgexf\\"", + keywords = "gexf graph, NodosChile, R, rgexf"), keepFactors = FALSE, encoding = "UTF-8", vers = "1.3") + +write.gexf(...) } \arguments{ \item{nodes}{A two-column data-frame or matrix of \dQuote{id}s and @@ -71,6 +74,8 @@ the graph as a GEXF file.} \item{vers}{Character scalar. Version of the GEXF format to generate. By default \code{"1.3"}.} + +\item{...}{Passed to \code{gexf}.} } \value{ A \code{gexf} class object (list). Contains the following: \itemize{ @@ -86,7 +91,7 @@ edges' ids, labels, sources, targets and weights. \item \code{graph} : (String) GEXF (XML) representation of the graph. } } \description{ -\code{write.gexf} takes a \code{node} matrix (or dataframe) and an +Takes a \code{node} matrix (or dataframe) and an \code{edge} matrix (or dataframe) and creates a \code{gexf} object containing a data-frame representation and a gexf representation of a graph. } diff --git a/man/gexf-methods.Rd b/man/gexf-methods.Rd index fe3fb04..7a4884c 100644 --- a/man/gexf-methods.Rd +++ b/man/gexf-methods.Rd @@ -67,7 +67,7 @@ requires this). to target=c(4,2,3,3,4,2,4,1,1)) # Building gexf graph - mygraph <- write.gexf(nodes=people, edges=relations) + mygraph <- gexf(nodes=people, edges=relations) # Summary and pring summary(mygraph) diff --git a/man/rgexf-package.Rd b/man/rgexf-package.Rd index 5b3c639..fc7a004 100644 --- a/man/rgexf-package.Rd +++ b/man/rgexf-package.Rd @@ -3,7 +3,6 @@ \docType{package} \name{rgexf-package} \alias{gephi} -\alias{gexf} \alias{rgexf} \alias{rgexf-package} \title{Build, Import and Export GEXF Graph Files} @@ -26,9 +25,6 @@ attributes and colors. Please visit the project home for more information: \url{https://github.com/gvegayon/rgexf}. - -\tabular{ll}{ Package: \tab rgexf\cr Type: \tab Package\cr Version: \tab -0.16.9000\cr Date: \tab 2016-11-08\cr License: \tab MIT+file\cr } } \note{ See the GEXF primer for details on the GEXF graph format: diff --git a/only_comp.sh b/only_comp.sh deleted file mode 100644 index 6fdb233..0000000 --- a/only_comp.sh +++ /dev/null @@ -1,8 +0,0 @@ -cd .. -R CMD REMOVE rgexf -rm -f rgexf_* -R CMD build rgexf -#R CMD check --as-cran rgexf_* -R CMD INSTALL rgexf_* -cd rgexf -# Rscript test.rgexf.R diff --git a/rgexf.Rproj b/rgexf.Rproj index 4d263d7..ff46899 100644 --- a/rgexf.Rproj +++ b/rgexf.Rproj @@ -17,4 +17,4 @@ AutoAppendNewline: Yes BuildType: Package PackageUseDevtools: Yes PackageInstallArgs: --no-multiarch --with-keep.source -PackageRoxygenize: rd,collate,namespace,vignette +PackageRoxygenize: rd,collate,namespace diff --git a/tests/testthat.R b/tests/testthat.R new file mode 100644 index 0000000..46b8fd6 --- /dev/null +++ b/tests/testthat.R @@ -0,0 +1,4 @@ +library(testthat) +library(rgexf) + +test_check("rgexf") diff --git a/tests/testthat/test-test-gexf.R b/tests/testthat/test-test-gexf.R new file mode 100644 index 0000000..f921d4f --- /dev/null +++ b/tests/testthat/test-test-gexf.R @@ -0,0 +1,33 @@ +context("gexf function") + +nodes <- cbind(a=1:10, b=letters[1:10]) +edges <- matrix(sample(1:10, 20, TRUE), ncol=2) + +# ------------------------------------------------------------------------------ +test_that("data.frame or matrix work OK", { + + ans0 <- gexf(as.data.frame(nodes), as.data.frame(edges)) + ans1 <- gexf(nodes, edges) + + expect_equal(ans0,ans1) +}) + +# ------------------------------------------------------------------------------ +test_that("errors", { + # edge.list + expect_error(edge.list(cbind(1:10)), "number of columns") + expect_error(edge.list(list), "class not supported") + + # gexf + expect_error(gexf(nodes[,-1,drop=FALSE], edges), "nodes.+columns") + expect_error(gexf(nodes, edges[,-1,drop=FALSE]), "edges.+columns") + expect_error(gexf(nodes, edges, digits = 1.1), "digits") + expect_error(gexf(nodes, edges, nodeDynamic = nodes[-1,,drop=TRUE]), + "number of rows") + expect_error(gexf(nodes, edges, edgeDynamic = edges[-1,,drop=TRUE]), + "number of rows") + + expect_error(gexf(nodes, edges, nodeDynamic = list(1)),"should be a ") + expect_error(gexf(nodes, edges, edgeDynamic = list(1)),"should be a ") + +}) diff --git a/vignettes/rgexf.Rmd b/vignettes/rgexf.Rmd index dcaa63e..01ffe62 100644 --- a/vignettes/rgexf.Rmd +++ b/vignettes/rgexf.Rmd @@ -64,7 +64,7 @@ pos3 <- pos pos3[,1] <- pos3[,1] + max(pos2[,1])-min(pos[,1]) # Plotting -graph <- write.gexf( +graph <- gexf( rbind(vertex1,vertex2,vertex3), rbind(edges1, edges2,edges3), nodesVizAtt=list(