diff --git a/R/exercise.R b/R/exercise.R index c46aa4aa0..1f0467074 100644 --- a/R/exercise.R +++ b/R/exercise.R @@ -15,7 +15,6 @@ setup_exercise_handler <- function(exercise_rx, session) { # observe input observeEvent(exercise_rx(), { - # get exercise exercise <- exercise_rx() @@ -187,7 +186,7 @@ evaluate_exercise <- function(exercise, envir, evaluate_global_setup = FALSE) { # do not consider this an exercise submission if (!nzchar(str_trim(paste0(exercise$code, collapse = "\n")))) { # " " since html_output needs to pass a req() - return(exercise_result(html_output = " ")) + return(exercise_result(html_output = " ", exercise = NULL)) } if (evaluate_global_setup) { @@ -239,9 +238,11 @@ evaluate_exercise <- function(exercise, envir, evaluate_global_setup = FALSE) { } # include any checker feedback with the exercise results + exercise_result( feedback = checker_feedback$feedback, - html_output = rmd_results$html_output + html_output = rmd_results$html_output, + exercise = exercise ) } @@ -253,7 +254,10 @@ try_checker <- function(exercise, name, check_code, envir_result, get_checker_func(exercise, name, envir_prep), error = function(e) { message("Error occured while retrieving 'exercise.checker'. Error:\n", e) - exercise_result_error(e$message) + exercise_result_error( + e$message, + exercise = exercise + ) } ) # If retrieving checker_func fails, return an error result @@ -280,7 +284,7 @@ try_checker <- function(exercise, name, check_code, envir_result, name, paste(missing_args, collapse = "', '") ) message(msg) - return(exercise_result_error(msg)) + return(exercise_result_error(msg, exercise = exercise)) } # Call the check function @@ -289,7 +293,7 @@ try_checker <- function(exercise, name, check_code, envir_result, error = function(e) { msg <- paste("Error occurred while evaluating", sprintf("'%s'", name)) message(msg, ": ", conditionMessage(e)) - exercise_result_error(msg) + exercise_result_error(msg, exercise = exercise) } ) # If checker code fails, return an error result @@ -298,7 +302,7 @@ try_checker <- function(exercise, name, check_code, envir_result, } # If checker doesn't return anything, there's no exercise result to return if (length(feedback)) { - exercise_result(feedback) + exercise_result(feedback, exercise = exercise) } else { feedback } @@ -395,7 +399,7 @@ render_exercise <- function(exercise, envir, envir_prep) { # make the time limit error message a bit more friendly pattern <- gettext("reached elapsed time limit", domain = "R") if (grepl(pattern, msg, fixed = TRUE)) { - return(exercise_result_timeout()) + return(exercise_result_timeout(exercise = exercise)) } if (length(exercise$error_check)) { # Run the condition through an error checker (the exercise could be to throw an error!) @@ -412,7 +416,7 @@ render_exercise <- function(exercise, envir, envir_prep) { return(checker_feedback) } } - exercise_result_error(msg) + exercise_result_error(msg, exercise = exercise) }) if (is_exercise_result(output_file)) { @@ -436,8 +440,9 @@ render_exercise <- function(exercise, envir, envir_prep) { message = "The submitted code didn't produce a visible value, so exercise checking may not work correctly.", type = "warning", correct = FALSE ) + html_output <- htmltools::tagList( - feedback_as_html(invisible_feedback), + feedback_as_html(invisible_feedback, exercise = exercise), html_output ) } @@ -463,41 +468,126 @@ exercise_code_chunks <- function(exercise) { } -exercise_result_timeout <- function() { +exercise_result_timeout <- function(exercise) { exercise_result_error( "Error: Your code ran longer than the permitted timelimit for this exercise.", - timeout_exceeded = TRUE + timeout_exceeded = TRUE, + exercise = exercise ) } # @param timeout_exceeded represents whether or not the error was triggered # because the exercise exceeded the timeout. Use NA if unknown -exercise_result_error <- function(error_message, feedback = NULL, timeout_exceeded = NA) { +exercise_result_error <- function( + error_message, + feedback = NULL, + timeout_exceeded = NA, + exercise = NULL +) { exercise_result( feedback = feedback, timeout_exceeded = timeout_exceeded, error_message = error_message, - html_output = error_message_html(error_message) + html_output = error_message_html(error_message, exercise), + exercise = exercise ) } -exercise_result <- function(feedback = NULL, html_output = NULL, - error_message = NULL, timeout_exceeded = FALSE) { +exercise_result <- function( + feedback = NULL, + html_output = NULL, + error_message = NULL, + timeout_exceeded = FALSE, + exercise = NULL +) { + + # When `exercise` is empty, we return a list of as.is values + if (is.null(exercise)){ + return( + structure( + list( + feedback = feedback, + error_message = error_message, + timeout_exceeded = timeout_exceeded, + html_output = html_output + ), + class = "learnr_exercise_result" + ) + ) + } + feedback <- feedback_validated(feedback) - feedback_html <- feedback_as_html(feedback) + feedback_html <- feedback_as_html(feedback, exercise = exercise) + + if ( + is.null(exercise$check) && + is.null(exercise$code_check) + ){ + exercise.submitted_feedback <- FALSE + exercise.submitted_output <- TRUE + } else { + exercise.submitted_feedback <- exercise$options$exercise.submitted_feedback %||% TRUE + exercise.submitted_output <- exercise$options$exercise.submitted_output %||% TRUE + } + + # The trainer want feedbacks and code (the default) + if ( + exercise.submitted_feedback & + exercise.submitted_output + ){ + html_output <- switch( + feedback$location %||% "append", + append = { + feedback_html$children <- list( + feedback_html$children[[1]], + html_output + + ) + feedback_html + }, + prepend = { + feedback_html$children <- list( + html_output, + feedback_html$children[[1]] + ) + feedback_html + }, + replace = feedback_html, + stop("Feedback location of ", feedback$location, " not supported") + ) + } else if ( + # The trainer want feedbacks only + exercise.submitted_feedback & + ! exercise.submitted_output + ) { + html_output <- feedback_html + } else if ( + # The trainer wants code only + ! exercise.submitted_feedback & + exercise.submitted_output + ) { + html_output <- tags$div( + html_output + ) + } else if ( + # The trainer wants no feedback + ! exercise.submitted_feedback & + ! exercise.submitted_output + ){ + # Not sure what to do there, (i.e the trainer want neither feedback nor code) + html_output <- div( + class = "alert alert-grey", + role = "alert", + "Code submitted" + ) + } structure( list( feedback = feedback, error_message = error_message, timeout_exceeded = timeout_exceeded, - html_output = switch( - feedback$location %||% "append", - append = htmltools::tagList(html_output, feedback_html), - prepend = htmltools::tagList(feedback_html, html_output), - replace = feedback_html, - stop("Feedback location of ", feedback$location, " not supported") - ) + html_output = html_output ), class = "learnr_exercise_result" ) diff --git a/R/feedback.R b/R/feedback.R index 785ca4fc7..3f748f62c 100644 --- a/R/feedback.R +++ b/R/feedback.R @@ -41,7 +41,11 @@ feedback_validated <- function(feedback) { feedback } -feedback_as_html <- function(feedback) { +# This function is called to build the html of the feedback +# provided by gradethis +# It's called both when pressing Run Code and Submit Answer +feedback_as_html <- function(feedback, exercise) { + if (!length(feedback)) { return(feedback) } @@ -52,17 +56,43 @@ feedback_as_html <- function(feedback) { if (feedback$type %in% "error") { feedback$type <- "danger" } - if (feedback$type %in% c("success", "info", "warning", "danger")) { - return(div( - role = "alert", - class = paste0("alert alert-", feedback$type), - feedback$message - )) + if (!feedback$type %in% c("success", "info", "warning", "danger")) { + stop("Invalid message type specified.", call. = FALSE) } - stop("Invalid message type specified.", call. = FALSE) + # Applying custom classes if they exist + + feedback$type <- switch( + feedback$type, + success = exercise$options$exercise.success_class %||% "alert-success", + info = exercise$options$exercise.info_class %||% "alert-info", + warning = exercise$options$exercise.warning_class %||% "alert-warning", + danger = exercise$options$exercise.danger_class %||% "alert-danger" + ) + + return(div( + role = "alert", + class = paste0("alert ", feedback$type), + feedback$message + )) } # helper function to create tags for error message -error_message_html <- function(message) { - div(class = "alert alert-danger", role = "alert", message) +# It is called by learnr when clicking "Run code" & the +# code produced an error +# It's called only when pressing Run Code +error_message_html <- function(message, exercise) { + # When the Run Code button is pressed, the output is __always__ shown. + # This html builder function adds colored border around the code output if there is an error. + class <- sprintf( + "alert run-code %s", + exercise$options$exercise.alert_class %||% "alert-red" + ) + + div( + class = class, + role = "alert", + tags$pre( + message + ) + ) } diff --git a/R/options.R b/R/options.R index e0da519f0..794c3f49a 100644 --- a/R/options.R +++ b/R/options.R @@ -18,29 +18,40 @@ #' @param exercise.completion Use code completion in exercise editors. #' @param exercise.diagnostics Show diagnostics in exercise editors. #' @param exercise.startover Show "Start Over" button on exercise. +#' @param exercise.alert_class,exercise.info_class,exercise.success_class,exercise.warning_class,exercise.danger_class The CSS class for `{learnr}` and `{gradethis}` message. +#' It can be one of `alert-success`, `alert-info`, `alert-warning`, `alert-danger`, +#' `alert-red`, `alert-orange`, `alert-purple`, `alert-blue`, `alert-violet`, +#' `alert-yellow`, `alert-pink`, `alert-green`, or `alert-grey`. +#' You can also use your own CSS class. +# #' @param exercise.execution_error_message What message should `{learnr}` print on error? +#' @param exercise.submitted_feedback Should submitted exercise feedback be shown? +#' @param exercise.submitted_output Should submitted exercise output be shown? #' #' @export -tutorial_options <- function(exercise.cap = NULL, - exercise.eval = FALSE, - exercise.timelimit = 30, - exercise.lines = NULL, - exercise.checker = NULL, - exercise.error.check.code = NULL, - exercise.completion = TRUE, - exercise.diagnostics = TRUE, - exercise.startover = TRUE) +tutorial_options <- function( + exercise.cap = NULL, + exercise.eval = FALSE, + exercise.timelimit = 30, + exercise.lines = NULL, + exercise.checker = NULL, + exercise.error.check.code = NULL, + exercise.completion = TRUE, + exercise.diagnostics = TRUE, + exercise.startover = TRUE, + exercise.alert_class = "alert-red", + exercise.success_class = "alert-success", + exercise.info_class = "alert-info", + exercise.warning_class = "alert-warning", + exercise.danger_class = "alert-danger", + exercise.submitted_feedback = TRUE, + exercise.submitted_output = TRUE +) { # string to evalute for setting chunk options %1$s set_option_code <- 'if (!missing(%1$s)) knitr::opts_chunk$set(%1$s = %1$s)' # set options as required - eval(parse(text = sprintf(set_option_code, "exercise.cap"))) - eval(parse(text = sprintf(set_option_code, "exercise.eval"))) - eval(parse(text = sprintf(set_option_code, "exercise.timelimit"))) - eval(parse(text = sprintf(set_option_code, "exercise.lines"))) - eval(parse(text = sprintf(set_option_code, "exercise.checker"))) - eval(parse(text = sprintf(set_option_code, "exercise.error.check.code"))) - eval(parse(text = sprintf(set_option_code, "exercise.completion"))) - eval(parse(text = sprintf(set_option_code, "exercise.diagnostics"))) - eval(parse(text = sprintf(set_option_code, "exercise.startover"))) + for (i in names(formals())){ + eval(parse(text = sprintf(set_option_code, i))) + } } diff --git a/inst/lib/tutorial/tutorial.css b/inst/lib/tutorial/tutorial.css index 0cf6c7128..8a07b57f8 100644 --- a/inst/lib/tutorial/tutorial.css +++ b/inst/lib/tutorial/tutorial.css @@ -1,134 +1,238 @@ +:root { + --red-back: #f2dede; + --red-color: #b94a48; + --red-border: #eed3d7; + --orange-back: #ffa0142e; + --orange-color: #b96e00; + --orange-border: #ffc10787; + --purple-back: #9c27b029; + --purple-color: #681876; + --purple-border: #9c27b01f; + --blue-back: #cce5ff; + --blue-color: #004085; + --blue-border: #b8daff; + --violet-back: #6610f214; + --violet-color: #3e246d; + --violet-border: #6610f23b; + --yellow-back: #ffc10747; + --yellow-color: #da6605; + --yellow-border: #ffc107; + --pink-back: #e83eb424; + --pink-color: #9b2158; + --pink-border: #e83e8c45; + --green-back: #dff0d8; + --green-color: #468847; + --green-border: #d6e9c6; + --grey-back: #f5f5f5; + --grey-color: #555555; + --grey-border: #dcdcdc; +} .tutorial-exercise-support { - display: none; + display: none; } .slide .tutorial-exercise { - line-height: 1.4; + line-height: 1.4; } .tutorial-exercise { - position: relative; + position: relative; } .tutorial-exercise-input { - margin-top: 15px; + margin-top: 15px; } .tutorial-panel-heading { - padding-top: 6px; - padding-bottom: 6px; - padding-left: 8px; - padding-right: 8px; - font-size: 13px; - font-weight: 500; - width: 100%; - display: flex; - justify-content: space-between; + padding-top: 6px; + padding-bottom: 6px; + padding-left: 8px; + padding-right: 8px; + font-size: 13px; + font-weight: 500; + width: 100%; + display: flex; + justify-content: space-between; } + .tutorial-panel-heading-left, .tutorial-panel-heading-right { - display: flex; + display: flex; } + .tutorial-quiz-title { - font-weight: 300; - font-size: 18px; - padding-top: 6px; - padding-bottom: 0px; - padding-left: 0px; - padding-right: 8px; - width: 100%; + font-weight: 300; + font-size: 18px; + padding-top: 6px; + padding-bottom: 0px; + padding-left: 0px; + padding-right: 8px; + width: 100%; } .tutorial-question { - padding-top: 10px; - padding-bottom: 15px; + padding-top: 10px; + padding-bottom: 15px; } .tutorial-exercise-input .btn-xs { - margin-right: 0; - margin-top: -1px; - font-size: 11px; - margin-left: 12px; - padding-right: 8px; - font-weight: normal; + margin-right: 0; + margin-top: -1px; + font-size: 11px; + margin-left: 12px; + padding-right: 8px; + font-weight: normal; } .btn-light { - color: #333; - background-color: #fff; - border-color: #ccc; + color: #333; + background-color: #fff; + border-color: #ccc; } .tutorial-exercise-input .btn-tutorial-solution { - margin-left: 15px; + margin-left: 15px; } .tutorial-exercise-input .btn-tutorial-next-hint { - margin-left: 15px; - padding-right: 4px; + margin-left: 15px; + padding-right: 4px; } .tutorial-exercise-input .btn-xs i { - width: 10px; - margin-right: 1px; + width: 10px; + margin-right: 1px; } - .tutorial-exercise-input .panel-body { - padding: 0; + padding: 0; } - .tutorial-exercise-code-editor { - width: 100%; + width: 100%; } - .tutorial-solution-popover { - max-width: none; - width: 100%; + max-width: none; + width: 100%; } .tutorial-solution-popover.top>.arrow { - margin-left: 0; + margin-left: 0; } -.tutorial-hint { - -} +.tutorial-hint {} .ace-tm { - font-family: monospace; - font-size: 90%; + font-family: monospace; + font-size: 90%; } - .tutorial-video-container { - position: relative; - margin-top: 15px; - margin-bottom: 15px; + position: relative; + margin-top: 15px; + margin-bottom: 15px; } .tutorial-exercise-output>pre { - max-height: 500px; - overflow-y: auto; + max-height: 500px; + overflow-y: auto; } .tutorial-video { - position: absolute; - top: 0; - left: 0; - width: 100%; - height: 100%; - border: solid 1px #cccccc; + position: absolute; + top: 0; + left: 0; + width: 100%; + height: 100%; + border: solid 1px #cccccc; } .tutorial_engine_icon { - vertical-align: middle; - fill: currentColor; - height: 20px; - width: 20px; - margin-right: -9px; - /* net 6px */ + vertical-align: middle; + fill: currentColor; + height: 20px; + width: 20px; + margin-right: -9px; + /* net 6px */ +} + +.alert { + width: 100%!important; +} + +.run-code { + background-color: unset!important; + color: unset!important; +} + +.alert-red { + background-color: var(--red-back); + color: var(--red-color); + border-color: var(--red-border); +} + +.alert-orange { + background-color: var(--orange-back); + color: var(--orange-color); + border-color: var(--orange-border); +} + +.alert-purple { + background-color: var(--purple-back); + color: var(--purple-color); + border-color: var(--purple-border); +} + +.alert-blue { + background-color: var(--blue-back); + color: var(--blue-color); + border-color: var(--blue-border); +} + +.alert-violet { + background-color: var(--violet-back); + color: var(--violet-color); + border-color: var(--violet-border); +} + +.alert-yellow { + background-color: var(--yellow-back); + color: var(--yellow-color); + border-color: var(--yellow-border); +} + +.alert-pink { + background-color: var(--pink-back); + color: var(--pink-color); + border-color: var(--pink-border); } + +.alert-green { + background-color: var(--green-back); + color: var(--green-color); + border-color: var(--green-border); +} + +.alert-grey { + background-color: var(--grey-back); + color: var(--grey-color); + border-color: var(--grey-border); +} + + +/* Class to display pagetable inside an alert without inheriting from it*/ + +.alert>.pagedtable-wrapper { + border: 0px!important; + margin-top: 1em; + background-color: white; + color: #555555; +} + +.alert>pre { + border: none; + border-radius: 4px; + margin-top: 1em; +} \ No newline at end of file diff --git a/man/tutorial_options.Rd b/man/tutorial_options.Rd index b9c42103b..c9ee2b352 100644 --- a/man/tutorial_options.Rd +++ b/man/tutorial_options.Rd @@ -13,7 +13,17 @@ tutorial_options( exercise.error.check.code = NULL, exercise.completion = TRUE, exercise.diagnostics = TRUE, - exercise.startover = TRUE + exercise.startover = TRUE, + exercise.alert_class = "red", + exercise.feedback_show = TRUE, + exercise.code_show = TRUE, + exercise.execution_error_message = NULL, + exercise.gradethis_success_color = NULL, + exercise.gradethis_info_color = NULL, + exercise.gradethis_warning_color = NULL, + exercise.gradethis_danger_color = NULL, + exercise.gradethis_feedback_show = TRUE, + exercise.gradethis_code_show = TRUE ) } \arguments{ @@ -39,6 +49,21 @@ code when an exercise evaluation error occurs (e.g., \code{"gradethis::grade_cod \item{exercise.diagnostics}{Show diagnostics in exercise editors.} \item{exercise.startover}{Show "Start Over" button on exercise.} + +\item{exercise.alert_class, exercise.gradethis_info_color, exercise.gradethis_success_color, exercise.gradethis_warning_color, exercise.gradethis_danger_color}{Slug for the CSS class for \code{{learnr}} and \code{{gradethis}} message. +It can be one of \code{red}, \code{orange}, \code{purple}, \code{blue}, \code{violet}, \code{yellow}, \code{pink}, \code{green}, +or \code{grey}. You can also implement your own CSS rule, in that case you need to define a +class that starts with \verb{alert-} (for example \code{alert-rainbow}).} + +\item{exercise.feedback_show}{Should the \code{{learnr}} feedback be shown?} + +\item{exercise.code_show}{Should \code{{learnr}} output code be shown?} + +\item{exercise.execution_error_message}{What message should \code{{learnr}} print on error?} + +\item{exercise.gradethis_feedback_show}{Should the \code{{gradethis}} feedback be shown?} + +\item{exercise.gradethis_code_show}{Should \code{{gradethis}} output code be shown?} } \description{ Set various tutorial options that control the display and evaluation of diff --git a/sandbox/colored-output-gradethis.Rmd b/sandbox/colored-output-gradethis.Rmd new file mode 100644 index 000000000..c76f73d2b --- /dev/null +++ b/sandbox/colored-output-gradethis.Rmd @@ -0,0 +1,192 @@ +--- +title: "Tutorial" +output: + learnr::tutorial: + progressive: true + allow_skip: true +runtime: shiny_prerendered +--- + +```{r setup, include=FALSE} +library(learnr) +library(dplyr) +#options(tutorial.event_recorder = learnr:::debug_event_recorder) +gradethis::gradethis_setup( + exercise.eval = FALSE, + exercise.alert_class = "alert-orange", + exercise.success_class = "alert-pink", + exercise.info_class = "alert-orange", + exercise.warning_class = "alert-violet", + exercise.danger_class = "alert-blue" +) + +tutorial_options( + exercise.submitted_feedback = TRUE, + exercise.submitted_output = TRUE +) + +``` + +## Using globally set color + +Done: + ++ The gradethis colors can be set using options: `exercise.success_class`, `exercise.info_class`, `exercise.warning_class` and `exercise.danger_class` + +__Example__ + +The current tutorial uses the following call in the setup chunk: + +``` +gradethis::gradethis_setup( + exercise.eval = FALSE, + exercise.alert_class = "alert-orange", + exercise.success_class = "alert-pink", + exercise.info_class = "alert-orange", + exercise.warning_class = "alert-violet", + exercise.danger_class = "alert-blue" +) +``` + +Enter `mtcars` + +```{r mtcars, exercise = TRUE} + +``` + +```{r mtcars-solution} +mtcars +``` + + +```{r mtcars-check} +grade_result( + fail_if(~identical(.result, cars), "This is the cars (not mtcars) dataset."), + pass_if(~identical(.result, mtcars)) +) +``` + +## Using locally set color + +With the following chunk setup: + +``` +{r mtcars2 exercise.success_class = "alert-red", ,exercise.info_class = "alert-violet", exercise.warning_class = "alert-blue", exercise.danger_class = "alert-green"} +``` + +Enter `mtcars` + +```{r mtcars2, exercise = TRUE, exercise.success_class = "alert-red", ,exercise.info_class = "alert-violet", exercise.warning_class = "alert-blue", exercise.danger_class = "alert-green"} + +``` + +```{r mtcars2-solution} +mtcars +``` + + +```{r mtcars2-check } +grade_result( + fail_if(~identical(.result, cars), "This is the cars (not mtcars) dataset."), + pass_if(~identical(.result, mtcars)) +) +``` + +## Toggle Feedback or code display + +With the following chunk: + +``` +{r mtcars3, exercise.submitted_feedback = TRUE, exercise.submitted_output = TRUE} +``` + +Enter `mtcars` + +```{r mtcars3, exercise = TRUE, exercise.submitted_feedback = TRUE, exercise.submitted_output = TRUE} +airquality +``` + +```{r mtcars3-solution} +mtcars +``` + + +```{r mtcars3-check } +grade_result( + fail_if(~identical(.result, cars), "This is the cars (not mtcars) dataset."), + pass_if(~identical(.result, mtcars)) +) +``` + +With the following chunk: + +``` +{r mtcars4, exercise.submitted_feedback = TRUE, exercise.submitted_output = FALSE} +``` + +Enter `mtcars` + +```{r mtcars4, exercise = TRUE, exercise.submitted_feedback = TRUE, exercise.submitted_output = FALSE} +airquality +``` + +```{r mtcars4-solution} +mtcars +``` + + +```{r mtcars4-check } +grade_result( + fail_if(~identical(.result, cars), "This is the cars (not mtcars) dataset."), + pass_if(~identical(.result, mtcars)) +) +``` + +With the following chunk: + +``` +{r mtcars5, exercise.submitted_feedback = FALSE, exercise.submitted_output = TRUE} +``` + +Enter `mtcars` + +```{r mtcars5, exercise = TRUE, exercise.submitted_feedback = FALSE, exercise.submitted_output = TRUE} +airquality +``` + +```{r mtcars5-solution} +mtcars +``` + + +```{r mtcars5-check } +grade_result( + fail_if(~identical(.result, cars), "This is the cars (not mtcars) dataset."), + pass_if(~identical(.result, mtcars)) +) +``` + +With the following chunk: + +``` +{r mtcars6, exercise.submitted_feedback = FALSE, exercise.submitted_output = FALSE} +``` + +Enter `mtcars` + +```{r mtcars6, exercise = TRUE, exercise.submitted_feedback = FALSE, exercise.submitted_output = FALSE} +airquality +``` + +```{r mtcars6-solution} +mtcars +``` + + +```{r mtcars6-check } +grade_result( + fail_if(~identical(.result, cars), "This is the cars (not mtcars) dataset."), + pass_if(~identical(.result, mtcars)) +) +``` + diff --git a/sandbox/colored-output.Rmd b/sandbox/colored-output.Rmd new file mode 100644 index 000000000..702cd19df --- /dev/null +++ b/sandbox/colored-output.Rmd @@ -0,0 +1,174 @@ +--- +title: "Tutorial" +output: + learnr::tutorial: + progressive: true + allow_skip: true +runtime: shiny_prerendered +--- + +```{r setup, include=FALSE} +library(learnr) +library(dplyr) +options(tutorial.event_recorder = learnr:::debug_event_recorder) +tutorial_options( + exercise.eval = FALSE, + exercise.alert_class = "alert-orange" +) +``` + + +## Using globally set color + +Done: + ++ `exercise.alert_class` in the setup chunk can be used to change the alert color. + ++ The output of the code is now inside the alert, formatted as code/table. + +To do: + ++ Add a check that the colors set by the user is valid (we have a finite set of colors) + ++ Document the colors available + +To discuss: + ++ Should we allow custom colors? For example, we could have `exercise.alert_class = "#f5a67d"` + +__Example__ + +The current tutorial uses the following call in the setup chunk: + +``` +tutorial_options( + exercise.eval = FALSE, + exercise.alert_class = "orange" +) +``` + +> Try typing errors in the chunks of this tutorial + +> NB: the solution to all is `mtcars` + +```{r car, exercise=TRUE, exercise.timelimit = 10} +list( +``` + +```{r car-solution} +mtcars +``` + +## Using locally set color + +Colors can also be set at the chunk level. + +### red + +``` +{r car-red, exercise.alert_class = "alert-red"} +``` + +```{r car-red, exercise.alert_class = "alert-red", exercise=TRUE} +list( +``` + + +```{r car-red-solution} +mtcars +``` + + +### orange + +`exercise.alert_class = "alert-orange"` + +```{r car-orange, exercise.alert_class = "alert-orange", exercise=TRUE, exercise.timelimit = 10} +list( +``` + + +```{r car-orange-solution} +mtcars +``` + + +### purple + +`exercise.alert_class = "alert-purple"` + +```{r car-purple, exercise.alert_class = "alert-purple", exercise=TRUE, exercise.timelimit = 10} +list( +``` + + +```{r car-purple-solution} +mtcars +``` + +### blue + +`exercise.alert_class = "alert-blue"` + +```{r car-blue, exercise.alert_class = "alert-blue", exercise=TRUE, exercise.timelimit = 10} +list( +``` + + +```{r car-blue-solution} +mtcars +``` + + +### violet + +`exercise.alert_class = "alert-violet"` + +```{r car-violet, exercise.alert_class = "alert-violet", exercise=TRUE, exercise.timelimit = 10} +list( +``` + + +```{r car-violet-solution} +mtcars +``` + + +### yellow + +`exercise.alert_class = "alert-yellow"` + +```{r car-yellow, exercise.alert_class = "alert-yellow", exercise=TRUE, exercise.timelimit = 10} +list( +``` + + +```{r car-yellow-solution} +mtcars +``` + +### pink + +`exercise.alert_class = "alert-pink"` + +```{r car-pink, exercise.alert_class = "alert-pink", exercise=TRUE, exercise.timelimit = 10} +list( +``` + + +```{r car-pink-solution} +mtcars +``` + +### green + +`exercise.alert_class = "alert-green"` + +```{r car-green, exercise.alert_class = "alert-green", exercise=TRUE, exercise.timelimit = 10} +list( +``` + + +```{r car-green-solution} +mtcars +``` \ No newline at end of file