Skip to content

Commit

Permalink
refine tests
Browse files Browse the repository at this point in the history
  • Loading branch information
DanChaltiel committed Jan 28, 2025
1 parent b534896 commit 4a5cbb6
Show file tree
Hide file tree
Showing 4 changed files with 59 additions and 4 deletions.
40 changes: 40 additions & 0 deletions tests/testthat/helper-init.R
Original file line number Diff line number Diff line change
Expand Up @@ -133,6 +133,46 @@ test_autoimport = function(files, bad_ns=FALSE, use_cache=FALSE, root=NULL, ...,
#diapo 3 donc en non-binding on est surpuissant ou c'est juste une paramétrisation ?


#' @examples
#' warn("hello", class="foobar") %>% expect_classed_conditions(warning_class="foo")
expect_classed_conditions = function(expr, message_class=NULL, warning_class=NULL, error_class=NULL){
dummy = c("rlang_message", "message", "rlang_warning", "warning", "rlang_error", "error", "condition")
ms = list()
ws = list()
es = list()
x = withCallingHandlers(
withRestarts(expr, muffleStop=function() "expect_classed_conditions__error"),
message=function(m){
ms <<- c(ms, list(m))
invokeRestart("muffleMessage")
},
warning=function(w){
ws <<- c(ws, list(w))
invokeRestart("muffleWarning")
},
error=function(e){
es <<- c(es, list(e))
invokeRestart("muffleStop")
}
)

f = function(cond_list, cond_class){
cl = map(cond_list, class) %>% purrr::flatten_chr()
missing = setdiff(cond_class, cl) %>% setdiff(dummy)
extra = setdiff(cl, cond_class) %>% setdiff(dummy)
if(length(missing)>0 || length(extra)>0){
cli_abort(c("{.arg {caller_arg(cond_class)}} is not matching thrown conditions:",
i="Missing expected classes: {.val {missing}}",
i="Extra unexpected classes: {.val {extra}}"),
call=rlang::caller_env())
}
}
f(es, error_class)
f(ws, warning_class)
f(ms, message_class)
expect_true(TRUE)
x
}

condition_overview = function(expr){
tryCatch2(expr) %>% attr("overview")
Expand Down
3 changes: 3 additions & 0 deletions tests/testthat/source/R/sample_funs.R
Original file line number Diff line number Diff line change
Expand Up @@ -75,4 +75,7 @@ dplyr::`%>%`

#this is
#a trailing comment
#with multiple empty lines at EOF



4 changes: 4 additions & 0 deletions tests/testthat/source/R/sample_funs2.R
Original file line number Diff line number Diff line change
Expand Up @@ -46,3 +46,7 @@ foobar = function(){
bind_rows()
}


#this is
#a trailing comment
#with only one empty line at EOF
16 changes: 12 additions & 4 deletions tests/testthat/test-ai_errors.R
Original file line number Diff line number Diff line change
@@ -1,10 +1,18 @@

test_that("autoimport warnings", {
test_autoimport(files="sample_funs2.R") %>%
ai = test_autoimport(files="sample_funs2.R") %>%
suppressMessages() %>%
expect_warning(class="autoimport_duplicate_warn") %>%
expect_warning(class="autoimport_fun_not_in_desc_warn") %>%
expect_warning(class="autoimport_fun_not_found_warn")
expect_classed_conditions(warning_class=c("autoimport_duplicate_warn",
"autoimport_fun_not_in_desc_warn",
"autoimport_fun_not_found_warn"))

target_dir = attr(ai, "target_dir")
target_file = path(target_dir, "sample_funs2.R")
expect_true(file_exists(target_dir))

#test output
out1 = readLines(target_file)
expect_in(c("#this is", "#a trailing comment"), out1)
})


Expand Down

0 comments on commit 4a5cbb6

Please sign in to comment.