Skip to content

Commit

Permalink
Tests for color utilities and global settings (#285)
Browse files Browse the repository at this point in the history
* Tests for color utilities

* tests for global settings

* Use functions for error messages
  • Loading branch information
IndrajeetPatil authored Jul 27, 2022
1 parent 1d7e876 commit f402204
Show file tree
Hide file tree
Showing 6 changed files with 76 additions and 1 deletion.
4 changes: 4 additions & 0 deletions R/messages.R
Original file line number Diff line number Diff line change
Expand Up @@ -48,6 +48,10 @@ messages$valueShouldNotBeNegative <- function(parameterName, value) {
paste0(parameterName, " must be a positive numerical value, but the value is ", value)
}

messages$nrOfColorsShouldBePositive <- function(nrOfColors) {
paste0("nrOfColors must be positive, value ", nrOfColors, " is not valid!")
}


messages$noPKDataToWrite <- function() {
"`pkDataFilePath` argument is specified, but there is no PK parameters data to write to spreadsheets."
Expand Down
2 changes: 1 addition & 1 deletion R/utilities-figures.R
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ esqLABS_colors <- function(nrOfColors) {
deltaV_r_g <- max(esqRed_hsv[3], esqGreen_hsv[3]) - min(esqRed_hsv[3], esqGreen_hsv[3])

if (nrOfColors < 0) {
stop("nrOfColors must be positive, value ", nrOfColors, " is not valid!")
stop(messages$nrOfColorsShouldBePositive(nrOfColors))
}
if (nrOfColors == 0) {
return(c())
Expand Down
2 changes: 2 additions & 0 deletions R/zzz.R
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
# nocov start
.onLoad <- function(...) {
options(warnPartialMatchDollar = TRUE)
Sys.setenv("_R_CHECK_LENGTH_1_CONDITION_" = "true")
}
# nocov end
18 changes: 18 additions & 0 deletions tests/testthat/_snaps/esqlabsr-settings.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
# Names for settings are as expected

Code
esqlabsRSettingNames
Output
$packageVersion
[1] "packageVersion"
$packageName
[1] "packageName"
$widthPerPlotMapping
[1] "widthPerPlotMapping"
$heightPerPlotMapping
[1] "heightPerPlotMapping"

12 changes: 12 additions & 0 deletions tests/testthat/test-esqlabsr-settings.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
test_that("Names for settings are as expected", {
expect_snapshot(esqlabsRSettingNames)
})

test_that("Check that values for package environment bindings are correct", {
expect_error(
getEsqlabsRSetting("xyz"),
messages$errorPackageSettingNotFound("xyz", esqlabsEnv)
)

expect_equal(getEsqlabsRSetting("packageName"), "esqlabsR")
})
39 changes: 39 additions & 0 deletions tests/testthat/test-utilities-figures.R
Original file line number Diff line number Diff line change
@@ -1,12 +1,51 @@
## context("esqLABS_colors")

test_that("esqLABS_colors input validation works as expected", {
expect_error(esqLABS_colors(-1), messages$nrOfColorsShouldBePositive(-1))
})

test_that("esqLABS_colors wprks with empty argument vector", {
expect_equal(length(esqLABS_colors(0)), 0)
})

test_that("esqLABS_colors returns two colors", {
expect_equal(length(esqLABS_colors(2)), 2)
})

test_that("esqLABS_colors returns three colors", {
expect_equal(length(esqLABS_colors(3)), 3)
})

test_that("esqLABS_colors returns ten colors", {
expect_equal(length(esqLABS_colors(10)), 10)
})

test_that("esqLABS_colors returns ten colors", {
expect_equal(length(esqLABS_colors(10)), 10)
})

## context("col2hsv")

test_that("col2hsv returns expected HSV values for a given R color name", {
expect_equal(
col2hsv("yellow"),
structure(c(0.166666666666667, 1, 1),
.Dim = c(3L, 1L),
.Dimnames = list(c("h", "s", "v"), NULL)
)
)

expect_equal(
col2hsv("white"),
structure(c(0, 0, 1),
.Dim = c(3L, 1L),
.Dimnames = list(c("h", "s", "v"), NULL)
)
)
})



## context("createEsqlabsPlotConfiguration")

test_that("createEsqlabsPlotConfiguration() creates object with chosen defaults", {
Expand Down

0 comments on commit f402204

Please sign in to comment.