Skip to content

Commit

Permalink
add adjust_epi_recipe and adjust_frosting funs, update docs and tests
Browse files Browse the repository at this point in the history
  • Loading branch information
rachlobay committed Sep 16, 2023
1 parent dbb5c49 commit 12ef4cf
Show file tree
Hide file tree
Showing 8 changed files with 229 additions and 101 deletions.
69 changes: 46 additions & 23 deletions R/epi_recipe.R
Original file line number Diff line number Diff line change
Expand Up @@ -240,21 +240,11 @@ is_epi_recipe <- function(x) {
#' [workflows::add_recipe()] but sets a different
#' default blueprint to automatically handle [epiprocess::epi_df] data.
#'
#' The `update_epi_recipe` function can either update the entire recipe or a
#' step in an existing recipe in an `epi_workflow`. In the latter case, the
#' parameter name that the new value it is equal to must be input into `...`.
#' See the examples below for brief illustrations of both types of updates.
#'
#' @param x A workflow or epi_workflow
#' @param x A `workflow` `or `epi_workflow`
#'
#' @param recipe A recipe created using [recipes::recipe()].
#' Optional for `update_epi_recipe()` only.
#'
#' @param step_num the number of the step to update.
#' Can only be used in `update_epi_recipe()` only.
#'
#' @param ... Can only be used in `update_epi_recipe()` to input a parameter
#' update.
#' @param ... Not used
#'
#' @param blueprint A hardhat blueprint used for fine tuning the preprocessing.
#'
Expand Down Expand Up @@ -298,16 +288,6 @@ is_epi_recipe <- function(x) {
#'
#' workflow
#'
#' # Additional feature in `update_epi_recipe` is to change a step
#' # in the recipe from the workflow
#' workflow <- epi_workflow() %>%
#' add_epi_recipe(r)
#'
#' # Update second step, `step_epi_ahead()`, to have an
#' # ahead value of 14 days
#' workflow = workflow %>% update_epi_recipe(step_num = 2, ahead = 14)
#' workflows::extract_preprocessor(workflow)
#'
add_epi_recipe <- function(
x, recipe, ..., blueprint = default_epi_recipe_blueprint()) {
workflows::add_recipe(x, recipe, ..., blueprint = blueprint)
Expand Down Expand Up @@ -341,11 +321,54 @@ update_epi_recipe <- function(x, recipe, ..., blueprint = NULL) {
add_epi_recipe(x, recipe, blueprint = blueprint)
}

#' Adjust a step in an `epi_workflow` or `epi_recipe`
#'
#' Make a parameter adjustment to a step in either an
#' `epi_workflow` or `epi_recipe` object.
#'
#'
#' @details This function can either adjust a step in a `epi_recipe` object
#' or a step from a `epi_recipe` object in an `epi_workflow`. In any case, the
#' argument name and update value must be inputted as `...`.
#' See the examples below for brief illustrations of both types of updates.
#'
#' @param x A `epi_workflow` or `epi_recipe` object
#'
#' @param step_num the number of the step to adjust
#'
#' @param ... Used to input a parameter adjustment
#'
#' @return
#' `x`, updated with the adjustment to the specified `epi_recipe` step.
#'
#' @export
#' @examples
#' jhu <- case_death_rate_subset %>%
#' filter(time_value > "2021-11-01", geo_value %in% c("ak", "ca", "ny"))
#' r <- epi_recipe(jhu) %>%
#' step_epi_lag(death_rate, lag = c(0, 7, 14)) %>%
#' step_epi_ahead(death_rate, ahead = 7) %>%
#' step_epi_naomit()
#'
#' wf <- epi_workflow(r, parsnip::linear_reg()) %>% fit(jhu)
#' latest <- jhu %>%
#' dplyr::filter(time_value >= max(time_value) - 14)
#'
#' # Adjust `step_epi_ahead` to have an ahead value of 14
#' # in the `epi_workflow`
#' wf2 = wf %>% adjust_epi_recipe(step_num = 2, ahead = 14)
#' workflows::extract_preprocessor(wf2)
#'
#' # Adjust `step_epi_ahead` to have an ahead value of 14
#' # in the `epi_recipe`
#' r2 = r %>% adjust_epi_recipe(step_num = 2, ahead = 14)
#' r2
#'
adjust_epi_recipe <- function(x, step_num, ..., blueprint = default_epi_recipe_blueprint()) {
UseMethod("adjust_epi_recipe")
}

#' @rdname adjust_epi_recipe
#' @export
adjust_epi_recipe.epi_workflow <- function(
x, step_num, ..., blueprint = default_epi_recipe_blueprint()) {
Expand All @@ -356,6 +379,7 @@ adjust_epi_recipe.epi_workflow <- function(
update_epi_recipe(x, recipe, blueprint = blueprint)
}

#' @rdname adjust_epi_recipe
#' @export
adjust_epi_recipe.epi_recipe <- function(
x, step_num, ..., blueprint = default_epi_recipe_blueprint()) {
Expand All @@ -364,7 +388,6 @@ adjust_epi_recipe.epi_recipe <- function(
x
}


# unfortunately, almost everything the same as in prep.recipe except string/fctr handling
#' @export
prep.epi_recipe <- function(
Expand Down
79 changes: 54 additions & 25 deletions R/frosting.R
Original file line number Diff line number Diff line change
@@ -1,20 +1,11 @@
#' Add frosting to a workflow
#'
#' @param x A workflow
#' @param frosting A frosting layer created using `frosting()`.
#' Optional for `update_epi_recipe()` only.
#' @param layer_num the number of the layer to update in an `epi_workflow`.
#' Intended for use in `update_frosting()` only.
#' @param ... Can only be used in `update_frosting()` to input a parameter
#' update.
#'
#' @return `x`, updated with a new or removed frosting postprocessor
#' @export
#' @param frosting A frosting object created using `frosting()`.
#' @param ... Not used.
#'
#' @details The `update_frosting` function can either update the entire frosting
#' or a layer in an existing frosting in an `epi_workflow`. In the latter case,
#' the parameter name the new value it is equal to must be input into `...`.
#' See the examples below for brief illustrations of both types of updates.
#' @return `x`, updated with a new frosting postprocessor
#' @export
#'
#' @examples
#' jhu <- case_death_rate_subset %>%
Expand Down Expand Up @@ -42,18 +33,8 @@
#'
#' # Remove frosting from the workflow and predict
#' wf3 <- wf2 %>% remove_frosting()
#' p2 <- predict(wf3, latest)
#' p2
#'
#' # Additional feature in `update_frosting` is to change a layer
#' # in the frosting from the workflow
#' f3 <- frosting() %>% layer_predict() %>% layer_threshold(.pred)
#'
#' wf3 = wf %>% add_frosting(f3)
#'
#' # Update `layer_threshold` to have an upper bound of 1
#' wf3 = wf3 %>% update_frosting(layer_num = 2, upper = 1)
#' extract_frosting(wf3)
#' p3 <- predict(wf3, latest)
#' p3
#'
add_frosting <- function(x, frosting, ...) {
rlang::check_dots_empty()
Expand Down Expand Up @@ -116,11 +97,58 @@ update_frosting <- function(x, frosting, ...) {
add_frosting(x, frosting)
}


#' Adjust a layer in an `epi_workflow` or `frosting`
#'
#' Make a parameter adjustment to a layer in either an
#' `epi_workflow` or `frosting` object.
#'
#'
#' @details This function can either adjust a layer in a `frosting` object
#' or a layer from a `frosting` object in an `epi_workflow`. In any case, the
#' argument name and update value must be inputted as `...`.
#' See the examples below for brief illustrations of both types of updates.
#'
#' @param x An `epi_workflow` or `frosting` object
#'
#' @param layer_num the number of the layer to adjust
#'
#' @param ... Used to input a parameter adjustment
#'
#' @return
#' `x`, updated with the adjustment to the specified `frosting` layer.
#'
#' @export
#' @examples
#' jhu <- case_death_rate_subset %>%
#' filter(time_value > "2021-11-01", geo_value %in% c("ak", "ca", "ny"))
#' r <- epi_recipe(jhu) %>%
#' step_epi_lag(death_rate, lag = c(0, 7, 14)) %>%
#' step_epi_ahead(death_rate, ahead = 7) %>%
#' step_epi_naomit()
#'
#' wf <- epi_workflow(r, parsnip::linear_reg()) %>% fit(jhu)
#'
#' # in the frosting from the workflow
#' f1 <- frosting() %>% layer_predict() %>% layer_threshold(.pred)
#'
#' wf2 = wf %>% add_frosting(f1)
#'
#' # Adjust `layer_threshold` to have an upper bound of 1
#' # in the `epi_workflow`
#' wf2 = wf2 %>% adjust_frosting(layer_num = 2, upper = 1)
#' extract_frosting(wf2)
#'
#' # Adjust `layer_threshold` to have an upper bound of 1
#' # in the `frosting` object
#' f2 = f1 %>% adjust_frosting(layer_num = 2, upper = 5)
#' extract_frosting(wf2)
#'
adjust_frosting <- function(x, layer_num, ...) {
UseMethod("adjust_frosting")
}

#' @rdname adjust_frosting
#' @export
adjust_frosting.epi_workflow <- function(
x, layer_num, ...) {
Expand All @@ -131,6 +159,7 @@ adjust_frosting.epi_workflow <- function(
update_frosting(x, frosting)
}

#' @rdname adjust_frosting
#' @export
adjust_frosting.frosting <- function(
x, layer_num, ...) {
Expand Down
26 changes: 3 additions & 23 deletions man/add_epi_recipe.Rd

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

31 changes: 5 additions & 26 deletions man/add_frosting.Rd

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

57 changes: 57 additions & 0 deletions man/adjust_epi_recipe.Rd

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

Loading

0 comments on commit 12ef4cf

Please sign in to comment.