Skip to content

Commit

Permalink
Merge pull request #17 from lemna/master
Browse files Browse the repository at this point in the history
proposal to fix issue #16
  • Loading branch information
gforge authored Oct 25, 2016
2 parents 036bd87 + 6bd3910 commit 15506f4
Show file tree
Hide file tree
Showing 3 changed files with 20 additions and 4 deletions.
18 changes: 15 additions & 3 deletions R/txtFrmt.R
Original file line number Diff line number Diff line change
Expand Up @@ -177,7 +177,7 @@ txtPval <- function(pvalues,
#'
#' @param x The value/vector/data.frame/matrix to be rounded
#' @param digits The number of digits to round each element to.
#' If you provide a vector each element for corresponding columns.
#' If you provide a vector each element will apply to the corresponding columns.
#' @param excl.cols Columns to exclude from the rounding procedure.
#' This can be either a number or regular expression. Skipped if x is a vector.
#' @param excl.rows Rows to exclude from the rounding procedure.
Expand Down Expand Up @@ -205,7 +205,13 @@ txtRound <- function(x, ...){
#' @export
#' @rdname txtRound
txtRound.default = function(x, digits = 0, txt.NA = "", dec = ".", ...){
if(length(digits) > length(x)) stop("You have ", length(digits), " but only a vector of length ", length(x), ": ", paste(x, collape=", "))
if(length(digits) != 1 & length(digits) != length(x))
stop("You have ",
length(digits),
" digits specifications but a vector of length ",
length(x),
": ",
paste(x, collapse=", "))

dec_str <- sprintf("^[^0-9\\%s-]*([\\-]{0,1}(([0-9]*|[0-9]+[ 0-9]+)[\\%s]|)[0-9]+)(|[^0-9]+.*)$",
dec, dec)
Expand Down Expand Up @@ -281,7 +287,13 @@ txtRound.matrix <- function(x, digits = 0, excl.cols, excl.rows, ...){
if (length(rows) == 0)
stop("No rows to round")

if(length(digits) > length(cols)) stop("You have ", length(digits), " but only ", length(cols), " to apply them to: ", paste(cols, collape=", "))
if(length(digits) != 1 & length(digits) != length(cols))
stop("You have ",
length(digits),
" digits specifications but ",
length(cols),
" columns to apply them to: ",
paste(cols, collapse = ", "))

ret_x <- x
for (row in rows){
Expand Down
2 changes: 1 addition & 1 deletion man/txtRound.Rd

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

4 changes: 4 additions & 0 deletions tests/testthat/test-txtFrmt.R
Original file line number Diff line number Diff line change
Expand Up @@ -74,6 +74,10 @@ test_that("Numerical matrices",{

expect_equivalent(txtRound(matrix(c(NA, 2.22), ncol=1), 1, txt.NA = "missing")[1,1],
"missing")

expect_error(txtRound(test_mx, digits = c(2, 3, 4, 5)))

expect_error(txtRound(test_mx, digits = c(2, 3)))
})


Expand Down

0 comments on commit 15506f4

Please sign in to comment.