Skip to content

Commit

Permalink
Allow dt > 1
Browse files Browse the repository at this point in the history
  • Loading branch information
weshinsley committed Nov 22, 2024
1 parent 7bc8470 commit d6a25bb
Show file tree
Hide file tree
Showing 4 changed files with 38 additions and 13 deletions.
18 changes: 12 additions & 6 deletions R/filter-support.R
Original file line number Diff line number Diff line change
Expand Up @@ -53,12 +53,18 @@ check_dt <- function(dt, allow_null = FALSE, name = deparse(substitute(dt)),
if (dt <= 0) {
cli::cli_abort("Expected '{name}' to be greater than 0")
}
if (dt > 1) {
cli::cli_abort("Expected '{name}' to be at most 1")
}
if (!rlang::is_integerish(1 / dt)) {
cli::cli_abort("Expected '{name}' to be the inverse of an integer",
arg = "dt", call = call)
if (dt >= 1) {
if (!rlang::is_integerish(dt) || is.infinite(dt)) {
cli::cli_abort(
"Expected '{name}' to be an integer, if greater than 1",
arg = "dt", call = call)
}
} else {
if (!rlang::is_integerish(1 / dt)) {
cli::cli_abort(
"Expected '{name}' to be the inverse of an integer, if less than 1",
arg = "dt", call = call)
}
}
dt
}
Expand Down
12 changes: 8 additions & 4 deletions inst/include/dust2/r/helpers.hpp
Original file line number Diff line number Diff line change
Expand Up @@ -236,11 +236,15 @@ inline double check_dt(cpp11::list r_time_control, bool enabled = true,
cpp11::stop("Expected 'dt' to be greater than 0");
}
if (dt > 1) {
cpp11::stop("Expected 'dt' to be at most 1");
if (!is_integer_like(dt, eps)) {
cpp11::stop("Expected 'dt' to be an integer, if above 1");
}
}
const auto inv_dt = 1 / dt;
if (!is_integer_like(inv_dt, eps)) {
cpp11::stop("Expected 'dt' to be the inverse of an integer");
if (dt < 1) {
const auto inv_dt = 1 / dt;
if (!is_integer_like(inv_dt, eps)) {
cpp11::stop("Expected 'dt' to be the inverse of an integer, if below 1");
}
}
return dt;
}
Expand Down
7 changes: 5 additions & 2 deletions tests/testthat/test-filter-support.R
Original file line number Diff line number Diff line change
@@ -1,15 +1,18 @@
test_that("can validate that 'dt' is reasonable", {
expect_no_error(check_dt(1))
expect_no_error(check_dt(1 / 5))
expect_no_error(check_dt(2))
expect_no_error(check_dt(NULL, allow_null = TRUE))
expect_error(check_dt(-1, name = "dt"),
"Expected 'dt' to be greater than 0")
expect_error(check_dt(2, name = "dt"),
"Expected 'dt' to be at most 1")
expect_error(check_dt(2.5, name = "dt"),
"Expected 'dt' to be an integer, if greater than 1")
expect_error(check_dt(1 / 3.5, name = "dt"),
"Expected 'dt' to be the inverse of an integer")
expect_error(check_dt(NULL, name = "dt"),
"'dt' must be a scalar")
expect_error(check_dt(Inf, name = "dt"),
"Expected 'dt' to be an integer, if greater than 1")
})


Expand Down
14 changes: 13 additions & 1 deletion tests/testthat/test-walk.R
Original file line number Diff line number Diff line change
Expand Up @@ -85,7 +85,7 @@ test_that("provided dt is reasonable", {
"Expected 'dt' to be greater than 0")
expect_error(
dust_system_create(walk(), pars, n_particles = 10, dt = 1.5),
"Expected 'dt' to be at most 1")
"Expected 'dt' to be an integer, if greater than 1")
expect_error(
dust_system_create(walk(), pars, n_particles = 10, dt = sqrt(2) / 2),
"Expected 'dt' to be the inverse of an integer")
Expand All @@ -111,6 +111,18 @@ test_that("time aligns to grid when dt is less than 1", {
fixed = TRUE)
})

test_that("time aligns to grid when dt is more than 1", {
pars <- list(sd = 1, random_initial = TRUE)
obj <- dust_system_create(walk(), pars, n_particles = 10, dt = 2.0,
time = 0.0)
expect_equal(dust_system_time(obj), 0.0)

expect_error(
dust_system_create(walk(), pars, n_particles = 10, dt = 2.0,
time = 1.0),
"'time' must be a multiple of 'dt'")
})


## Not a test at all of the system, but of the error handling in
## helpers.hpp
Expand Down

0 comments on commit d6a25bb

Please sign in to comment.