Skip to content

Commit

Permalink
Merge pull request #14 from richierocks/master
Browse files Browse the repository at this point in the history
Fixes for issues #12 and #13
  • Loading branch information
gaborcsardi committed May 26, 2016
2 parents 2cc7caa + 33747e5 commit 134914a
Show file tree
Hide file tree
Showing 4 changed files with 36 additions and 12 deletions.
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -2,5 +2,6 @@

export(cyclocomp)
export(cyclocomp_package)
export(cyclocomp_q)
importFrom(utils,head)
importFrom(utils,tail)
19 changes: 12 additions & 7 deletions R/cyclocomp.R
Original file line number Diff line number Diff line change
Expand Up @@ -12,11 +12,7 @@ NULL

#' Cyclomatic Complexity of R Code
#'
#' Cyclomatic complexity is a software metric (measurement), used to indicate
#' the complexity of a program. It is a quantitative measure of the number of
#' linearly independent paths through a program's source code. It was developed
#' by Thomas J. McCabe, Sr. in 1976.
#'
#' Calculate the cyclomatic complexity of an R function or expression.
#' @param expr An R function or expression.
#' @return Integer scalar, the cyclomatic complexity of the
#' expression.
Expand All @@ -33,7 +29,9 @@ NULL
#'
#' ## Or a quoted expression
#' cyclocomp(quote( if (condition) "foo" else "bar" ))
#' cyclocomp(quote( while (condition) { loop } ))
#'
#' ## cyclocomp_q quotes the expression for you
#' cyclocomp_q(while (condition) { loop })
#'
#' ## Complexity of individual control flow constructs
#' cyclocomp(quote({
Expand Down Expand Up @@ -96,9 +94,16 @@ cyclocomp <- function(expr) {
cyclocomp_package <- function(package) {
names <- ls(asNamespace(package))
cc <- vapply(names, function(n) cyclocomp(get(n, asNamespace(package))), 1L)
data.frame(
d <- data.frame(
stringsAsFactors = FALSE,
name = unname(names),
cyclocomp = unname(cc)
)
d[order(d$cyclocomp, decreasing = TRUE), ]
}

#' @rdname cyclocomp
#' @export
cyclocomp_q <- function(expr) {
cyclocomp(substitute(expr))
}
12 changes: 7 additions & 5 deletions man/cyclocomp.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

16 changes: 16 additions & 0 deletions tests/testthat/test-cyclocomp_q.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@

context("cyclocomp_q")

test_that("cyclocomp_q works the same as cyclocomp + quote", {


expect_equal(
cyclocomp_q(if (TRUE) "foo" else if(FALSE) "bar" else "baz"),
cyclocomp(quote(if (TRUE) "foo" else if(FALSE) "bar" else "baz")))

expect_equal(
cyclocomp_q(while(condition && another_condition) if(something) do_something else break),
cyclocomp(quote(while(condition && another_condition) if(something) do_something else break)))

})

0 comments on commit 134914a

Please sign in to comment.