Skip to content

Commit fa6de97

Browse files
authored
Merge pull request #72 from topepo/varying_functions
Varying functions
2 parents 7b74051 + e4fea2a commit fa6de97

33 files changed

+1185
-158
lines changed

NAMESPACE

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -34,6 +34,8 @@ S3method(translate,mars)
3434
S3method(translate,mlp)
3535
S3method(translate,rand_forest)
3636
S3method(translate,surv_reg)
37+
S3method(type_sum,model_fit)
38+
S3method(type_sum,model_spec)
3739
S3method(update,boost_tree)
3840
S3method(update,linear_reg)
3941
S3method(update,logistic_reg)
@@ -43,6 +45,9 @@ S3method(update,multinom_reg)
4345
S3method(update,nearest_neighbor)
4446
S3method(update,rand_forest)
4547
S3method(update,surv_reg)
48+
S3method(varying_args,model_spec)
49+
S3method(varying_args,recipe)
50+
S3method(varying_args,step)
4651
export("%>%")
4752
export(boost_tree)
4853
export(check_empty_ellipse)
@@ -78,6 +83,10 @@ export(show_call)
7883
export(surv_reg)
7984
export(translate)
8085
export(varying)
86+
export(varying_args)
87+
export(varying_args.model_spec)
88+
export(varying_args.recipe)
89+
export(varying_args.step)
8190
import(rlang)
8291
importFrom(dplyr,arrange)
8392
importFrom(dplyr,as_tibble)
@@ -102,6 +111,8 @@ importFrom(purrr,imap)
102111
importFrom(purrr,imap_lgl)
103112
importFrom(purrr,list_modify)
104113
importFrom(purrr,map)
114+
importFrom(purrr,map2_dfr)
115+
importFrom(purrr,map_chr)
105116
importFrom(purrr,map_dbl)
106117
importFrom(purrr,map_df)
107118
importFrom(purrr,map_dfr)
@@ -129,6 +140,7 @@ importFrom(stats,update)
129140
importFrom(tibble,as_tibble)
130141
importFrom(tibble,is_tibble)
131142
importFrom(tibble,tibble)
143+
importFrom(tibble,type_sum)
132144
importFrom(tidyr,gather)
133145
importFrom(utils,capture.output)
134146
importFrom(utils,getFromNamespace)

R/arguments.R

Lines changed: 0 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -1,32 +1,12 @@
11
#' @import rlang
22

3-
does_it_vary <- function(x) {
4-
if(is.null(x)) {
5-
res <- FALSE
6-
} else {
7-
res <- if(is_quosure(x))
8-
isTRUE(all.equal(x[[-1]], quote(varying())))
9-
else
10-
isTRUE(all.equal(x, quote(varying())))
11-
}
12-
res
13-
}
14-
153
null_value <- function(x) {
164
res <- if(is_quosure(x))
175
isTRUE(all.equal(x[[-1]], quote(NULL))) else
186
isTRUE(all.equal(x, NULL))
197
res
208
}
219

22-
#' A Placeholder Function for Argument Values
23-
#'
24-
#' [varying()] is used when a parameter will be specified at a later date.
25-
#' @export
26-
varying <- function()
27-
quote(varying())
28-
29-
3010
deharmonize <- function(args, key, engine) {
3111
nms <- names(args)
3212
orig_names <- key[nms, engine]

R/descriptors.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -189,7 +189,7 @@ get_descr_xy <- function(x, y) {
189189
}
190190

191191
has_exprs <- function(x) {
192-
if(is.null(x) | does_it_vary(x) | is_missing_arg(x))
192+
if(is.null(x) | is_varying(x) | is_missing_arg(x))
193193
return(FALSE)
194194
is_symbolic(x)
195195
}

R/engines.R

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -40,13 +40,14 @@ check_engine <- function(object) {
4040

4141
#' @importFrom utils installed.packages
4242
check_installs <- function(x) {
43-
lib_inst <- rownames(installed.packages())
44-
if (length(x$method$libs) > 0) {
45-
is_inst <- x$method$libs %in% lib_inst
43+
if (length(x$method$library) > 0) {
44+
lib_inst <- rownames(installed.packages())
45+
is_inst <- x$method$library %in% lib_inst
4646
if (any(!is_inst)) {
4747
stop(
4848
"This engine requires some package installs: ",
49-
paste0("'", x$method$libs[!is_inst], "'", collapse = ", ")
49+
paste0("'", x$method$library[!is_inst], "'", collapse = ", "),
50+
call. = FALSE
5051
)
5152
}
5253
}

R/mars.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -85,7 +85,7 @@ mars <-
8585
stop("`prod_degree` should be >= 1", call. = FALSE)
8686
if (is.numeric(num_terms) && num_terms < 0)
8787
stop("`num_terms` should be >= 1", call. = FALSE)
88-
if (!does_it_vary(prune_method) &&
88+
if (!is_varying(prune_method) &&
8989
!is.null(prune_method) &&
9090
!is.character(prune_method))
9191
stop("`prune_method` should be a single string value", call. = FALSE)

R/type_sum.R

Lines changed: 53 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,53 @@
1+
#' Succinct summary of parsnip object
2+
#'
3+
#' `type_sum` controls how objects are shown when inside tibble
4+
#' columns.
5+
#' @param x A `model_spec` or `model_fit` object to summarise.
6+
#' @details For `model_spec` objects, the summary is "`spec[?]`"
7+
#' or "`spec[+]`". The former indicates that either the model
8+
#' mode has not been declared or that the specification has
9+
#' `varying()` parameters. Otherwise, the latter is shown.
10+
#'
11+
#' For fitted models, either "`fit[x]`" or "`fit[+]`" are used
12+
#' where the "x" implies that the model fit failed in some way.
13+
#' @return A character value.
14+
#' @importFrom tibble type_sum
15+
#' @method type_sum model_spec
16+
#' @keywords internal
17+
#' @export
18+
type_sum.model_spec <- function(x) {
19+
resolved <- TRUE
20+
if (x$mode == "unknown")
21+
resolved <- FALSE
22+
arg_info <- varying_args(x)
23+
if (any(arg_info$varying))
24+
resolved <- FALSE
25+
26+
res <- "spec"
27+
if (resolved) {
28+
res <- paste0(res, "[+]")
29+
} else {
30+
res <- paste0(res, "[?]")
31+
}
32+
res
33+
}
34+
35+
#' @rdname type_sum.model_spec
36+
#' @importFrom tibble type_sum
37+
#' @method type_sum model_fit
38+
#' @keywords internal
39+
#' @export
40+
type_sum.model_fit <- function(x) {
41+
resolved <- TRUE
42+
if (inherits(x$fit, "try-error"))
43+
resolved <- FALSE
44+
45+
res <- "fit"
46+
if (resolved) {
47+
res <- paste0(res, "[+]")
48+
} else {
49+
res <- paste0(res, "[x]")
50+
}
51+
res
52+
}
53+

R/varying.R

Lines changed: 166 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,166 @@
1+
#' A placeholder function for argument values
2+
#'
3+
#' [varying()] is used when a parameter will be specified at a later date.
4+
#' @export
5+
varying <- function()
6+
quote(varying())
7+
8+
#' Determine varying arguments
9+
#'
10+
#' `varying_args` takes a model specification and lists all of the arguments
11+
#' along with whether they are fully specified or not.
12+
#' @param x An object
13+
#' @param id A string describing the object `x`.
14+
#' @param ... Not currently used.
15+
#' @return A tibble with columns for the parameter name (`name`), whether is
16+
#' contains _any_ varying value (`varying`), the `id` for the object, and the
17+
#' class that was used to call the method (`type`).
18+
#' @examples
19+
#' library(dplyr)
20+
#' library(rlang)
21+
#'
22+
#' rand_forest() %>% varying_args(id = "plain")
23+
#'
24+
#' rand_forest(mtry = varying()) %>% varying_args(id = "one arg")
25+
#'
26+
#' rand_forest(others = list(sample.fraction = varying())) %>%
27+
#' varying_args(id = "only others")
28+
#'
29+
#' rand_forest(
30+
#' others = list(
31+
#' strata = expr(Class),
32+
#' sampsize = c(varying(), varying())
33+
#' )
34+
#' ) %>%
35+
#' varying_args(id = "add an expr")
36+
#'
37+
#' rand_forest(others = list(classwt = c(class1 = 1, class2 = varying()))) %>%
38+
#' varying_args(id = "list of values")
39+
#'
40+
#' @export
41+
varying_args <- function (x, id, ...)
42+
UseMethod("varying_args")
43+
44+
#' @importFrom purrr map map_lgl
45+
#' @export
46+
#' @export varying_args.model_spec
47+
#' @rdname varying_args
48+
varying_args.model_spec <- function(x, id = NULL, ...) {
49+
cl <- match.call()
50+
51+
if (!is.null(id) && !is.character(id))
52+
stop ("`id` should be a single character string.", call. = FALSE)
53+
id <- id[1]
54+
55+
if (is.null(id))
56+
id <- deparse(cl$x)
57+
varying_args <- map(x$args, find_varying)
58+
varying_others <- map(x$others, find_varying)
59+
res <- c(varying_args, varying_others)
60+
res <- map_lgl(res, any)
61+
tibble(
62+
name = names(res),
63+
varying = unname(res),
64+
id = id,
65+
type = caller_method(cl)
66+
)
67+
}
68+
69+
# NOTE Look at the `sampsize` and `classwt` examples above. Using varying() in
70+
# a vector will convert it to list. When the model-specific `translate` is
71+
# run, we should catch those and convert them back to vectors if the varying
72+
# parameter has been replaced with a real value.
73+
74+
# Need to figure out a way to meld the results of varying_args with
75+
# parameter objects from `dials` or from novel parameters in the user's
76+
# workspace. Maybe register the parameters in dials and have a way of
77+
# adding/modifying them? A list vector could be added to these tibbles with
78+
# the actual parameter objects (and the ranges may need to be set).
79+
80+
# Maybe use this data as substrate to make a new object type (param_set?) that
81+
# would have its own methods for grids and random sampling.
82+
83+
# lots of code duplication below and probably poor planning; just a prototype.
84+
# once the generics package is done, these will go into recipes
85+
86+
#' @importFrom purrr map2_dfr map_chr
87+
#' @export
88+
#' @export varying_args.recipe
89+
#' @rdname varying_args
90+
varying_args.recipe <- function(x, id = NULL, ...) {
91+
step_type <- map_chr(x$steps, function(x) class(x)[1])
92+
step_type <- make.names(step_type, unique = TRUE) # change with new tibble version
93+
res <- map2_dfr(x$steps, step_type, varying_args)
94+
res
95+
}
96+
97+
#' @importFrom purrr map map_lgl
98+
#' @export
99+
#' @export varying_args.step
100+
#' @rdname varying_args
101+
varying_args.step <- function(x, id = NULL, ...) {
102+
cl <- match.call()
103+
if (!is.null(id) && !is.character(id))
104+
stop ("`id` should be a single character string.", call. = FALSE)
105+
id <- id[1]
106+
107+
if (is.null(id))
108+
id <- deparse(cl$x)
109+
110+
exclude <-
111+
c("terms", "role", "trained", "skip", "na.rm", "impute_with", "seed",
112+
"prefix", "naming", "denom", "outcome", "id")
113+
x <- x[!(names(x) %in% exclude)]
114+
x <- x[!map_lgl(x, is.null)]
115+
res <- map(x, find_varying)
116+
res <- map_lgl(res, any)
117+
tibble(
118+
name = names(res),
119+
varying = unname(res),
120+
id = id,
121+
type = caller_method(cl)
122+
)
123+
}
124+
125+
# helpers ----------------------------------------------------------------------
126+
127+
is_varying <- function(x) {
128+
if(is.null(x)) {
129+
res <- FALSE
130+
} else {
131+
res <- if(is_quosure(x))
132+
isTRUE(all.equal(x[[-1]], quote(varying())))
133+
else
134+
isTRUE(all.equal(x, quote(varying())))
135+
}
136+
res
137+
}
138+
139+
# Error: C stack usage 7970880 is too close to the limit (in some cases)
140+
find_varying <- function(x) {
141+
if (is.atomic(x) | is.name(x)) {
142+
FALSE
143+
} else if (is.call(x)) {
144+
if (is_varying(x)) {
145+
TRUE
146+
} else {
147+
find_varying(x)
148+
}
149+
} else if (is.pairlist(x)) {
150+
find_varying(x)
151+
} else if (is.vector(x) | is.list(x)) {
152+
map_lgl(x, find_varying)
153+
} else {
154+
# User supplied incorrect input
155+
stop("Don't know how to handle type ", typeof(x),
156+
call. = FALSE)
157+
}
158+
}
159+
160+
caller_method <- function(cl) {
161+
x <- cl[[1]]
162+
x <- deparse(x)
163+
x <- gsub("varying_args.", "", x, fixed = TRUE)
164+
x
165+
}
166+

_pkgdown.yml

Lines changed: 7 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -25,15 +25,17 @@ reference:
2525
- surv_reg
2626
- title: Infrastructure
2727
contents:
28-
- model_spec
29-
- model_fit
30-
- predict.model_fit
31-
- translate
28+
- descriptors
3229
- fit.model_spec
3330
- fit_xy
3431
- fit_control
32+
- model_fit
33+
- model_spec
34+
- predict.model_fit
35+
- translate
3536
- varying
36-
- descriptors
37+
- varying_args
38+
3739
- title: Data
3840
contents:
3941
- lending_club

docs/articles/articles/Classification.html

Lines changed: 3 additions & 3 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

0 commit comments

Comments
 (0)