Skip to content

Commit

Permalink
post_exercise_code
Browse files Browse the repository at this point in the history
  • Loading branch information
Filip Schouwenaars committed Mar 10, 2017
1 parent f51971d commit eca2aa2
Show file tree
Hide file tree
Showing 6 changed files with 62 additions and 15 deletions.
3 changes: 2 additions & 1 deletion NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -51,7 +51,8 @@ export(check_that)
export(check_wd)
export(check_while)
export(ex)
export(execute_code)
export(execute_solution)
export(execute_student)
export(get_solution_code)
export(get_solution_env)
export(get_student_code)
Expand Down
24 changes: 15 additions & 9 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -13,19 +13,25 @@ check_sufficient <- function(calls, index, name) {
}
}

#' @importFrom magrittr %>%
#' @param code The code to execute
#'
#' @export
execute_code <- function(code, stud_env = TRUE, sol_env = TRUE) {
if (stud_env) {
eval(substitute(code), envir = get_student_env())
}
if (sol_env) {
eval(substitute(code), envir = get_solution_env())
}
magrittr::`%>%`

# Execute code in the student environment
#' @export
execute_student <- function(code) {
try(eval(substitute(code), envir = get_student_env()))
}

#' @importFrom magrittr %>%
#' Execute code in the solution environment
#' @param code The code to execute
#'
#' @export
magrittr::`%>%`
execute_solution <- function(code) {
try(eval(substitute(code), envir = get_solution_env()))
}

#' Get solution environment (backwards comp)
#' @export
Expand Down
14 changes: 14 additions & 0 deletions man/execute_solution.Rd

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

4 changes: 2 additions & 2 deletions man/get_student_env.Rd

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

3 changes: 3 additions & 0 deletions man/reexports.Rd

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

29 changes: 26 additions & 3 deletions tests/testthat/test-utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -30,24 +30,47 @@ test_that("accessor works", {


test_that("check_output - basic", {
# Student envrionment manipulation
lst <- list()
lst$DC_ECHO <- TRUE
lst$DC_SOLUTION <- "x <- 5"
lst$DC_SCT <- "tryCatch(test_object('x'), finally = execute_code(rm(x)))"
lst$DC_SCT <- "tryCatch(test_object('x'), finally = execute_student(rm(x)))"

# correct answer
lst$DC_CODE <- "x <- 5"
output <- test_it(lst)
passes(output)
# should be cleaned up
expect_equal(length(ls(envir = RBackend:::dc$get("sol_env"))), 0)
expect_equal(length(ls(envir = .GlobalEnv)), 0)
expect_equal(length(ls(envir = RBackend:::dc$get("sol_env"))), 1)

# incorrect answer
lst$DC_CODE <- "x <- 7"
output <- test_it(lst)
fails(output)
# should also be cleaned up
expect_equal(length(ls(envir = RBackend:::dc$get("sol_env"))), 0)
expect_equal(length(ls(envir = .GlobalEnv)), 0)
expect_equal(length(ls(envir = RBackend:::dc$get("sol_env"))), 1)

# Solution envrionment manipulation
lst <- list()
lst$DC_ECHO <- TRUE
lst$DC_SOLUTION <- "x <- 5"
lst$DC_SCT <- "tryCatch(test_object('x'), finally = execute_solution(rm(x)))"

# correct answer
lst$DC_CODE <- "x <- 5"
output <- test_it(lst)
passes(output)
# should be cleaned up
expect_equal(length(ls(envir = .GlobalEnv)), 1)
expect_equal(length(ls(envir = RBackend:::dc$get("sol_env"))), 0)

# incorrect answer
lst$DC_CODE <- "x <- 7"
output <- test_it(lst)
fails(output)
# should also be cleaned up
expect_equal(length(ls(envir = .GlobalEnv)), 1)
expect_equal(length(ls(envir = RBackend:::dc$get("sol_env"))), 0)
})

0 comments on commit eca2aa2

Please sign in to comment.