Skip to content

Commit

Permalink
improve bound & isBound
Browse files Browse the repository at this point in the history
  • Loading branch information
Qile0317 committed Jul 28, 2024
1 parent 90a95df commit 42c1abc
Show file tree
Hide file tree
Showing 4 changed files with 43 additions and 21 deletions.
6 changes: 4 additions & 2 deletions R/character.R
Original file line number Diff line number Diff line change
@@ -1,10 +1,12 @@
#' Extract Substring from Start to End Difference
#'
#' This function extracts a substring from a given start position to the position determined by subtracting `endDiff` from the string length.
#' Extract a substring from a given start position to the position
#' determined by subtracting `endDiff` from the string length.
#'
#' @param x A character string from which the substring is extracted.
#' @param start The starting position for the substring extraction.
#' @param endDiff The difference to subtract from the string length to determine the end position.
#' @param endDiff The difference to subtract from the string length to
#' determine the end position.
#'
#' @return A substring of the input character string.
#' @export
Expand Down
6 changes: 3 additions & 3 deletions R/color.R
Original file line number Diff line number Diff line change
Expand Up @@ -23,10 +23,10 @@
#'
getAvgHex <- function(...) {

hex_vector <- unlist(list(...))
hexVector <- unlist(list(...))

Reduce(add, lapply(hex_vector, grDevices::col2rgb)) %>%
divide(length(hex_vector)) %>%
Reduce(add, lapply(hexVector, grDevices::col2rgb)) %>%
divide(length(hexVector)) %>%
round() %>%
t() %>%
grDevices::rgb(maxColorValue = 256)
Expand Down
24 changes: 21 additions & 3 deletions R/math.R
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
#' Bound a Number within a Range
#'
#' This function bounds a number within a specified range.
#' This function bounds a number within a specified range. This function
#' is vectorized in a way such that either or both lowerbound and upperbound
#' can be length 1 or the same length as the input vector.
#'
#' @param num A numeric vector to be bounded.
#' @param lowerbound The lower bound of the range.
Expand All @@ -15,12 +17,15 @@
#' bound(1:10, -1, 5)
#'
bound <- function(num, lowerbound, upperbound) {
sapply(num, function(x) min(max(x, lowerbound), upperbound))
.assertNumAndBoundsAreValid(num, lowerbound, upperbound)
pmin(pmax(num, lowerbound), upperbound)
}

#' Check if a Number is within a Range
#'
#' This function checks if a number is within a specified range.
#' This function checks if a number is within a specified range. This function
#' is vectorized in a way such that either or both lowerbound and upperbound
#' can be length 1 or the same length as the input vector.
#'
#' @param num A numeric vector to be checked.
#' @param lowerbound The lower bound of the range.
Expand All @@ -36,9 +41,22 @@ bound <- function(num, lowerbound, upperbound) {
#' isBound(1:10, -1, 5)
#'
isBound <- function(num, lowerbound, upperbound) {
.assertNumAndBoundsAreValid(num, lowerbound, upperbound)
(num >= lowerbound) & (num <= upperbound)
}

.assertNumAndBoundsAreValid <- function(num, lowerbound, upperbound) {
assertthat::assert_that(is.numeric(num))
assertthat::assert_that(is.numeric(lowerbound))
assertthat::assert_that(
length(lowerbound) == 1 || length(lowerbound) == length(num)
)
assertthat::assert_that(is.numeric(upperbound))
assertthat::assert_that(
length(upperbound) == 1 || length(upperbound) == length(num)
)
}

#' Add Two Objects
#'
#' This function adds two objects. If both objects are numeric vectors,
Expand Down
28 changes: 15 additions & 13 deletions tests/testthat/test-math.R
Original file line number Diff line number Diff line change
@@ -1,36 +1,38 @@
test_that("Bound a Number within a Range", {
expect_equal(bound(5, 1, 10), 5)
expect_equal(bound(c(0, 5, 15), 1, 10), c(1, 5, 10))
expect_equal(bound(5, 1, 10), 5)
expect_equal(bound(c(0, 5, 15), 1, 10), c(1, 5, 10))
expect_equal(bound(1:7, 4, rep(6, 7)), c(4, 4, 4, 4, 5, 6, 6))
expect_equal(bound(1:7, rep(4, 7), rep(6, 7)), c(4, 4, 4, 4, 5, 6, 6))
})

test_that("Check if a Number is within a Range", {
expect_equal(isBound(5, 1, 10), TRUE)
expect_equal(isBound(c(0, 5, 15), 1, 10), c(FALSE, TRUE, FALSE))
expect_equal(isBound(5, 1, 10), TRUE)
expect_equal(isBound(c(0, 5, 15), 1, 10), c(FALSE, TRUE, FALSE))
})

test_that("Add Two Objects", {
expect_equal(add(2, 3), 5)
expect_equal(add("hello", "world"), "helloworld")
expect_equal(add(2, 3), 5)
expect_equal(add("hello", "world"), "helloworld")
})

test_that("Subtract Two Numbers", {
expect_equal(subtract(5, 3), 2)
expect_equal(subtract(5, 3), 2)
})

test_that("Multiply Two Numbers", {
expect_equal(multiply(2, 3), 6)
expect_equal(multiply(2, 3), 6)
})

test_that("Divide Two Numbers", {
expect_equal(divide(6, 3), 2)
expect_equal(divide(6, 3), 2)
})

test_that("Check if a Number is Even", {
expect_equal(isEven(4), TRUE)
expect_equal(isEven(5), FALSE)
expect_equal(isEven(4), TRUE)
expect_equal(isEven(5), FALSE)
})

test_that("Check if a Number is Odd", {
expect_equal(isOdd(4), FALSE)
expect_equal(isOdd(5), TRUE)
expect_equal(isOdd(4), FALSE)
expect_equal(isOdd(5), TRUE)
})

0 comments on commit 42c1abc

Please sign in to comment.