Skip to content

Commit

Permalink
Merge pull request #19 from datacamp/roxygen_fix
Browse files Browse the repository at this point in the history
Roxygen fix
  • Loading branch information
TimSangster committed Aug 26, 2022
2 parents acf563f + ac53374 commit 6b9f25d
Show file tree
Hide file tree
Showing 13 changed files with 246 additions and 121 deletions.
12 changes: 8 additions & 4 deletions DESCRIPTION
@@ -1,13 +1,18 @@
Package: testwhat.ext
Type: Package
Title: Extensions for testwhat
Version: 0.3.0
Authors@R: person("Filip", "Schouwenaars", ,"filip@datacamp.com", role = c("aut", "cre"))
Version: 0.3.1
Authors@R: c(
person("Filip", "Schouwenaars", email = "filip@datacamp.com", role = c("aut", "cre")),
person("Richie", "Cotton", email = "richie@datacamp.com", role = "ctb"),
person("Andy", "Chen", email = "andy.chen@datacamp.com", role = "ctb")
)
Description: This package contains functions that build off of the core
building blocks in testwhat. Often, these will be multiple simple
SCTs combined.
Imports:
magrittr,
purrr,
stats,
testwhat,
utils
Expand All @@ -19,5 +24,4 @@ Suggests:
roxygen2 (>= 6.1.0),
testthat
License: GPL-3 + file LICENSE
LazyData: TRUE
RoxygenNote: 6.1.0
RoxygenNote: 7.1.2
2 changes: 2 additions & 0 deletions NAMESPACE
Expand Up @@ -26,6 +26,8 @@ export(check_roxy_param_matches)
export(parse_desc)
export(parse_roxy)
importFrom(magrittr,"%>%")
importFrom(purrr,map)
importFrom(purrr,map_chr)
importFrom(stats,setNames)
importFrom(testwhat,ChildState)
importFrom(testwhat,build_pd)
Expand Down
55 changes: 37 additions & 18 deletions R/check-roxygen.R
Expand Up @@ -95,8 +95,8 @@ check_has_roxy_element <- function(state, element, index = 1L, missing_msg = NUL
element, index
)
}
actual <- is.null(student_pd[[index]][[element]])
check_that(is_false(actual), feedback = missing_msg)
actual <- roxygen2::block_has_tags(student_pd[[index]], element)
check_that(actual, feedback = missing_msg)
return(invisible(state))
}

Expand All @@ -116,8 +116,8 @@ check_roxy_element_equals <- function(state, element, index = 1L, incorrect_msg
)
}

actual <- student_pd[[index]][[element]]
expected <- solution_pd[[index]][[element]]
actual <- roxygen2::block_get_tag_value(student_pd[[index]], element)
expected <- roxygen2::block_get_tag_value(solution_pd[[index]], element)

check_that(is_equal(actual, expected), feedback = incorrect_msg)
return(invisible(state))
Expand All @@ -137,13 +137,14 @@ check_roxy_element_matches <- function(state, element, regex, fixed = FALSE, tim
element, index, regex
)
}
actual <- student_pd[[index]][[element]]
actual <- roxygen2::block_get_tag_value(student_pd[[index]], element)
num_hits <- get_num_hits(regex = regex, x = actual, fixed = fixed)
check_that(is_gte(num_hits, times), feedback = not_typed_msg)
return(invisible(state))
}

#' @rdname check_has_roxy
#' @importFrom purrr map_chr
#' @importFrom testwhat check_that is_false
#' @export
check_has_roxy_param <- function(state, param_name, index = 1L, missing_msg = NULL, append = TRUE) {
Expand All @@ -157,8 +158,9 @@ check_has_roxy_param <- function(state, param_name, index = 1L, missing_msg = NU
param_name, index
)
}
actual <- is.null(student_pd[[index]][["param"]][[param_name]])
check_that(is_false(actual), feedback = missing_msg)
student_param_tags <- roxygen2::block_get_tags(student_pd[[index]], "param")
actual <- param_name %in% map_chr(student_param_tags, ~ .x[["val"]][["name"]])
check_that(actual, feedback = missing_msg)
return(invisible(state))
}

Expand All @@ -176,13 +178,16 @@ check_roxy_param_matches <- function(state, param_name, regex, fixed = FALSE, in
param_name, index, regex
)
}
actual <- student_pd[[index]][["param"]][[param_name]]
student_param_tags <- roxygen2::block_get_tags(student_pd[[index]], "param")
param_idx <- which(map_chr(student_param_tags, ~ .x[["val"]][["name"]]) == param_name)
actual <- map_chr(student_param_tags, ~ .x[["val"]][["description"]])[param_idx]
num_hits <- get_num_hits(regex = regex, x = actual, fixed = fixed)
check_that(is_gte(num_hits, 1L), feedback = not_typed_msg)
return(invisible(state))
}

#' @rdname check_has_roxy
#' @importFrom purrr map_chr
#' @importFrom testwhat check_that is_true
#' @export
check_roxy_imports_package <- function(state, pkg_name, index = 1L, missing_msg = NULL, append = TRUE) {
Expand All @@ -196,9 +201,10 @@ check_roxy_imports_package <- function(state, pkg_name, index = 1L, missing_msg
index, pkg_name
)
}

pkgs_imported <- student_pd[[index]][["import"]]
student_import_tags <- roxygen2::block_get_tags(student_pd[[1]], "import")
pkgs_imported <- map_chr(student_import_tags, ~ .x[["val"]])
check_that(is_true(pkg_name %in% pkgs_imported), feedback = missing_msg)
return(invisible(state))
}

#' @rdname check_has_roxy
Expand All @@ -216,11 +222,15 @@ check_roxy_imports_from_package <- function(state, pkg_name, index = 1L, missing
index, pkg_name
)
}
pkg_to_import_from <- student_pd[[index]][["importFrom"]][[pkg_name]]
check_that(is_false(is.null(pkg_to_import_from)), feedback = missing_msg)
student_importFrom_tags <- roxygen2::block_get_tags(student_pd[[index]], "importFrom")
pkgs_to_import_from <- unique(purrr::map_chr(student_importFrom_tags, purrr::pluck, "val", 1))
check_that(is_true(pkg_name %in% pkgs_to_import_from), feedback = missing_msg)
return(invisible(state))
}

#' @rdname check_has_roxy
#' @importFrom purrr map_chr
#' @importFrom purrr map
#' @importFrom testwhat check_that
#' @importFrom testwhat is_true
#' @export
Expand All @@ -235,8 +245,12 @@ check_roxy_imports_object_from_package <- function(state, pkg_name, object_name,
index, object_name, pkg_name
)
}
imported_objects <- student_pd[[index]][["importFrom"]][[pkg_name]]
student_importFrom_tags <- roxygen2::block_get_tags(student_pd[[index]], "importFrom")
pkgs_to_import_from <- map_chr(student_importFrom_tags, ~ .x[["val"]][[1]])
this_pkg <- pkgs_to_import_from == pkg_name
imported_objects <- unlist(map(student_importFrom_tags[this_pkg], ~ .x[["val"]][-1]))
check_that(is_true(object_name %in% imported_objects), feedback = missing_msg)
return(invisible(state))
}

#' @rdname check_has_roxy
Expand All @@ -256,7 +270,8 @@ check_roxy_examples_run <- function(state, index = 1L, not_runnable_msg = NULL,
index
)
}
actual <- student_pd[[index]][["examples"]]
student_examples_tags <- roxygen2::block_get_tags(student_pd[[index]], "examples")
actual <- map_chr(student_examples_tags, ~ .x[["val"]])
is_runnable <- tryCatch({
eval_parse(pre_ex_code, student_env)
eval_parse(actual, student_env)
Expand All @@ -269,7 +284,8 @@ check_roxy_examples_run <- function(state, index = 1L, not_runnable_msg = NULL,
}

#' @rdname check_has_roxy
#' @importFrom testwhat check_that is_gte
#' @importFrom testwhat check_that
#' @importFrom testwhat is_gte
#' @export
check_roxy_examples_result_equals <- function(state, index = 1L, incorrect_msg = NULL, append = TRUE) {
check_roxy_examples_run(state, index)
Expand All @@ -289,10 +305,12 @@ check_roxy_examples_result_equals <- function(state, index = 1L, incorrect_msg =

set.seed(19790801)
eval_parse(pre_ex_code, student_env)
actual <- eval_parse(student_pd[[index]][["examples"]], student_env)
student_examples_tags <- roxygen2::block_get_tags(student_pd[[index]], "examples")
solution_examples_tags <- roxygen2::block_get_tags(solution_pd[[index]], "examples")
actual <- eval_parse(map_chr(student_examples_tags, ~ .x[["val"]]), student_env)
set.seed(19790801)
eval_parse(pre_ex_code, solution_env)
expected <- eval_parse(solution_pd[[index]][["examples"]], solution_env)
expected <- eval_parse(map_chr(solution_examples_tags, ~ .x[["val"]]), solution_env)

check_that(is_equal(actual, expected), feedback = incorrect_msg)
return(invisible(state))
Expand All @@ -312,7 +330,8 @@ check_roxy_example_matches <- function(state, regex, fixed = FALSE, index = 1L,
index, regex
)
}
actual <- student_pd[[index]][["examples"]]
student_examples_tags <- roxygen2::block_get_tags(student_pd[[index]], "examples")
actual <- map_chr(student_examples_tags, ~ .x[["val"]])
num_hits <- get_num_hits(regex = regex, x = actual, fixed = fixed)
check_that(is_gte(num_hits, 1L), feedback = not_typed_msg)
return(invisible(state))
Expand Down
9 changes: 1 addition & 8 deletions R/parse-roxygen.R
Expand Up @@ -20,15 +20,8 @@ extract_roxygen_from_code <- function(lines) {
# and roxygen2:::find_data() and roxygen2:::find_data_for_package()
lines <- sub("[\r\n] *['\"]_PACKAGE['\"] *(\n|\r|$)", "\nNULL\n", lines)

# registry setup inferred from body of roxygenize()
registry <- c(
roxygen2::roclet_tags(roxygen2::roclet_find("rd_roclet")),
roxygen2::roclet_tags(roxygen2::roclet_find("namespace_roclet")),
include = roxygen2::tag_value
)

# Parse the file
roxy <- roxygen2::parse_text(lines, new.env(), registry)
roxy <- roxygen2::parse_text(lines, new.env())

# Unclass object to fix the print method
roxy <- roxy %>%
Expand Down
3 changes: 1 addition & 2 deletions man/check_cpp_function_exported.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

41 changes: 31 additions & 10 deletions man/check_has_desc_element.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

0 comments on commit 6b9f25d

Please sign in to comment.