Skip to content

Commit

Permalink
tests: utils-documentation is now covered
Browse files Browse the repository at this point in the history
  • Loading branch information
atsyplenkov committed Jan 8, 2025
1 parent b35affa commit b0c8459
Show file tree
Hide file tree
Showing 2 changed files with 121 additions and 1 deletion.
6 changes: 5 additions & 1 deletion R/utils_documentation.R
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
#' @keywords internal
rd_wbw_link <-
function(fun_name) {
checkmate::assert_character(fun_name, min.chars = 1L)
paste0(
"@references For more information, see ",
"<https://www.whiteboxgeo.com/manual",
Expand All @@ -23,6 +24,7 @@ rd_wbw_link <-
#' @keywords internal
rd_input_raster <-
function(param) {
checkmate::assert_character(param, min.chars = 1L)
paste0(
"@param ", param,
" Raster object of class [WhiteboxRaster]. ",
Expand All @@ -35,6 +37,8 @@ rd_input_raster <-
#' @keywords internal
rd_example <-
function(foo, args = NULL) {
checkmate::assert_character(foo, min.chars = 1L)
checkmate::assert_vector(args, null.ok = TRUE)
paste(
"@examples",
# "\\dontrun{",
Expand All @@ -51,4 +55,4 @@ rd_example <-
# "}",
sep = "\n"
)
}
}
116 changes: 116 additions & 0 deletions tests/testthat/test-utils-documentation.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,116 @@
test_that("rd_wbw_link creates correct reference links", {
# Test basic function name
expected <- paste0(
"@references For more information, see ",
"<https://www.whiteboxgeo.com/manual",
"/wbw-user-manual/book/tool_help.html#",
"slope>"
)
expect_equal(rd_wbw_link("slope"), expected)

# Test function name with underscores
expected <- paste0(
"@references For more information, see ",
"<https://www.whiteboxgeo.com/manual",
"/wbw-user-manual/book/tool_help.html#",
"breach_depressions>"
)
expect_equal(rd_wbw_link("breach_depressions"), expected)

# Test function name with numbers
expected <- paste0(
"@references For more information, see ",
"<https://www.whiteboxgeo.com/manual",
"/wbw-user-manual/book/tool_help.html#",
"d8_flow_accumulation>"
)
expect_equal(rd_wbw_link("d8_flow_accumulation"), expected)
})

test_that("rd_input_raster creates correct parameter documentation", {
# Test basic parameter name
expected <- paste0(
"@param dem Raster object of class [WhiteboxRaster]. ",
"See [wbw_read_raster()] for more details."
)
expect_equal(rd_input_raster("dem"), expected)

# Test parameter name with underscore
expected <- paste0(
"@param flow_acc Raster object of class [WhiteboxRaster]. ",
"See [wbw_read_raster()] for more details."
)
expect_equal(rd_input_raster("flow_acc"), expected)

# Test parameter name with numbers
expected <- paste0(
"@param dem2 Raster object of class [WhiteboxRaster]. ",
"See [wbw_read_raster()] for more details."
)
expect_equal(rd_input_raster("dem2"), expected)
})

test_that("rd_example creates correct example documentation", {
# Test without arguments
expected <- paste(
"@examples",
'f <- system.file("extdata/dem.tif", package = "wbw")',
"wbw_read_raster(f) |>",
" slope()",
sep = "\n"
)
expect_equal(rd_example("slope"), expected)

# Test with single argument
expected <- paste(
"@examples",
'f <- system.file("extdata/dem.tif", package = "wbw")',
"wbw_read_raster(f) |>",
" slope(units = 'degrees')",
sep = "\n"
)
expect_equal(rd_example("slope", "units = 'degrees'"), expected)

# Test with multiple arguments
expected <- paste(
"@examples",
'f <- system.file("extdata/dem.tif", package = "wbw")',
"wbw_read_raster(f) |>",
" breach_depressions(max_depth = 10, max_length = 100)",
sep = "\n"
)
expect_equal(
rd_example(
"breach_depressions",
c("max_depth = 10", "max_length = 100")
),
expected
)

# Test with NULL arguments
expected <- paste(
"@examples",
'f <- system.file("extdata/dem.tif", package = "wbw")',
"wbw_read_raster(f) |>",
" slope()",
sep = "\n"
)
expect_equal(rd_example("slope", NULL), expected)
})

test_that("documentation functions handle edge cases", {
# Test empty strings
expect_error(rd_wbw_link(""))
expect_error(rd_input_raster(""))
expect_error(rd_example(""))

# Test NULL inputs
expect_error(rd_wbw_link(NULL))
expect_error(rd_input_raster(NULL))
expect_error(rd_example(NULL))

# Test non-character inputs
expect_error(rd_wbw_link(123))
expect_error(rd_input_raster(123))
expect_error(rd_example(123))
})

0 comments on commit b0c8459

Please sign in to comment.