From 5a353d9834766105a2dd9c89603ccbf652213eff Mon Sep 17 00:00:00 2001 From: Michel Lang Date: Wed, 28 Feb 2024 15:08:09 +0100 Subject: [PATCH] S3 params (#350) * faster * extend tests a little * minor improvements * document * more efficient deps handling in PSC * fix ps_union * transparent tags * dynamic tags shadow * avoid some instantiation of tags * renaming param to prevent misuse * trying to make R 4 tests work * testing shadow tags * tag shadows work with adds / removes * Towards S3 Params tuning sets and ParamSetCollection still missing * some fixes * a few fixes * a few fixes * quality of life stuff: set6 cache, domain class propreties, init values * some reorg * PSC & PSC trafos * relatively done with PSC * psc should be feature complete now * remove 'describe_error' * minor fixes * experiments * solution demo * progress * condition as S3 * Param.R -> Domain_methods.R * S6ObjectCache is pretty cool but we don't need it * domain -> Domain * for domain methods: default -> Domain * cleaning up * "feature complete" * more efficient tags * rename package * some bugfixes * qiute some progress * commit message * tests pass * S3 consistency * tests pass * trafo info flags * news and docs * rename back to 'paradox' * vignette progress * vignette builds * rd_info repair * work with bbotk * PSC * bugfix * checking strict now * handle requirements as in current paradox * documentation * small correction in doc * document * fix in examples * fix in examples II * document domain_-functions * document() * clean up documentation * document() * some more small doc fixes * document() --------- Co-authored-by: mb706 --- .gitignore | 7 + DESCRIPTION | 14 +- NAMESPACE | 66 +- NEWS.md | 10 +- R/Condition.R | 167 +-- R/Design.R | 8 +- R/{domain.R => Domain.R} | 248 ++--- R/Domain_methods.R | 176 +++ R/NoDefault.R | 17 +- R/Param.R | 211 ---- R/ParamDbl.R | 129 +-- R/ParamFct.R | 97 +- R/ParamInt.R | 130 +-- R/ParamLgl.R | 66 +- R/ParamSet.R | 1023 +++++++++++------- R/ParamSetCollection.R | 298 +++-- R/ParamUty.R | 101 +- R/Sampler.R | 6 +- R/Sampler1D.R | 36 +- R/SamplerHierarchical.R | 8 +- R/SamplerJointIndep.R | 7 +- R/SamplerUnif.R | 6 +- R/asserts.R | 36 +- R/generate_design_grid.R | 20 +- R/generate_design_lhs.R | 20 +- R/generate_design_random.R | 16 +- R/generate_design_sobol.R | 18 +- R/helper.R | 130 +-- R/ps.R | 73 +- R/ps_replicate.R | 60 + R/ps_union.R | 56 + R/to_tune.R | 142 ++- R/zzz.R | 7 +- attic/ParamS6.R | 71 ++ attic/ParamSet_add.R | 73 ++ attic/S6ObjectCache.R | 170 +++ attic/demo.R | 12 + attic/helper_r6.R | 78 ++ attic/vectoralgorithm.R | 130 +++ attic/vectoralgorithm_ii.R | 174 +++ man-roxygen/field_constraint.R | 4 + man-roxygen/field_extra_trafo.R | 10 + man-roxygen/field_is_bounded.R | 4 +- man-roxygen/field_levels.R | 4 +- man-roxygen/field_lower.R | 2 +- man-roxygen/field_nlevels.R | 6 +- man-roxygen/field_params.R | 4 +- man-roxygen/field_params_unid.R | 5 - man-roxygen/field_storage_type.R | 10 +- man-roxygen/field_tags.R | 4 + man-roxygen/field_upper.R | 2 +- man-roxygen/param_param.R | 3 +- man/Condition.Rd | 169 +-- man/Domain.Rd | 95 +- man/NO_DEF.Rd | 5 +- man/Param.Rd | 317 ------ man/ParamDbl.Rd | 191 ---- man/ParamFct.Rd | 154 --- man/ParamInt.Rd | 181 ---- man/ParamLgl.Rd | 140 --- man/ParamSet.Rd | 512 ++++++--- man/ParamSetCollection.Rd | 109 +- man/ParamUty.Rd | 160 --- man/Sampler.Rd | 9 +- man/Sampler1D.Rd | 11 +- man/Sampler1DCateg.Rd | 7 +- man/Sampler1DNormal.Rd | 7 +- man/Sampler1DRfun.Rd | 5 +- man/Sampler1DUnif.Rd | 5 +- man/SamplerHierarchical.Rd | 9 +- man/SamplerJointIndep.Rd | 4 +- man/SamplerUnif.Rd | 7 +- man/{assert_param.Rd => assert_param_set.Rd} | 15 +- man/domain_check.Rd | 33 + man/domain_is_bounded.Rd | 18 + man/domain_is_categ.Rd | 18 + man/domain_is_number.Rd | 18 + man/domain_nlevels.Rd | 19 + man/domain_qunif.Rd | 20 + man/domain_sanitize.Rd | 23 + man/generate_design_grid.Rd | 18 +- man/generate_design_lhs.Rd | 14 +- man/generate_design_random.Rd | 16 +- man/generate_design_sobol.Rd | 14 +- man/paradox-package.Rd | 4 +- man/ps.Rd | 21 +- man/ps_replicate.Rd | 71 ++ man/ps_union.Rd | 57 + man/to_tune.Rd | 43 +- tests/testthat/helper_02_ParamSet.R | 53 +- tests/testthat/helper_03_domain.R | 33 + tests/testthat/helper_compat.R | 42 + tests/testthat/test_Condition.R | 18 +- tests/testthat/test_Design.R | 6 +- tests/testthat/test_Param.R | 43 +- tests/testthat/test_ParamDbl.R | 33 +- tests/testthat/test_ParamFct.R | 8 +- tests/testthat/test_ParamInt.R | 20 +- tests/testthat/test_ParamLgl.R | 10 +- tests/testthat/test_ParamSet.R | 172 +-- tests/testthat/test_ParamSetCollection.R | 139 +-- tests/testthat/test_ParamUty.R | 18 +- tests/testthat/test_Param_rep.R | 19 +- tests/testthat/test_deps.R | 82 +- tests/testthat/test_domain.R | 131 ++- tests/testthat/test_generate_design.R | 66 +- tests/testthat/test_param_vals.R | 18 +- tests/testthat/test_sampler.R | 50 +- tests/testthat/test_to_tune.R | 110 +- tests/testthat/test_trafo.R | 6 +- vignettes/indepth.Rmd | 375 +++---- 111 files changed, 4210 insertions(+), 3936 deletions(-) rename R/{domain.R => Domain.R} (60%) create mode 100644 R/Domain_methods.R delete mode 100644 R/Param.R create mode 100644 R/ps_replicate.R create mode 100644 R/ps_union.R create mode 100644 attic/ParamS6.R create mode 100644 attic/ParamSet_add.R create mode 100644 attic/S6ObjectCache.R create mode 100644 attic/demo.R create mode 100644 attic/helper_r6.R create mode 100644 attic/vectoralgorithm.R create mode 100644 attic/vectoralgorithm_ii.R create mode 100644 man-roxygen/field_constraint.R create mode 100644 man-roxygen/field_extra_trafo.R delete mode 100644 man-roxygen/field_params_unid.R create mode 100644 man-roxygen/field_tags.R delete mode 100644 man/Param.Rd delete mode 100644 man/ParamDbl.Rd delete mode 100644 man/ParamFct.Rd delete mode 100644 man/ParamInt.Rd delete mode 100644 man/ParamLgl.Rd delete mode 100644 man/ParamUty.Rd rename man/{assert_param.Rd => assert_param_set.Rd} (67%) create mode 100644 man/domain_check.Rd create mode 100644 man/domain_is_bounded.Rd create mode 100644 man/domain_is_categ.Rd create mode 100644 man/domain_is_number.Rd create mode 100644 man/domain_nlevels.Rd create mode 100644 man/domain_qunif.Rd create mode 100644 man/domain_sanitize.Rd create mode 100644 man/ps_replicate.Rd create mode 100644 man/ps_union.Rd create mode 100644 tests/testthat/helper_03_domain.R diff --git a/.gitignore b/.gitignore index 310bcea7..c30156f9 100644 --- a/.gitignore +++ b/.gitignore @@ -102,5 +102,12 @@ $RECYCLE.BIN/ !.vscode/extensions.json *.code-workspace .vscode + +# Autosaves and Temp files +.#* +*~ +\#*# +*.swp + README.html cran-comments\.md diff --git a/DESCRIPTION b/DESCRIPTION index 6afba9a1..6c79cb3a 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -2,11 +2,11 @@ Type: Package Package: paradox Title: Define and Work with Parameter Spaces for Complex Algorithms -Version: 0.11.1-9000 +Version: 1.0.0 Authors@R: c(person(given = "Michel", family = "Lang", - role = c("cre", "aut"), + role = "aut", email = "michellang@gmail.com", comment = c(ORCID = "0000-0001-9754-0393")), person(given = "Bernd", @@ -26,7 +26,7 @@ Authors@R: comment = c(ORCID = "0000-0003-3269-2307")), person(given = "Martin", family = "Binder", - role = "aut", + role = c("aut", "cre"), email = "mlr.developer@mb706.com"), person(given = "Marc", family = "Becker", @@ -66,8 +66,9 @@ VignetteBuilder: knitr Collate: 'Condition.R' 'Design.R' + 'Domain.R' + 'Domain_methods.R' 'NoDefault.R' - 'Param.R' 'ParamDbl.R' 'ParamFct.R' 'ParamInt.R' @@ -82,13 +83,14 @@ Collate: 'SamplerUnif.R' 'asserts.R' 'default_values.R' - 'helper.R' - 'domain.R' 'generate_design_grid.R' 'generate_design_lhs.R' 'generate_design_random.R' 'generate_design_sobol.R' + 'helper.R' 'ps.R' + 'ps_replicate.R' + 'ps_union.R' 'reexports.R' 'to_tune.R' 'zzz.R' diff --git a/NAMESPACE b/NAMESPACE index 5c5180aa..b3eefa14 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -1,8 +1,52 @@ # Generated by roxygen2: do not edit by hand -S3method(as.data.table,Param) +S3method("$",Constructor) S3method(as.data.table,ParamSet) +S3method(c,ParamSet) +S3method(condition_as_string,Condition) +S3method(condition_test,CondAnyOf) +S3method(condition_test,CondEqual) S3method(default_values,ParamSet) +S3method(domain_check,ParamDbl) +S3method(domain_check,ParamFct) +S3method(domain_check,ParamInt) +S3method(domain_check,ParamLgl) +S3method(domain_check,ParamUty) +S3method(domain_is_bounded,Domain) +S3method(domain_is_bounded,ParamDbl) +S3method(domain_is_bounded,ParamFct) +S3method(domain_is_bounded,ParamInt) +S3method(domain_is_bounded,ParamLgl) +S3method(domain_is_bounded,ParamUty) +S3method(domain_is_categ,Domain) +S3method(domain_is_categ,ParamDbl) +S3method(domain_is_categ,ParamFct) +S3method(domain_is_categ,ParamInt) +S3method(domain_is_categ,ParamLgl) +S3method(domain_is_categ,ParamUty) +S3method(domain_is_number,Domain) +S3method(domain_is_number,ParamDbl) +S3method(domain_is_number,ParamFct) +S3method(domain_is_number,ParamInt) +S3method(domain_is_number,ParamLgl) +S3method(domain_is_number,ParamUty) +S3method(domain_nlevels,Domain) +S3method(domain_nlevels,ParamDbl) +S3method(domain_nlevels,ParamFct) +S3method(domain_nlevels,ParamInt) +S3method(domain_nlevels,ParamLgl) +S3method(domain_nlevels,ParamUty) +S3method(domain_qunif,Domain) +S3method(domain_qunif,ParamDbl) +S3method(domain_qunif,ParamFct) +S3method(domain_qunif,ParamInt) +S3method(domain_qunif,ParamLgl) +S3method(domain_qunif,ParamUty) +S3method(domain_sanitize,Domain) +S3method(domain_sanitize,ParamDbl) +S3method(domain_sanitize,ParamInt) +S3method(format,Condition) +S3method(print,Condition) S3method(print,Domain) S3method(print,FullTuneToken) S3method(print,ObjectTuneToken) @@ -13,15 +57,8 @@ export(CondEqual) export(Condition) export(Design) export(NO_DEF) -export(NoDefault) -export(Param) -export(ParamDbl) -export(ParamFct) -export(ParamInt) -export(ParamLgl) export(ParamSet) export(ParamSetCollection) -export(ParamUty) export(Sampler) export(Sampler1D) export(Sampler1DCateg) @@ -32,9 +69,18 @@ export(SamplerHierarchical) export(SamplerJointIndep) export(SamplerUnif) export(as.data.table) -export(assert_param) export(assert_param_set) +export(condition_as_string) export(default_values) +export(domain_assert) +export(domain_check) +export(domain_is_bounded) +export(domain_is_categ) +export(domain_is_number) +export(domain_nlevels) +export(domain_qunif) +export(domain_sanitize) +export(domain_test) export(generate_design_grid) export(generate_design_lhs) export(generate_design_random) @@ -45,6 +91,8 @@ export(p_int) export(p_lgl) export(p_uty) export(ps) +export(ps_replicate) +export(ps_union) export(psc) export(to_tune) import(checkmate) diff --git a/NEWS.md b/NEWS.md index 78d71ba8..79a119c3 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,11 @@ -# paradox 0.11.1-9000 - +# paradox 0.12.0 +* Removed `Param` objects. `ParamSet` now uses a `data.table` internally; individual parameters are more like `Domain` objects now. `ParamSets` should be constructed using the `ps()` shorthand and `Domain` objects. This entails the following major changes: + * `ParamSet` now supports `extra_trafo` natively; it behaves like `.extra_trafo` of the `ps()` call. + * `ParamSet` has `$constraint` + * `ParamSet` objects are now less mutable. The only properties that can be changed are `values`, `tags`, `deps`, `constraint` and `extra_trafo`. + * `ParamSet$is_bounded` is a vector with an entry for each parameter. Use `$all_bounded` for the previous behavior. + * `Condition` objects are now S3 objects and can be constructed with `CondEqual()` and `CondAnyOf()`, instead of `CondXyz$new()`. (It is recommended to use the `Domain` interface for conditions, which has not changed) + * `ParamSet` has new fields `$is_logscale`, `$has_trafo_param` (per-param), and `$has_trafo_param` (scalar for the whole set). * Added a vignette which was previously a chapter in the `mlr3book` # paradox 0.11.1 diff --git a/R/Condition.R b/R/Condition.R index 618d2794..3d58e8fc 100644 --- a/R/Condition.R +++ b/R/Condition.R @@ -1,88 +1,113 @@ +# -- class methods + +#' @describeIn Condition +#' +#' Used internally. Tests whether a value satisfies a given condition. +#' Vectorizes when `x` is atomic. +#' +#' @param cond (`Condition`)\cr +#' `Condition` to use +#' @param x (`any`)\cr +#' Value to test +condition_test = function(cond, x) { + UseMethod("condition_test") +} + +#' @describeIn Condition +#' +#' Used internally. Returns a string that represents the condition for pretty +#' printing, in the form `" "`, e.g. `"x == 3"` or +#' `"param %in% {1, 2, 10}"`. +#' +#' @param cond (`Condition`)\cr +#' `Condition` to use +#' @param lhs_chr (`character(1)`)\cr +#' Symbolic representation to use for `` in the returned string. +#' @export +condition_as_string = function(cond, lhs_chr = "x") { + assert_string(lhs_chr) + UseMethod("condition_as_string") +} + +# -- Condition + #' @title Dependency Condition #' #' @description #' Condition object, to specify the condition in a dependency. #' +#' @param rhs (`any`)\cr +#' Right-hand-side of the condition. +#' @param condition_format_string (`character(1)`)\cr +#' Format-string for representing the condition when pretty-printing +#' in [`condition_as_string()`]. +#' Should contain two `%s`, as it is used in an `sprintf()`-call with +#' two further string values. +#' #' @section Currently implemented simple conditions: -#' * `CondEqual$new(rhs)` \cr -#' Parent must be equal to `rhs`. -#' * `CondAnyOf$new(rhs)` \cr -#' Parent must be any value of `rhs`. +#' * `CondEqual(rhs)` \cr +#' Value must be equal to `rhs`. +#' * `CondAnyOf(rhs)` \cr +#' Value must be any value of `rhs`. #' #' @aliases CondEqual CondAnyOf #' @export -Condition = R6Class("Condition", - public = list( - #' @field type (`character(1)`)\cr - #' Name / type of the condition. - type = NULL, - #' @field rhs (`any`)\cr - #' Right-hand-side of the condition. - rhs = NULL, - #' @description - #' Creates a new instance of this [R6][R6::R6Class] class. - #' - #' @param type (`character(1)`)\cr - #' Name / type of the condition. - #' @param rhs (`any`)\cr - #' Right-hand-side of the condition. - initialize = function(type, rhs) { - self$type = assert_string(type) - self$rhs = rhs - }, +Condition = function(rhs, condition_format_string) { + assert_string(condition_format_string) + structure(list(rhs = rhs, condition_format_string = condition_format_string), class = "Condition") +} - #' @description - #' Checks if condition is satisfied. - #' Called on a vector of parent param values. - #' - #' @param x (`vector()`). - #' @return `logical(1)`. - test = function(x) stop("abstract"), +#' @export +condition_as_string.Condition = function(cond, lhs_chr = "x") { + sprintf(cond$condition_format_string, lhs_chr, str_collapse(cond$rhs)) +} + +#' @export +format.Condition = function(x, ...) { + sprintf("", class(x)[[1L]]) +} + +#' @export +print.Condition = function(x, ...) { + catf("%s: %s", class(x)[[1L]], condition_as_string(x)) +} - #' @description - #' Conversion helper for print outputs. - #' @param lhs_chr (`character(1)`) - as_string = function(lhs_chr = "x") { - sprintf("%s %s %s", lhs_chr, self$type, str_collapse(self$rhs)) - }, +# -- CondEqual - #' @description - #' Helper for print outputs. - #' @param ... (ignored). - format = function(...) { - sprintf("<%s:%s>", class(self)[1L], self$type) - }, +#' @export +CondEqual = function(rhs) { + assert_atomic(rhs, any.missing = FALSE, len = 1) + cond = Condition(rhs, "%s == %s") + set_class(cond, c("CondEqual", class(cond))) +} - #' @description - #' Printer. - #' - #' @param ... (ignored). - print = function(...) { - catf("%s: %s", class(self)[1L], self$as_string()) - } - ), -) +#' @export +condition_test.CondEqual = function(cond, x) { + !is.na(x) & x == cond$rhs +} #' @export -CondEqual = R6Class("CondEqual", inherit = Condition, - public = list( - initialize = function(rhs) { - assert_atomic(rhs, any.missing = FALSE, len = 1) - super$initialize("equal", rhs) - }, - test = function(x) !is.na(x) & x == self$rhs, - as_string = function(lhs_chr = "x") sprintf("%s = %s", lhs_chr, as.character(self$rhs)) - ) -) +CondAnyOf = function(rhs) { + assert_atomic(rhs, any.missing = FALSE, min.len = 1, unique = TRUE) + cond = Condition(rhs, "%s %%in%% {%s}") + set_class(cond, c("CondAnyOf", class(cond))) +} #' @export -CondAnyOf = R6Class("CondAnyOf", inherit = Condition, - public = list( - initialize = function(rhs) { - assert_atomic(rhs, any.missing = FALSE, min.len = 1, unique = TRUE) - super$initialize("anyof", rhs) - }, - test = function(x) !is.na(x) & x %in% self$rhs, - as_string = function(lhs_chr = "x") sprintf("%s \u2208 {%s}", lhs_chr, str_collapse(self$rhs)) - ) -) +condition_test.CondAnyOf = function(cond, x) { + !is.na(x) & x %in% cond$rhs +} + +# FIXME: the following makes `condition$new()` possible for paradox transition +# should give a deprecated warning at some point. +#' @export +`$.Constructor` = function(e1, e2) { + if (!identical(e2, "new")) { + stop("only 'new' element can be accessed.") + } else { + e1 + } +} + +CondEqual = structure(CondEqual, class = c("Constructor", "function")) +CondAnyOf = structure(CondAnyOf, class = c("Constructor", "function")) diff --git a/R/Design.R b/R/Design.R index 71ed96db..41a6b425 100644 --- a/R/Design.R +++ b/R/Design.R @@ -82,7 +82,7 @@ Design = R6Class("Design", xs = map(xs, function(x) Filter(Negate(is_scalar_na), x)) } if (ps$has_trafo && trafo) { - xs = map(xs, function(x) ps$trafo(x, ps)) + xs = map(xs, function(x) ps$trafo(x)) } return(xs) } @@ -103,14 +103,14 @@ Design = R6Class("Design", graph = graph[, list("parents" = list(unlist(get("parents")))), by = "id"] topo = topo_sort(graph) pids_sorted = topo$id + storage_types = ps$storage_type for (param_id in pids_sorted) { - param = ps$params[[param_id]] dd = ps$deps[get("id") == param_id, ] for (j in seq_row(dd)) { pcol = self$data[[dd$on[j]]] # we are ok if parent was active and cond on parent is OK - not_ok = which(is.na(pcol) | !dd$cond[[j]]$test(pcol)) - set(self$data, not_ok, j = param_id, value = as_type(NA, param$storage_type)) + not_ok = which(is.na(pcol) | !condition_test(dd$cond[[j]], pcol)) + set(self$data, not_ok, j = param_id, value = as_type(NA, storage_types[[param_id]])) } } } diff --git a/R/domain.R b/R/Domain.R similarity index 60% rename from R/domain.R rename to R/Domain.R index 68532c6d..56b98a55 100644 --- a/R/domain.R +++ b/R/Domain.R @@ -1,19 +1,16 @@ -#' @include helper.R - #' @title Domain: Parameter Range without an Id #' #' @description #' A `Domain` object is a representation of a single dimension of a [`ParamSet`]. `Domain` objects are used to construct -#' [`ParamSet`]s, either through the [`ps()`] short form, or through the [`ParamSet`]`$search_space()` mechanism (see -#' [`to_tune()`]). `Domain` corresponds to a [`Param`] object, except it does not have an `$id`, and it *does* have a -#' `trafo` and dependencies (`depends`) associated with it. For each of the basic [`Param`] classes ([`ParamInt`], -#' [`ParamDbl`], [`ParamLgl`], [`ParamFct`], and [`ParamUty`]) there is a function constructing a `Domain` object -#' (`p_int()`, `p_dbl()`, `p_lgl()`, `p_fct()`, `p_uty()`). They each have the same arguments as the corresponding -#' [`Param`] `$new()` function, except without the `id` argument, and with the the additional parameters `trafo`, and -#' `depends`. +#' [`ParamSet`]s, either through the [`ps()`] short form, through the [`ParamSet`] constructor itself, +#' or through the [`ParamSet`]`$search_space()` mechanism (see +#' [`to_tune()`]). +#' For each of the basic parameter classes (`"ParamInt"`, `"ParamDbl"`, `"ParamLgl"`, `"ParamFct"`, and `"ParamUty"`) there is a function constructing a `Domain` object +#' (`p_int()`, `p_dbl()`, `p_lgl()`, `p_fct()`, `p_uty()`). They each have fitting construction arguments that control their +#' bounds and behavior. #' #' `Domain` objects are representations of parameter ranges and are intermediate objects to be used in short form -#' constructions in [`to_tune()`] and [`ps()`]. Because of their nature, they should not be modified by the user. +#' constructions in [`to_tune()`] and [`ps()`]. Because of their nature, they should not be modified by the user, once constructed. #' The `Domain` object's internals are subject to change and should not be relied upon. #' #' @template param_lower @@ -38,17 +35,17 @@ #' An expression indicating a requirement for the parameter that will be constructed from this. Can be given as an #' expression (using `quote()`), or the expression can be entered directly and will be parsed using NSE (see #' examples). The expression may be of the form ` == ` or ` %in% `, which will result in -#' dependencies according to `ParamSet$add_dep(on = "", cond = CondEqual$new())` or -#' `ParamSet$add_dep(on = "", cond = CondAnyOf$new())`, respectively (see [`CondEqual`], +#' dependencies according to `ParamSet$add_dep(on = "", cond = CondEqual())` or +#' `ParamSet$add_dep(on = "", cond = CondAnyOf())`, respectively (see [`CondEqual`], #' [`CondAnyOf`]). The expression may also contain multiple conditions separated by `&&`. #' @param logscale (`logical(1)`)\cr #' Put numeric domains on a log scale. Default `FALSE`. Log-scale `Domain`s represent parameter ranges where lower and upper bounds #' are logarithmized, and where a `trafo` is added that exponentiates sampled values to the original scale. This is #' *not* the same as setting `trafo = exp`, because `logscale = TRUE` will handle parameter bounds internally: -#' a `p_dbl(1, 10, logscale = TRUE)` results in a [`ParamDbl`] that has lower bound `0`, upper bound `log(10)`, +#' a `p_dbl(1, 10, logscale = TRUE)` results in a parameter that has lower bound `0`, upper bound `log(10)`, #' and uses `exp` transformation on these. Therefore, the given bounds represent the bounds *after* the transformation. #' (see examples).\cr -#' `p_int()` with `logscale = TRUE` results in a [`ParamDbl`], not a [`ParamInt`], but with bounds `log(max(lower, 0.5))` ... +#' `p_int()` with `logscale = TRUE` results in a continuous parameter similar to `p_dbl()`, not an integer-valued parameter, with bounds `log(max(lower, 0.5))` ... #' `log(upper + 1)` and a trafo similar to "`as.integer(exp(x))`" (with additional bounds correction). The lower bound #' is lifted to `0.5` if `lower` 0 to handle the `lower == 0` case. The upper bound is increased to `log(upper + 1)` #' because the trafo would otherwise almost never generate a value of `upper`.\cr @@ -60,12 +57,19 @@ #' defining domains or hyperparameter ranges of learning algorithms, because these do not use trafos.\cr #' `logscale` happens on a natural (`e == 2.718282...`) basis. Be aware that using a different base (`log10()`/`10^`, #' `log2()`/`2^`) is completely equivalent and does not change the values being sampled after transformation. +#' @param repr (`language`)\cr +#' Symbol to use to represent the value given in `default`. +#' The `deparse()` of this object is used when printing the domain, in some cases. +#' @param init (`any`)\cr +#' Initial value. When this is given, then the corresponding entry in `ParamSet$values` is initialized with this +#' value upon construction. #' #' @return A `Domain` object. #' #' @details -#' The `p_fct` function admits a `levels` argument that goes beyond the `levels` accepted by [`ParamFct`]`$new()`. -#' Instead of a `character` vector, any atomic vector or list (optionally named) may be given. (If the value is a list +#' Although the `levels` values of a constructed `p_fct()` will always be `character`-valued, the `p_fct` function admits +#' a `levels` argument that goes beyond this: +#' Besides a `character` vector, any atomic vector or list (optionally named) may be given. (If the value is a list #' that is not named, the names are inferred using `as.character()` on the values.) The resulting `Domain` will #' correspond to a range of values given by the names of the `levels` argument with a `trafo` that maps the `character` #' names to the arbitrary values of the `levels` argument. @@ -103,7 +107,7 @@ #' # But the values are on a log scale with desired bounds after trafo #' print(grid$transpose()) #' -#' # Integer parameters with logscale are `ParamDbl`s pre-trafo +#' # Integer parameters with logscale are `p_dbl()`s pre-trafo #' params = ps(x = p_int(0, 10, logscale = TRUE)) #' print(params) #' @@ -117,103 +121,32 @@ #' @name Domain NULL -#' @rdname Domain -#' @export -p_int = function(lower = -Inf, upper = Inf, special_vals = list(), default = NO_DEF, tags = character(), depends = NULL, trafo = NULL, logscale = FALSE) { - if (assert_flag(logscale)) { - if (!is.null(trafo)) stop("When a trafo is given then logscale must be FALSE") - # assert_int will stop for `Inf` values - if (!isTRUE(is.infinite(lower))) assert_int(lower) - if (!isTRUE(is.infinite(upper))) assert_int(upper) - if (lower < 0) stop("When logscale is TRUE then lower bound must be greater or equal 0") - trafo = crate(function(x) as.integer(max(min(exp(x), upper), lower)), lower, upper) - constargs_override = list(lower = log(max(lower, 0.5)), upper = log(upper + 1)) - constructor = ParamDbl - } else { - constructor = ParamInt - constargs_override = NULL - } - - domain(constructor = constructor, constargs = as.list(match.call()[-1]), - depends_expr = substitute(depends), trafo = trafo, constargs_override = constargs_override) -} - -#' @rdname Domain -#' @export -p_dbl = function(lower = -Inf, upper = Inf, special_vals = list(), default = NO_DEF, tags = character(), tolerance = sqrt(.Machine$double.eps), depends = NULL, trafo = NULL, logscale = FALSE) { - if (assert_flag(logscale)) { - if (!is.null(trafo)) stop("When a trafo is given then logscale must be FALSE") - if (assert_number(lower) <= 0) stop("When logscale is TRUE then lower bound must be strictly greater than 0") - trafo = exp - constargs_override = list(lower = log(lower), upper = log(assert_number(upper))) - } else { - constargs_override = NULL - } - - domain(constructor = ParamDbl, constargs = as.list(match.call()[-1]), - depends_expr = substitute(depends), trafo = trafo, constargs_override = constargs_override) -} - -#' @rdname Domain -#' @export -p_uty = function(default = NO_DEF, tags = character(), custom_check = NULL, depends = NULL, trafo = NULL) { - # For better printing of untyped parameters - constargs = as.list(match.call()[-1]) - if (!missing(default)) constargs$repr = as.character(substitute(default)) - domain(constructor = ParamUty, constargs = constargs, - depends_expr = substitute(depends), trafo = trafo) -} - -#' @rdname Domain -#' @export -p_lgl = function(special_vals = list(), default = NO_DEF, tags = character(), depends = NULL, trafo = NULL) { - domain(constructor = ParamLgl, constargs = as.list(match.call()[-1]), - depends_expr = substitute(depends), trafo = trafo) -} - -#' @rdname Domain -#' @export -p_fct = function(levels, special_vals = list(), default = NO_DEF, tags = character(), depends = NULL, trafo = NULL) { - constargs = as.list(match.call()[-1]) - levels = eval.parent(constargs$levels) - if (!is.character(levels)) { - # if the "levels" argument is not a character vector, then - # we add a trafo. - assert(check_atomic_vector(levels), check_list(levels)) - if (is.null(names(levels))) { - names(levels) = as.character(levels) - } - trafo = crate(function(x) { - x = levels[[x]] - if (!is.null(trafo)) x = trafo(x) - x - }, trafo, levels) - constargs$levels = names(levels) - } - domain(constructor = ParamFct, constargs = constargs, depends_expr = substitute(depends), trafo = trafo) -} - # Construct the actual `Domain` object # @param Constructor: The ParamXxx to call `$new()` for. # @param constargs: arguments of constructor # @param constargs_override: replace these in `constargs`, but don't represent this in printer -domain = function(constructor, constargs, depends_expr = NULL, trafo = NULL, constargs_override = NULL) { - constargs$trafo = NULL - constargs$depends = NULL - constargs = map(constargs, eval, envir = parent.frame(2)) - reprargs = constargs - - constargs$logscale = NULL - constargs = insert_named(constargs, constargs_override) - +Domain = function(cls, grouping, + cargo = NULL, + lower = NA_real_, upper = NA_real_, tolerance = NA_real_, levels = NULL, + special_vals = list(), + default = NO_DEF, + tags = character(0), + trafo = NULL, + depends_expr = NULL, + storage_type = "list", + init) { - if ("id" %in% names(constargs)) stop("id must not be given to p_xxx") + assert_string(cls) + assert_string(grouping) + assert_number(lower, na.ok = TRUE) + assert_number(upper, na.ok = TRUE) + assert_number(tolerance, na.ok = TRUE) + if (!is.logical(levels)) assert_character(levels, any.missing = FALSE, unique = TRUE, null.ok = TRUE) + assert_list(special_vals) + if (length(special_vals) && !is.null(trafo)) stop("trafo and special_values can not both be given at the same time.") + assert_character(tags, any.missing = FALSE, unique = TRUE) + assert_function(trafo, null.ok = TRUE) - # check that `...` are valid by constructing and making sure this doesn't error - # The object generated here is thrown away, this is only for checks. - param = invoke(constructor$new, id = "ID", .args = constargs) - param[[".__enclos_env__"]][["private"]]$.has_logscale = isTRUE(reprargs$logscale) - param[[".__enclos_env__"]][["private"]]$.has_trafo = !is.null(trafo) && !isTRUE(reprargs$logscale) # depends may be an expression, but may also be quote() or expression() if (length(depends_expr) == 1) { @@ -223,28 +156,95 @@ domain = function(constructor, constargs, depends_expr = NULL, trafo = NULL, con } } + # domain is a data.table with a few classes. + # setting `id` to something preliminary so that `domain_assert()` works. + + param = data.table(id = "domain being constructed", cls = cls, grouping = grouping, + cargo = list(cargo), + lower = lower, upper = upper, tolerance = tolerance, levels = list(levels), + special_vals = list(special_vals), + default = list(default), + storage_type = storage_type, + .tags = list(tags), + .trafo = list(trafo), + .requirements = list(parse_depends(depends_expr, parent.frame(2))), + + .init_given = !missing(init), + .init = list(if (!missing(init)) init) + ) + + class(param) = c(cls, "Domain", class(param)) + + if (!is_nodefault(default)) { + domain_assert(param, list(default)) + if ("required" %in% tags) stop("A 'required' parameter can not have a 'default'.\nWhen the method behaves the same as if the parameter value were 'X' whenever the parameter is missing, then 'X' should be a 'default', but the 'required' indicates that the parameter may not be missing.") + } + + if (!missing(init)) { + if (!is.null(trafo)) stop("Initial value and trafo can not both be given at the same time.") + domain_assert(param, list(init)) + if (identical(init, default)) warning("Initial value and 'default' value seem to be the same, this is usually a mistake due to a misunderstanding of the meaning of 'default'.\nWhen the method behaves the same as if the parameter value were 'X' whenever the parameter is missing, then 'X' should be a 'default' (but then there is no point in setting it as initial value). 'default' should not be used to indicate the value with which values are initialized.") + } + # repr: what to print - repr = sys.call(-1) - traforep = repr$trafo + # This takes the call of the shortform-constructor (such as `p_dbl()`) and inserts all the + # given values. + constructorcall = match.call(sys.function(-1), sys.call(-1), envir = parent.frame(2)) + trafoexpr = constructorcall$trafo + constructorcall$trafo = NULL + constructorcall$depends = NULL + reprargs = sapply(names(constructorcall)[-1], get, pos = parent.frame(1), simplify = FALSE) + reprargs$depends = depends_expr + reprargs$trafo = trafoexpr + if (isTRUE(reprargs$logscale)) reprargs$trafo = NULL + attr(param, "repr") = as.call(c(constructorcall[[1]], reprargs)) + set(param, , "id", repr(attr(param, "repr"))) # some ID for consistency with ParamSet$params, only for error messages. - repr = as.call(c(as.list(repr)[[1]], reprargs)) # use cleaned up constargs - repr$depends = depends_expr # put `depends` at the end, but only if not NULL - repr$trafo = traforep # put `trafo` at the end, but only if not NULL - if (isTRUE(repr$logscale)) repr$trafo = NULL # when the user declared logscale then the trafo stays hidden. + assert_names(names(param), identical.to = domain_names) # If this is not true then there is either a bug in Domain(), or empty_domain was not updated. - set_class(list( - param = param, - trafo = assert_function(trafo, null.ok = TRUE), - requirements = parse_depends(depends_expr, parent.frame(2)), - repr = repr - ), "Domain") + param } +empty_domain = data.table(id = character(0), cls = character(0), grouping = character(0), + cargo = list(), + lower = numeric(0), upper = numeric(0), tolerance = numeric(0), levels = list(), + special_vals = list(), + default = list(), + storage_type = character(0), + .tags = character(0), # should be list(), strictly speaking, but that would lose the 'character' type information + .trafo = list(), + .requirements = list(), + .init_given = logical(0), + .init = list() +) + +domain_names = names(empty_domain) +domain_names_permanent = grep("^\\.", domain_names, value = TRUE, invert = TRUE) + #' @export print.Domain = function(x, ...) { - print(x$repr) + repr = attr(x, "repr") + if (!is.null(repr)) { + print(repr) + } else { + plural_rows = + classes = class(x) + if ("Domain" %in% classes) { + domainidx = which("Domain" == classes)[[1]] + classes = first(classes, domainidx - 1) + class(x) = last(class(x), -domainidx) + } + catf("Param%s of class%s %s:\n", + if (NROW(x) > 1) "s" else "", + if (length(classes) > 1) "es" else "", + str_collapse(classes, sep = ", ", quote = '"') + ) + print(x) + } } + + # Parse the expression for requirements, as they are given to p_int, p_dbl etc. # We allow `==`, `%in%` `&&`, and `(`/`)` to occur in such expressions. # We construct a list of `Condition` objects with an additional `on` element of what @@ -254,8 +254,8 @@ print.Domain = function(x, ...) { # parse_depends(quote(x == 1 && y %in% c("b", "c")), environment()) # # same as: # list( -# list(on = "x", CondEqual$new(1)), -# list(on = "y", CondAnyOf$new(c("b", "c"))) +# list(on = "x", CondEqual(1)), +# list(on = "y", CondAnyOf(c("b", "c"))) # ) parse_depends = function(depends_expr, evalenv) { if (is.null(depends_expr)) return(NULL) @@ -324,7 +324,7 @@ parse_depends = function(depends_expr, evalenv) { if (!is.symbol(comparand)) throw("LHS must be a parameter name") comparand = as.character(comparand) value = eval(value, envir = evalenv) - list(list(on = comparand, cond = constructor$new(value))) + list(list(on = comparand, cond = constructor(value))) } recurse_expression(depends_expr) diff --git a/R/Domain_methods.R b/R/Domain_methods.R new file mode 100644 index 00000000..4ca7530d --- /dev/null +++ b/R/Domain_methods.R @@ -0,0 +1,176 @@ +#' @title Check Value Validity +#' +#' @description +#' \pkg{checkmate}-like check-function. Check whether a list of values is feasible in the domain. +#' A value is feasible if it is of the same `storage_type`, inside of the bounds or element of +#' `special_vals`. `TuneToken`s are generally *not* accepted, so they should be filtered out +#' before the call, if present. +#' +#' `domain_check` will return `TRUE` for accepted values, a `character(1)` error message otherwise. +#' +#' `domain_test` will return `TRUE` for accepted values, `FALSE` otherwise. +#' +#' `domain_assert` will return the `param` argument silently for accepted values, and throw an error message otherwise. +#' +#' @param x (`any`). +#' @return If successful `TRUE`, if not a string with the error message. +#' @keywords internal +#' @export +domain_check = function(param, values) { + if (!test_list(values, len = nrow(param))) return("values must be a list") + if (length(values) == 0) return(TRUE) # happens when there are no params + values to check + assert_string(unique(param$grouping)) + special_vals_hit = pmap_lgl(list(param$special_vals, values), has_element) + if (any(special_vals_hit)) { + # don't annoy domain_check methods with the burdon of having to filter out + # values that match special_values + Recall(param[!special_vals_hit], values[!special_vals_hit]) + } else { + UseMethod("domain_check") + } +} + +#' @export +#' @rdname domain_check +domain_assert = makeAssertionFunction(domain_check) + +#' @export +#' @rdname domain_check +domain_test = function(param, values) isTRUE(domain_check(param, values)) + + +#' @title The Number of Levels of a Given Domain +#' +#' @description +#' This should be the number of discrete possible levels for discrete type [`Domain`]s such as [`p_int()`] or [`p_fct()`], and +#' `Inf` for continuous or untyped parameters. +#' +#' @param x (`Domain`). +#' @return `numeric`. +#' @keywords internal +#' @export +domain_nlevels = function(param) { + if (!nrow(param)) return(integer(0)) + assert_string(unique(param$grouping)) + UseMethod("domain_nlevels") +} + +#' @title Whether a Given Domain is Bounded +#' +#' @description +#' This should generally be `TRUE` when `lower` and `upper` are given and finite, or when the `nlevels` is finite, and `FALSE` otherwise. +#' +#' @param x (`Domain`). +#' @return `logical`. +#' @keywords internal +#' @export +domain_is_bounded = function(param) { + if (!nrow(param)) return(logical(0)) + assert_string(unique(param$grouping)) + UseMethod("domain_is_bounded") +} + +#' @title Whether a Given Domain is Numeric +#' +#' @description +#' This should generally be `TRUE` for discrete or continuous numeric [`Domain`]s, and `FALSE` otherwise. +#' +#' @param x (`Domain`). +#' @return `logical`. +#' @keywords internal +#' @export +domain_is_number = function(param) { + if (!nrow(param)) return(logical(0)) + assert_string(unique(param$grouping)) + UseMethod("domain_is_number") +} + +#' @title Whether a Given Domain is Categorical +#' +#' @description +#' This should generally be `TRUE` for categorical [`Domain`]s, such as [`p_fct()`] or [`p_lgl()`], and `FALSE` otherwise. +#' +#' @param x (`Domain`). +#' @return `logical`. +#' @keywords internal +#' @export +domain_is_categ = function(param) { + if (!nrow(param)) return(logical(0)) + assert_string(unique(param$grouping)) + UseMethod("domain_is_categ") +} + +#' @title Transform a Numeric Value to a Sample +#' +#' @description +#' Return a valid sample from the given [`Domain`], given a value from the interval `[0, 1]`. +#' +#' @param param (`Domain`). +#' @param x `numeric` between 0 and 1. +#' @return `any` -- format depending on the `Domain`. +#' @keywords internal +#' @export +domain_qunif = function(param, x) { + if (!nrow(param)) return(logical(0)) + assert_string(unique(param$grouping)) + assert_numeric(x, lower = 0, upper = 1, any.missing = FALSE) + assert_true(length(x) %% length(nrow(param)) == 0) + UseMethod("domain_qunif") +} + +#' @title Map to Acceptable Value +#' +#' @description +#' Map values that are close enough to the given [`Domain`] to values that are truly acceptable. +#' +#' This is used to map `numeric()` values that are close to but outside the acceptable interval to the interval bounds. +#' It is also used to convert integer-valued `numeric` values to `integer` values for [`p_int()`]. +#' +#' @param param (`Domain`). +#' @param values (`any`) -- format depending on the `Domain`. +#' @return `any` -- format depending on the `Domain`. +#' @keywords internal +#' @export +domain_sanitize = function(param, values) { + if (!nrow(param)) return(values) + assert_string(unique(param$grouping)) + UseMethod("domain_sanitize") +} + +#' @export +domain_nlevels.Domain = function(param) rep(Inf, nrow(param)) + +#' @export +domain_is_bounded.Domain = function(param) rep(FALSE, nrow(param)) + +#' @export +domain_qunif.Domain = function(param, x) stop("undefined") + +#' @export +domain_sanitize.Domain = function(param, values) values + +#' @export +domain_is_categ.Domain = function(param) rep(FALSE, nrow(param)) + +#' @export +domain_is_number.Domain = function(param) rep(FALSE, nrow(param)) + + +# param: +check_domain_vectorize = function(ids, values, checker, more_args = list()) { + if (is.function(checker)) { + errors = pmap(c(list(ids, values), more_args), function(id, value, ...) { + ch = checker(value, ...) + if (isTRUE(ch)) NULL else sprintf("%s: %s", id, ch) + }) + } else { + # `checker` is a list of functions with the same length as `values` + errors = pmap(c(list(ids, values, checker), more_args), function(id, value, chck, ...) { + ch = chck(value, ...) + if (isTRUE(ch)) NULL else sprintf("%s: %s", id, ch) + }) + } + errors = unlist(errors) + if (!length(errors)) return(TRUE) + str_collapse(errors, sep = "\n") +} diff --git a/R/NoDefault.R b/R/NoDefault.R index 31de1240..d2a38c29 100644 --- a/R/NoDefault.R +++ b/R/NoDefault.R @@ -4,22 +4,13 @@ #' Special new data type for no-default. #' Not often needed by the end-user, mainly internal. #' -#' * `NoDefault`: R6 factory. -#' * `NO_DEF`: R6 Singleton object for type, used in [Param]. -#' * `is_nodefault()`: Is an object of type 'no default'? +#' * `NO_DEF`: Singleton object for type, used in [`Domain`] when no default is given. +#' * `is_nodefault()`: Is an object the 'no default' object? #' #' @name NO_DEF #' @aliases NoDefault is_nodefault NULL #' @export -NoDefault = R6Class("NoDefault", - public = list( - initialize = function() { - } - ), -) - -#' @export -NO_DEF = NoDefault$new() # nolint -is_nodefault = function(x) test_r6(x, "NoDefault") +NO_DEF = structure(list(), class = "NoDefault") # nolint +is_nodefault = function(x) identical(x, NO_DEF) diff --git a/R/Param.R b/R/Param.R deleted file mode 100644 index 8ceb299a..00000000 --- a/R/Param.R +++ /dev/null @@ -1,211 +0,0 @@ -#' @title Param Class -#' -#' @description -#' This is the abstract base class for parameter objects like [ParamDbl] and -#' [ParamFct]. -#' -#' @template param_id -#' @template param_special_vals -#' @template param_default -#' @template param_tags -#' -#' @section S3 methods: -#' * `as.data.table()`\cr -#' [Param] -> [data.table::data.table()]\cr -#' Converts param to [data.table::data.table()] with 1 row. See [ParamSet]. -#' -#' @family Params -#' @export -Param = R6Class("Param", - public = list( - #' @field id (`character(1)`)\cr - #' Identifier of the object. - id = NULL, - - #' @field description (`character(1)`)\cr - #' String to describe this parameter. Used, for example, in [mlr3misc::rd_info()] to automatically - #' generate documentation for parameter sets. - description = NULL, - - - #' @field special_vals (`list()`)\cr - #' Arbitrary special values this parameter is allowed to take. - special_vals = NULL, - - #' @field default (`any`)\cr - #' Default value. - default = NULL, - - #' @field tags (`character()`)\cr - #' Arbitrary tags to group and subset parameters. - tags = NULL, - - #' @description - #' Creates a new instance of this [R6][R6::R6Class] class. - #' - #' Note that this object is typically constructed via derived classes, - #' e.g., [ParamDbl]. - initialize = function(id, special_vals, default, tags) { - - assert_id(id) - assert_names(id, type = "strict") - assert_list(special_vals) - assert_character(tags, any.missing = FALSE, unique = TRUE) - - self$id = id - self$special_vals = special_vals - self$default = default - self$tags = tags - if (!is_nodefault(default)) { # check that default is feasible - self$assert(default) - } - }, - - #' @description - #' \pkg{checkmate}-like check-function. Take a value from the domain of the - #' parameter, and check if it is feasible. A value is feasible if it is of - #' the same `storage_type`, inside of the bounds or element of - #' `special_vals`. - #' - #' @param x (`any`). - #' @return If successful `TRUE`, if not a string with the error message. - check = function(x) { - # either we are directly feasible, or in special vals, if both are untrue return errmsg from 1st check - if (inherits(x, "TuneToken")) { - return(tryCatch({ - tunetoken_to_ps(x, self, self$id) - TRUE - }, error = function(e) paste("tune token invalid:", conditionMessage(e)))) - } - ch = private$.check(x) - ifelse(isTRUE(ch) || has_element(self$special_vals, x), TRUE, ch) - }, - - #' @description - #' \pkg{checkmate}-like assert-function. Take a value from the domain of - #' the parameter, and assert if it is feasible. A value is feasible if it - #' is of the same `storage_type`, inside of the bounds or element of - #' `special_vals`. - #' - #' @param x (`any`). - #' @return If successful `x` invisibly, if not an exception is raised. - assert = function(x) makeAssertionFunction(self$check)(x), - - #' @description - #' \pkg{checkmate}-like test-function. Take a value from the domain of the - #' parameter, and test if it is feasible. A value is feasible if it is of - #' the same `storage_type`, inside of the bounds or element of - #' `special_vals`. - #' - #' @param x (`any`). - #' @return If successful `TRUE`, if not `FALSE`. - test = function(x) makeTestFunction(self$check)(x), - - #' @description - #' Repeats this parameter n-times (by cloning). - #' Each parameter is named "\[id\]_rep_\[k\]" and gets the additional tag "\[id\]_rep". - #' - #' @param n (`integer(1)`). - #' @return [ParamSet]. - rep = function(n) { - assert_count(n) - pid = self$id - join_id = paste0(pid, "_rep") - ps = replicate(n, self$clone(), simplify = FALSE) - for (i in 1:n) { - p = ps[[i]] - p$id = paste0(join_id, "_", i) - p$tags = c(p$tags, join_id) - } - ParamSet$new(ps) - }, - - #' @description - #' Helper for print outputs. - #' @param ... (ignored). - format = function(...) { - sprintf("<%s:%s>", class(self)[1L], self$id) - }, - - #' @description - #' Printer. - #' - #' @param ... (ignored). - #' @param hide_cols (`character()`)\cr - #' Which fields should not be printed? Default is `"nlevels"`, - #' `"is_bounded"`, `"special_vals"`, `"tags"`, and `"storage_type"`. - print = function(..., hide_cols = c("nlevels", "is_bounded", "special_vals", "tags", "storage_type")) { - # this is bit bullshitty, but works by delegating to the printer of the PS - d = as.data.table(ParamSet$new(list(self))) - assert_subset(hide_cols, names(d)) - print(d[, setdiff(colnames(d), hide_cols), with = FALSE]) - }, - - #' @description - #' Takes values from \[0,1\] and maps them, regularly distributed, to the - #' domain of the parameter. Think of: quantile function or the use case to - #' map a uniform-\[0,1\] random variable into a uniform sample from this - #' param. - #' - #' @param x (`numeric(1)`). - #' @return Value of the domain of the parameter. - qunif = function(x) { - assert_numeric(x, lower = 0, upper = 1) - assert_true(self$is_bounded) - private$.qunif(x) - }, - - #' @description - #' Converts a value to the closest valid param. Only for values that - #' pass `$check()` and mostly used internally. - #' @param x (`any`). - #' @return `x` converted to a valid type for the `Param`. - convert = function(x) { - x - } - ), - - active = list( - #' @field class (`character(1)`)\cr - #' R6 class name. Read-only. - class = function() class(self)[[1L]], - - #' @field is_number (`logical(1)`)\cr - #' `TRUE` if the parameter is of type `"dbl"` or `"int"`. - is_number = function() self$class %in% c("ParamDbl", "ParamInt"), - - #' @field is_categ (`logical(1)`)\cr - #' `TRUE` if the parameter is of type `"fct"` or `"lgl"`. - is_categ = function() self$class %in% c("ParamFct", "ParamLgl"), - - #' @field has_default (`logical(1)`)\cr - #' Is there a default value? - has_default = function() !is_nodefault(self$default) - ), - - private = list( - .check = function(x) stop("abstract"), - .qunif = function(x) stop("abstract"), # should be implemented by subclasses, argcheck happens in Param$qunif - # is `TRUE` when `exp()` transformation function is applied to parameter - .has_logscale = FALSE, - # is `TRUE` when transformation function is applied to parameter - .has_trafo = FALSE - ) -) - -#' @export -as.data.table.Param = function(x, ...) { # nolint - data.table( - id = x$id, - class = x$class, - lower = x$lower, - upper = x$upper, - levels = list(x$levels), - nlevels = x$nlevels, - is_bounded = x$is_bounded, - special_vals = list(x$special_vals), - default = list(x$default), - storage_type = x$storage_type, - tags = list(x$tags) - ) -} diff --git a/R/ParamDbl.R b/R/ParamDbl.R index 84a9e31e..73000591 100644 --- a/R/ParamDbl.R +++ b/R/ParamDbl.R @@ -1,86 +1,55 @@ -#' @title Numerical Parameter -#' -#' @description -#' A [Param] to describe real-valued parameters. -#' -#' @note -#' The upper and lower bounds in `$check()` are expanded by -#' `sqrt(.Machine$double.eps)` to prevent errors due to the precision of double -#' values. -#' -#' @template param_id -#' @template param_lower -#' @template param_upper -#' @template param_special_vals -#' @template param_default -#' @template param_tags -#' @template param_tolerance -#' -#' @family Params -#' @include Param.R +#' @rdname Domain #' @export -#' @examples -#' ParamDbl$new("ratio", lower = 0, upper = 1, default = 0.5) -ParamDbl = R6Class("ParamDbl", inherit = Param, - public = list( - #' @template field_lower - lower = NULL, +p_dbl = function(lower = -Inf, upper = Inf, special_vals = list(), default = NO_DEF, tags = character(), tolerance = sqrt(.Machine$double.eps), depends = NULL, trafo = NULL, logscale = FALSE, init) { + assert_number(tolerance, lower = 0) + assert_number(lower) + assert_number(upper) + assert_true(lower <= upper) + if (assert_flag(logscale)) { + if (!is.null(trafo)) stop("When a trafo is given then logscale must be FALSE") + if (assert_number(lower) <= 0) stop("When logscale is TRUE then lower bound must be strictly greater than 0") + trafo = exp + # at this point we don't want to overwrite 'lower' and 'upper, since they get used for the representation + real_lower = log(lower) + real_upper = log(assert_number(upper)) + } else { + real_lower = lower + real_upper = upper + } - #' @template field_upper - upper = NULL, + Domain(cls = "ParamDbl", grouping = "ParamDbl", lower = real_lower, upper = real_upper, special_vals = special_vals, default = default, tags = tags, tolerance = tolerance, trafo = trafo, storage_type = "numeric", + depends_expr = substitute(depends), init = init, cargo = if (logscale) "logscale") +} - #' @field tolerance (`numeric(1)`)\cr - #' tolerance of values to accept beyond `$lower` and `$upper`. - #' Used both for relative and absolute tolerance. - tolerance = NULL, - - #' @description - #' Creates a new instance of this [R6][R6::R6Class] class. - initialize = function(id, lower = -Inf, upper = Inf, special_vals = list(), default = NO_DEF, tags = character(), tolerance = sqrt(.Machine$double.eps)) { - self$lower = assert_number(lower) - self$upper = assert_number(upper) - self$tolerance = assert_number(tolerance, lower = 0) - assert_true(lower <= upper) - super$initialize(id, special_vals = special_vals, default = default, tags = tags) - }, +#' @export +domain_check.ParamDbl = function(param, values) { + lower = param$lower - param$tolerance * pmax(1, abs(param$lower)) + upper = param$upper + param$tolerance * pmax(1, abs(param$upper)) + if (qtestr(values, "N1")) { + values_num = as.numeric(values) + if (all(values_num >= lower) && all(values_num <= upper)) return(TRUE) + } + check_domain_vectorize(param$id, values, check_number, more_args = list(lower = lower, upper = upper)) +} - #' @description - #' Restrict the value to within the allowed range. This works - #' in conjunction with `$tolerance`, which accepts values - #' slightly out of this range. - #' - #' @param x (`numeric(1)`)\cr - #' Value to convert. - convert = function(x) { - min(max(x, self$lower), self$upper) - } - ), +#' @export +domain_sanitize.ParamDbl = function(param, values) { + values = as.numeric(values) + values[values < param$lower] = param$lower + values[values > param$upper] = param$upper + as.list(values) +} - active = list( - #' @template field_levels - levels = function() NULL, - #' @template field_nlevels - nlevels = function() Inf, - #' @template field_is_bounded - is_bounded = function() is.finite(self$lower) && is.finite(self$upper), - #' @template field_storage_type - storage_type = function() "numeric" - ), +#' @export +domain_nlevels.ParamDbl = function(param) ifelse(param$upper == param$lower, 1, Inf) +#' @export +domain_is_bounded.ParamDbl = function(param) is.finite(param$lower) & is.finite(param$upper) +#' @export +domain_qunif.ParamDbl = function(param, x) { + pmax(pmin(x * param$upper - (x-1) * param$lower, param$upper), param$lower) # extra careful here w/ rounding errors +} - private = list( - .check = function(x) { - # Accept numbers between lower and upper bound, with tolerance self$tolerance - # Tolerance is both absolute & relative tolerance (if either tolerance is - # undercut the value is accepted: - # Values that go beyond the bound by less than `self$tolerance` are also - # accepted (absolute tolerance) - # Values that go beyond the bound by less than `abs() * self$tolerance` - # are also accepted (relative tolerance) - checkNumber(x, - lower = self$lower - self$tolerance * max(1, abs(self$lower)), - upper = self$upper + self$tolerance * max(1, abs(self$upper)) - ) - }, - .qunif = function(x) x * self$upper - (x-1) * self$lower - ) -) +#' @export +domain_is_number.ParamDbl = function(param) TRUE +#' @export +domain_is_categ.ParamDbl = function(param) FALSE diff --git a/R/ParamFct.R b/R/ParamFct.R index e703e732..cad930db 100644 --- a/R/ParamFct.R +++ b/R/ParamFct.R @@ -1,56 +1,51 @@ -#' @title Factor Parameter -#' -#' @description -#' A [Param] to describe categorical (factor) parameters. -#' -#' @template param_id -#' @template param_levels -#' @template param_special_vals -#' @template param_default -#' @template param_tags -#' -#' @family Params -#' @include Param.R +#' @rdname Domain #' @export -#' @examples -#' ParamFct$new("f", levels = letters[1:3]) -ParamFct = R6Class("ParamFct", inherit = Param, - public = list( - - #' @template field_levels - levels = NULL, - - #' @description - #' Creates a new instance of this [R6][R6::R6Class] class. - #' - #' @param levels (`character()`)\cr - #' Set of allowed levels. - initialize = function(id, levels, special_vals = list(), default = NO_DEF, tags = character()) { - assert_character(levels, any.missing = FALSE, unique = TRUE) - self$levels = levels - super$initialize(id, special_vals = special_vals, default = default, tags = tags) +p_fct = function(levels, special_vals = list(), default = NO_DEF, tags = character(), depends = NULL, trafo = NULL, init) { + constargs = as.list(match.call()[-1]) + levels = eval.parent(constargs$levels) + if (!is.character(levels)) { + # if the "levels" argument is not a character vector, then + # we add a trafo. + assert(check_atomic_vector(levels), check_list(levels)) + if (is.null(names(levels))) { + names(levels) = as.character(levels) } - ), + trafo = crate(function(x) { + x = levels[[x]] + if (!is.null(trafo)) x = trafo(x) + x + }, trafo, levels) + real_levels = names(levels) + } else { + real_levels = levels + } + # group p_fct by levels, so the group can be checked in a vectorized fashion. + # We escape '"' and '\' to '\"' and '\\', respectively. + grouping = str_collapse(gsub("([\\\\\"])", "\\\\\\1", sort(real_levels)), quote = '"', sep = ",") + Domain(cls = "ParamFct", grouping = grouping, levels = real_levels, special_vals = special_vals, default = default, tags = tags, trafo = trafo, storage_type = "character", depends_expr = substitute(depends), init = init) +} - active = list( - #' @template field_lower - lower = function() NA_real_, - #' @template field_upper - upper = function() NA_real_, - #' @template field_nlevels - nlevels = function() length(self$levels), - #' @template field_is_bounded - is_bounded = function() TRUE, - #' @template field_storage_type - storage_type = function() "character" - ), +#' @export +domain_check.ParamFct = function(param, values) { + if (qtestr(values, "S1")) { + values_str = as.character(values) + if (all(values_str %in% param$levels[[1]])) return(TRUE) # this works because we have the grouping -- all 'levels' are the same here. + } + check_domain_vectorize(param$id, values, check_choice, more_args = list(choices = param$levels)) +} - private = list( - .check = function(x) check_choice(x, choices = self$levels), +#' @export +domain_nlevels.ParamFct = function(param) map_dbl(param$levels, length) +#' @export +domain_is_bounded.ParamFct = function(param) rep(TRUE, nrow(param)) +#' @export +domain_qunif.ParamFct = function(param, x) { + nlevels = domain_nlevels(param) + z = pmin(floor(x * nlevels) + 1, nlevels) # make sure we dont map to upper+1 + as.character(pmap(list(param$levels, z), `[[`)) +} - .qunif = function(x) { - z = floor(x * self$nlevels * (1 - 1e-16)) + 1 # make sure we dont map to upper+1 - self$levels[z] - } - ) -) +#' @export +domain_is_number.ParamFct = function(param) FALSE +#' @export +domain_is_categ.ParamFct = function(param) TRUE diff --git a/R/ParamInt.R b/R/ParamInt.R index 6dcabdcc..495d4d86 100644 --- a/R/ParamInt.R +++ b/R/ParamInt.R @@ -1,70 +1,74 @@ -#' @title Integer Parameter -#' -#' @description -#' A [Param] to describe integer parameters. -#' -#' @template param_id -#' @template param_lower -#' @template param_upper -#' @template param_special_vals -#' @template param_default -#' @template param_tags -#' -#' @section Methods: -#' See [Param]. -#' -#' @family Params -#' @include Param.R + +#' @rdname Domain #' @export -#' @examples -#' ParamInt$new("count", lower = 0, upper = 10, default = 1) -ParamInt = R6Class("ParamInt", inherit = Param, - public = list( - #' @template field_lower - lower = NULL, +p_int = function(lower = -Inf, upper = Inf, special_vals = list(), default = NO_DEF, tags = character(), tolerance = sqrt(.Machine$double.eps), depends = NULL, trafo = NULL, logscale = FALSE, init) { + assert_number(tolerance, lower = 0, upper = 0.5) + # assert_int will stop for `Inf` values, which we explicitly allow as lower / upper bound + if (!isTRUE(is.infinite(lower))) assert_int(lower, tol = 1e-300) else assert_number(lower) + if (!isTRUE(is.infinite(upper))) assert_int(upper, tol = 1e-300) else assert_number(upper) + assert_true(lower <= upper) + if (assert_flag(logscale)) { + if (!is.null(trafo)) stop("When a trafo is given then logscale must be FALSE") + if (lower < 0) stop("When logscale is TRUE then lower bound must be greater or equal 0") + trafo = crate(function(x) as.integer(max(min(exp(x), upper), lower)), lower, upper) + # at this point we don't want to overwrite 'lower' and 'upper, since they get used for the representation + real_lower = log(max(lower, 0.5)) + real_upper = log(upper + 1) + cls = "ParamDbl" + storage_type = "numeric" + } else { + cls = "ParamInt" + storage_type = "integer" + real_lower = lower + real_upper = upper + } + + Domain(cls = cls, grouping = cls, lower = real_lower, upper = real_upper, special_vals = special_vals, default = default, tags = tags, tolerance = tolerance, trafo = trafo, + storage_type = storage_type, + depends_expr = substitute(depends), init = init, cargo = if (logscale) "logscale") +} - #' @template field_upper - upper = NULL, +#' @export +domain_check.ParamInt = function(param, values) { + if (!qtestr(values, "N1()")) { + return(check_domain_vectorize(param$id, values, check_int, + more_args = list(lower = param$lower - 0.5, upper = param$upper + 0.5, # be lenient with bounds, because they would refer to the rounded values + tol = .51) # we don't know the tolerances of individual values, but we do know that some values are not even (non-missing, finite) numerics + )) + } - #' @description - #' Creates a new instance of this [R6][R6::R6Class] class. - initialize = function(id, lower = -Inf, upper = Inf, special_vals = list(), default = NO_DEF, tags = character()) { - if (isTRUE(is.infinite(lower))) { - self$lower = lower - } else { - self$lower = assert_int(lower) - } - if (isTRUE(is.infinite(upper))) { - self$upper = upper - } else { - self$upper = assert_int(upper) - } - assert_true(lower <= upper) - super$initialize(id, special_vals = special_vals, default = default, tags = tags) - }, + values_num = as.numeric(values) - #' @description - #' Converts a value to an integer. - #' @param x (`numeric(1)`)\cr - #' Value to convert. - convert = function(x) { - as.integer(x) + if (all(abs(trunc(values_num + 0.5) - 0.5) <= param$tolerance)) { + values_num = round(values_num) + if (all(values_num >= param$lower) && all(values_num <= param$upper)) { + return(TRUE) } - ), - - active = list( - #' @template field_levels - levels = function() NULL, - #' @template field_nlevels - nlevels = function() (self$upper - self$lower) + 1L, - #' @template field_is_bounded - is_bounded = function() is.finite(self$lower) && is.finite(self$upper), - #' @template field_storage_type - storage_type = function() "integer" - ), + } - private = list( - .check = function(x) checkInt(x, lower = self$lower, upper = self$upper, tol = 1e-300), - .qunif = function(x) as.integer(floor(x * self$nlevels * (1 - 1e-16)) + self$lower) # make sure we dont map to upper+1 + check_domain_vectorize(param$id, values_num, check_int, + more_args = list(lower = param$lower - 0.5, upper = param$upper + 0.5, # be lenient with bounds, because they would refer to the rounded values + tol = pmax(1e-300, param$tolerance + 2 * abs(values_num) * .Machine$double.eps)) # want to have inclusive tolerance bounds. Not sure if 2* is necessary. ) -) +} + +#' @export +domain_sanitize.ParamInt = function(param, values) { + as.list(as.integer(as.numeric(values) + 0.5)) +} + +#' @export +domain_nlevels.ParamInt = function(param) (param$upper - param$lower) + 1 +#' @export +domain_is_bounded.ParamInt = function(param) is.finite(param$lower) & is.finite(param$upper) +#' @export +domain_qunif.ParamInt = function(param, x) { + # extra careful here w/ rounding errors and the x == 1 case + # note that as.integer alone rounds towards 0 and can not be used without 'floor' here + as.integer(floor(pmax(pmin(x * (param$upper + 1) - (x - 1) * param$lower, param$upper), param$lower))) +} + +#' @export +domain_is_number.ParamInt = function(param) TRUE +#' @export +domain_is_categ.ParamInt = function(param) FALSE diff --git a/R/ParamLgl.R b/R/ParamLgl.R index 7052165b..123fe73b 100644 --- a/R/ParamLgl.R +++ b/R/ParamLgl.R @@ -1,44 +1,28 @@ -#' @title Logical Parameter -#' -#' @description -#' A [Param] to describe logical parameters. -#' -#' @template param_id -#' @template param_special_vals -#' @template param_default -#' @template param_tags -#' -#' @family Params -#' @include Param.R +#' @rdname Domain #' @export -#' @examples -#' ParamLgl$new("flag", default = TRUE) -ParamLgl = R6Class("ParamLgl", inherit = Param, - public = list( - #' @description - #' Creates a new instance of this [R6][R6::R6Class] class. - initialize = function(id, special_vals = list(), default = NO_DEF, tags = character()) { - super$initialize(id, special_vals = special_vals, default = default, tags = tags) - } - ), +p_lgl = function(special_vals = list(), default = NO_DEF, tags = character(), depends = NULL, trafo = NULL, init) { + Domain(cls = "ParamLgl", grouping = "ParamLgl", levels = c(TRUE, FALSE), special_vals = special_vals, default = default, + tags = tags, trafo = trafo, storage_type = "logical", depends_expr = substitute(depends), init = init) +} - active = list( - #' @template field_lower - lower = function() NA_real_, - #' @template field_upper - upper = function() NA_real_, - #' @template field_levels - levels = function() c(TRUE, FALSE), - #' @template field_nlevels - nlevels = function() 2L, - #' @template field_is_bounded - is_bounded = function() TRUE, - #' @template field_storage_type - storage_type = function() "logical" - ), +#' @export +domain_check.ParamLgl = function(param, values) { + if (qtestr(values, "B1")) { + return(TRUE) + } + check_domain_vectorize(param$id, values, check_flag) +} - private = list( - .check = function(x) check_flag(x), - .qunif = function(x) x < 0.5 - ) -) +#' @export +domain_nlevels.ParamLgl = function(param) rep(2, nrow(param)) +#' @export +domain_is_bounded.ParamLgl = function(param) rep(TRUE, nrow(param)) +#' @export +domain_qunif.ParamLgl = function(param, x) { + x < 0.5 +} + +#' @export +domain_is_number.ParamLgl = function(param) FALSE +#' @export +domain_is_categ.ParamLgl = function(param) TRUE diff --git a/R/ParamSet.R b/R/ParamSet.R index e730d3f4..e389c211 100644 --- a/R/ParamSet.R +++ b/R/ParamSet.R @@ -1,41 +1,52 @@ #' @title ParamSet #' #' @description -#' A set of [Param] objects. -#' Please note that when creating a set or adding to it, the parameters of the -#' resulting set have to be uniquely named with IDs with valid R names. -#' The set also contains a member variable `values` which can be used to store an active configuration / -#' or to partially fix -#' some parameters to constant values (regarding subsequent sampling or generation of designs). +#' An object representing the space of possible parametrizations of a function or another object. +#' `ParamSet`s are used on the side of objects being parameterized, where they function as a configuration space determining the set of possible configurations accepted by these objects. +#' They can also be used to specify search spaces for optimization, indicating the set of legal configurations to try out. +#' It is often convenient to generate search spaces from configuration spaces, which can be done using the `$search_space()` method in combination with `to_tune()` / [`TuneToken`] objects. +#' +#' Individual dimensions of a `ParamSet` are specified by [`Domain`] objects, created as [`p_dbl()`], [`p_lgl()`] etc. +#' The field `$values` can be used to store an active configuration or to partially fix +#' some parameters to constant values -- the precise effect can be determined by the object being parameterized. +#' +#' Constructing a `ParamSet` can be done using `ParamSet$new()` in combination with a named list of [`Domain`] objects. +#' This route is recommended when the set of dimensions (i.e. the members of this named list) is dynamically created, such as when the number of parameters is variable. +#' `ParamSet`s can also be created using the [`ps()`] shorthand, which is the recommended way when the set of parameters is fixed. +#' In practice, the majority of cases where a `ParamSet` is created, the [`ps()`] should be used. #' #' @section S3 methods and type converters: #' * `as.data.table()`\cr -#' [ParamSet] -> [data.table::data.table()]\cr +#' `ParamSet` -> [data.table::data.table()]\cr #' Compact representation as datatable. Col types are:\cr #' - id: character -#' - lower, upper: double +#' - class: character +#' - lower, upper: numeric #' - levels: list col, with NULL elements -#' - special_vals: list col of list +#' - nlevels: integer valued numeric #' - is_bounded: logical -#' - default: list col, with NULL elements +#' - special_vals: list col of list +#' - default: list col #' - storage_type: character #' - tags: list col of character vectors #' @examples -#' ps = ParamSet$new( +#' pset = ParamSet$new( #' params = list( -#' ParamDbl$new("d", lower = -5, upper = 5, default = 0), -#' ParamFct$new("f", levels = letters[1:3]) +#' d = p_dbl(lower = -5, upper = 5, default = 0, trafo = function(x) 2^x), +#' f = p_fct(levels = letters[1:3]) #' ) #' ) #' -#' ps$trafo = function(x, param_set) { -#' x$d = 2^x$d -#' return(x) -#' } +#' # alternative, recommended way of construction in this case since the +#' # parameter list is not dynamic: +#' pset = ps( +#' d = p_dbl(lower = -5, upper = 5, default = 0, trafo = function(x) 2^x), +#' f = p_fct(levels = letters[1:3]) +#' ) #' -#' ps$add(ParamInt$new("i", lower = 0L, upper = 16L)) +#' pset$check(list(d = 2.1, f = "a")) #' -#' ps$check(list(d = 2.1, f = "a", i = 3L)) +#' pset$check(list(d = 2.1, f = "d")) #' @export ParamSet = R6Class("ParamSet", public = list( @@ -48,45 +59,57 @@ ParamSet = R6Class("ParamSet", #' @description #' Creates a new instance of this [R6][R6::R6Class] class. #' - #' @param params (`list()`)\cr - #' List of [Param], named with their respective ID. - #' Parameters are cloned. - initialize = function(params = named_list()) { - assert_list(params, types = "Param") - ids = map_chr(params, "id") - assert_names(ids, type = "strict") - private$.params = set_names(map(params, function(p) p$clone(deep = TRUE)), ids) - self$set_id = "" - }, - - #' @description - #' Adds a single param or another set to this set, all params are cloned. - #' - #' @param p ([Param] | [ParamSet]). - add = function(p) { - - assert_multi_class(p, c("Param", "ParamSet")) - p = if (inherits(p, "Param")) { # level-up param to set - ParamSet$new(list(p)) + #' @param params (named `list()`)\cr + #' List of [`Domain`], named with their respective ID. + #' @param allow_dangling_dependencies (`character(1)`)\cr + #' Whether dependencies depending on parameters that are not present should be allowed. A parameter `x` having + #' `depends = y == 0` if `y` is not present would usually throw an error, but if dangling + #' dependencies are allowed, the dependency is added regardless. This is mainly for internal + #' use. + initialize = function(params = named_list(), allow_dangling_dependencies = FALSE) { + assert_list(params, types = "Domain") + + if (length(params)) assert_names(names(params), type = "strict") + + if (!length(params)) { + paramtbl = copy(empty_domain) } else { - p$clone(deep = TRUE) + paramtbl = rbindlist(params) + set(paramtbl, , "id", names(params)) + if (".tags" %in% colnames(paramtbl)) { + private$.tags = paramtbl[, .(tag = unlist(.tags)), keyby = "id"] + setindexv(private$.tags, "tag") + } } - pparams = p$params - npparams = names(pparams) - assert_names(npparams, type = "strict", .var.name = "Names of params") - ii = wf(npparams %in% names(private$.params)) - if (length(ii)) { - stopf("Cannot add param with name '%s': duplicated name", npparams) + # get initvalues here, so we can delete the relevant column. + # we only assign it later, so checks can run normally. + initvalues = if (".init" %in% names(paramtbl)) with(paramtbl[(.init_given), .(.init, id)], set_names(.init, id)) + + if (".trafo" %in% names(paramtbl)) { + private$.trafos = setkeyv(paramtbl[!map_lgl(.trafo, is.null), .(id, trafo = .trafo)], "id") } - if (!is.null(p$trafo)) { - stop("Cannot add a param set with a trafo.") + if (".requirements" %in% names(paramtbl)) { + requirements = paramtbl$.requirements + private$.params = paramtbl # self$add_dep needs this + for (row in seq_len(nrow(paramtbl))) { + for (req in requirements[[row]]) { + invoke(self$add_dep, id = paramtbl$id[[row]], allow_dangling_dependencies = allow_dangling_dependencies, + .args = req) + } + } } - private$.params = insert_named(private$.params, pparams) - private$.values = insert_named(private$.values, p$values) - private$.deps = rbind(private$.deps, p$deps) - invisible(self) + + delendum_cols = setdiff(colnames(paramtbl), domain_names_permanent) + if (length(delendum_cols)) set(paramtbl, , delendum_cols, NULL) + assert_names(colnames(paramtbl), identical.to = domain_names_permanent) + + setindexv(paramtbl, c("id", "cls", "grouping")) + + private$.params = paramtbl # I am 99% sure this is not necessary, but maybe set() creates a copy when deleting too many cols? + + if (!is.null(initvalues)) self$values = initvalues }, #' @description @@ -94,36 +117,31 @@ ParamSet = R6Class("ParamSet", #' selections, `NULL` means no restriction. #' Only returns IDs of parameters that satisfy all conditions. #' - #' @param class (`character()`). - #' @param is_bounded (`logical(1)`). + #' @param class (`character()`)\cr + #' Typically a subset of `"ParamDbl"`, `"ParamInt"`, `"ParamFct"`, `"ParamLgl"`, `"ParamUty"`. + #' Other classes are possible if implemented by 3rd party packages. + #' Return only IDs of dimensions with the given class. #' @param tags (`character()`). + #' Return only IDs of dimensions that have *all* tags given in this argument. + #' @param any_tags (`character()`). + #' Return only IDs of dimensions that have at least one of the tags given in this argument. #' @return `character()`. - ids = function(class = NULL, is_bounded = NULL, tags = NULL) { + ids = function(class = NULL, tags = NULL, any_tags = NULL) { assert_character(class, any.missing = FALSE, null.ok = TRUE) - assert_flag(is_bounded, null.ok = TRUE) assert_character(tags, any.missing = FALSE, null.ok = TRUE) + assert_character(any_tags, any.missing = FALSE, null.ok = TRUE) - params = self$params_unid - ids = names(params) - if (is.null(class) && is.null(is_bounded) && is.null(tags)) { - return(ids) - } - - ii = rep(TRUE, length(ids)) - - if (!is.null(class)) { - ii = ii & map_chr(params, "class") %in% class - } - - if (!is.null(is_bounded)) { - ii = ii & map_lgl(params, "is_bounded") + if (is.null(class) && is.null(tags) && is.null(any_tags)) { + return(private$.params$id) } - - if (!is.null(tags)) { - ii = ii & map_lgl(params, function(p) all(tags %in% p$tags)) + ptbl = if (is.null(class)) private$.params else private$.params[cls %in% class, .(id)] + if (is.null(tags) && is.null(any_tags)) { + return(ptbl$id) } - - ids[ii] + tagtbl = private$.tags[ptbl, nomatch = 0] + idpool = if (is.null(any_tags)) list() else list(tagtbl[tag %in% any_tags, id]) + idpool = c(idpool, lapply(tags, function(t) tagtbl[t, id, on = "tag", nomatch = 0])) + Reduce(intersect, idpool) }, #' @description @@ -131,20 +149,24 @@ ParamSet = R6Class("ParamSet", #' restriction and is equivalent to `$values`. #' Only returns values of parameters that satisfy all conditions. #' - #' @param class (`character()`). - #' @param is_bounded (`logical(1)`). - #' @param tags (`character()`). + #' @param class (`character()`). See `$ids()`. + #' @param tags (`character()`). See `$ids()`. + #' @param any_tags (`character()`). See `$ids()`. #' @param type (`character(1)`)\cr - #' Return values `with_token`, `without_token` or `only_token`? + #' Return values `"with_token"` (i.e. all values), + # `"without_token"` (all values that are not [`TuneToken`] objects) or `"only_token"` (only [`TuneToken`] objects)? #' @param check_required (`logical(1)`)\cr - #' Check if all required parameters are set? + #' Check if all required parameters are set? + #' @param remove_dependencies (`logical(1)`)\cr + #' If `TRUE`, set values with dependencies that are not fulfilled to `NULL`. #' @return Named `list()`. - get_values = function(class = NULL, is_bounded = NULL, tags = NULL, - type = "with_token", check_required = TRUE) { + get_values = function(class = NULL, tags = NULL, any_tags = NULL, + type = "with_token", check_required = TRUE, remove_dependencies = TRUE) { assert_choice(type, c("with_token", "without_token", "only_token")) + assert_flag(check_required) + values = self$values - params = self$params_unid ns = names(values) if (type == "without_token") { @@ -153,15 +175,28 @@ ParamSet = R6Class("ParamSet", values = keep(values, is, "TuneToken") } - if(check_required) { - required = setdiff(names(keep(params, function(p) "required" %in% p$tags)), ns) + if (check_required) { + required = setdiff(self$ids(tags = "required"), ns) if (length(required) > 0L) { stop(sprintf("Missing required parameters: %s", str_collapse(required))) } } - values[intersect(names(values), self$ids(class = class, is_bounded = is_bounded, tags = tags))] + deps = self$deps + if (remove_dependencies && nrow(deps)) { + for (j in seq_row(deps)) { + p1id = deps$id[[j]] + p2id = deps$on[[j]] + cond = deps$cond[[j]] + if (p1id %in% ns && !inherits(values[[p2id]], "TuneToken") && !isTRUE(condition_test(cond, values[[p2id]]))) { + values[p1id] = NULL + } + } + } + + values[match(self$ids(class = class, tags = tags, any_tags = any_tags), names(values), nomatch = 0)] }, + #' @description #' Allows to to modify (and overwrite) or replace the parameter values. #' Per default already set values are being kept unless new values are being provided. @@ -181,49 +216,76 @@ ParamSet = R6Class("ParamSet", assert_disjunct(names(dots), names(.values)) new_values = insert_named(dots, .values) if (.insert) { + discarding = names(keep(new_values, is.null)) new_values = insert_named(self$values, new_values) + new_values = new_values[names(new_values) %nin% discarding] } - self$values = discard(new_values, function(x) is.null(x)) + self$values = new_values invisible(self) }, #' @description - #' Changes the current set to the set of passed IDs. - #' - #' @param ids (`character()`). - subset = function(ids) { - param_ids = names(self$params_unid) - assert_subset(ids, param_ids) - deps = self$deps - if (nrow(deps)) { # check that all required / leftover parents are still in new ids - parents = unique(deps[get("id") %in% ids, "on"][[1L]]) - pids_not_there = setdiff(parents, ids) - if (length(pids_not_there) > 0L) { - stopf(paste0("Subsetting so that dependencies on params exist which would be gone: %s.", - "\nIf you still want to do that, manipulate '$deps' yourself."), str_collapse(pids_not_there)) + #' Perform transformation specified by the `trafo` of [`Domain`] objects, as well as the `$extra_trafo` field. + #' @param x (named `list()` | `data.frame`)\cr + #' The value(s) to be transformed. + #' @param param_set (`ParamSet`)\cr + #' Passed to `extra_trafo()`. Note that the `extra_trafo` of `self` is used, not the `extra_trafo` of the + #' `ParamSet` given in the `param_set` argument. + #' In almost all cases, the default `param_set = self` should be used. + trafo = function(x, param_set = self) { + if (is.data.frame(x)) x = as.list(x) + assert_list(x, names = "unique") + trafos = private$.trafos[names(x), .(id, trafo), nomatch = 0] + trafos[, value := x[id]] + if (nrow(trafos)) { + transformed = pmap(trafos, function(id, trafo, value) trafo(value)) + x = insert_named(x, set_names(transformed, trafos$id)) + } + extra_trafo = self$extra_trafo + if (!is.null(extra_trafo)) { + # need to give the input of extra_trafo a different name than the output; otherwise the user would have to + # "force()" the x-argument of extra_trafo. + xin = x + if (test_function(extra_trafo, args = c("x", "param_set"))) { + x = extra_trafo(x = xin, param_set = param_set) + } else { + x = extra_trafo(xin) } } - private$.params = private$.params[ids] - # restrict to ids already in pvals - ids2 = union(intersect(ids, names(private$.values)), setdiff(names(private$.values), param_ids)) - private$.values = private$.values[ids2] - invisible(self) + x }, #' @description - #' Construct a [`ParamSet`] to tune over. Constructed from [`TuneToken`] in `$values`, see [`to_tune()`]. - #' - #' @param values (`named list`): optional named list of [`TuneToken`] objects to convert, in place of `$values`. - search_space = function(values = self$values) { - assert_list(values) - assert_names(names(values), subset.of = self$ids()) - pars = private$get_tune_ps(values) - on = NULL # pacify static code check - dangling_deps = pars$deps[!on %in% pars$ids()] - if (nrow(dangling_deps)) { - stopf("Dangling dependencies not allowed: Dependencies on %s dangling", str_collapse(dangling_deps$on)) - } - pars + #' \pkg{checkmate}-like test-function. Takes a named list. + #' Return `FALSE` if the given `$constraint` is not satisfied, `TRUE` otherwise. + #' Note this is different from satisfying the bounds or types given by the `ParamSet` itself: + #' If `x` does not satisfy these, an error will be thrown, given that `assert_value` is `TRUE`. + #' @param x (named `list()`)\cr + #' The value to test. + #' @param assert_value (`logical(1)`)\cr + #' Whether to verify that `x` satisfies the bounds and types given by this `ParamSet`. + #' Should be `TRUE` unless this was already checked before. + #' @return `logical(1)`: Whether `x` satisfies the `$constraint`. + test_constraint = function(x, assert_value = TRUE) { + if (assert_value) self$assert(x, check_strict = FALSE) + assert_flag(is.null(private$.constraint) || private$.constraint(x)) + }, + + #' @description + #' \pkg{checkmate}-like test-function. Takes a [`data.table`]. + #' For each row, return `FALSE` if the given `$constraint` is not satisfied, `TRUE` otherwise. + #' Note this is different from satisfying the bounds or types given by the `ParamSet` itself: + #' If `x` does not satisfy these, an error will be thrown, given that `assert_value` is `TRUE`. + #' @param x (`data.table`)\cr + #' The values to test. + #' @param assert_value (`logical(1)`)\cr + #' Whether to verify that `x` satisfies the bounds and types given by this `ParamSet`. + #' Should be `TRUE` unless this was already checked before. + #' @return `logical`: For each row in `x`, whether it satisfies the `$constraint`. + test_constraint_dt = function(x, assert_value = TRUE) { + assert_data_table(x) + if (assert_value) self$assert_dt(x, check_strict = FALSE) + map_lgl(transpose(x), self$test_constraint, assert_value = FALSE) }, #' @description @@ -231,64 +293,96 @@ ParamSet = R6Class("ParamSet", #' A point x is feasible, if it configures a subset of params, #' all individual param constraints are satisfied and all dependencies are satisfied. #' Params for which dependencies are not satisfied should not be part of `x`. + #' Constraints and dependencies are not checked when `check_strict` is `FALSE`. #' #' @param xs (named `list()`). - #' @return If successful `TRUE`, if not a string with the error message. - check = function(xs) { - + #' @param check_strict (`logical(1)`)\cr + #' Whether to check that constraints and dependencies are satisfied. + #' @return If successful `TRUE`, if not a string with an error message. + check = function(xs, check_strict = TRUE) { + assert_flag(check_strict) ok = check_list(xs, names = "unique") if (!isTRUE(ok)) { return(ok) } - params = self$params_unid + + params = private$.params ns = names(xs) - ids = names(params) + ids = private$.params$id extra = wf(ns %nin% ids) if (length(extra)) { return(sprintf("Parameter '%s' not available.%s", ns[extra], did_you_mean(extra, ids))) } - # check each parameters feasibility - for (n in ns) { - ch = params[[n]]$check(xs[[n]]) - if (test_string(ch)) { # we failed a check, return string - return(paste0(n, ": ", ch)) - } + if (length(xs) && test_list(xs, types = "TuneToken")) { + tunecheck = tryCatch({ + private$get_tune_ps(xs) + TRUE + }, error = function(e) paste("tune token invalid:", conditionMessage(e))) + if (!isTRUE(tunecheck)) return(tunecheck) } - # check dependencies - deps = self$deps - if (nrow(deps)) { - for (j in seq_row(deps)) { + # check each parameter group's feasibility + xs_nontune = discard(xs, inherits, "TuneToken") - p1id = deps$id[j] - p2id = deps$on[j] - if (inherits(xs[[p1id]], "TuneToken") || inherits(xs[[p2id]], "TuneToken")) { - next # be lenient with dependencies when any parameter involved is a TuneToken - } - # we are ONLY ok if: - # - if param is there, then parent must be there, then cond must be true - # - if param is not there - cond = deps$cond[[j]] - ok = (p1id %in% ns && p2id %in% ns && cond$test(xs[[p2id]])) || - (p1id %nin% ns) - if (isFALSE(ok)) { - message = sprintf("The parameter '%s' can only be set if the following condition is met '%s'.", - p1id, cond$as_string(p2id)) - val = xs[[p2id]] - if (is.null(val)) { - message = sprintf(paste("%s Instead the parameter value for '%s' is not set at all.", - "Try setting '%s' to a value that satisfies the condition"), message, p2id, p2id) - } else { - message = sprintf("%s Instead the current parameter value is: %s=%s", message, p2id, val) - } - return(message) - } - } + # need to make sure we index w/ empty character instead of NULL + params = params[names(xs_nontune) %??% character(0), on = "id"] + + set(params, , "values", list(xs_nontune)) + pgroups = split(params, by = c("cls", "grouping")) + checkresults = map(pgroups, function(x) { + domain_check(set_class(x, c(x$cls[[1]], "Domain", class(x))), x$values) + }) + checkresults = discard(checkresults, isTRUE) + if (length(checkresults)) { + return(str_collapse(checkresults, sep = "\n")) + } + + if (check_strict) { + ## required = setdiff(self$ids(tags = "required"), ns) + ## if (length(required) > 0L) { + ## return(sprintf("Missing required parameters: %s", str_collapse(required))) + ## } + if (!self$test_constraint(xs, assert_value = FALSE)) return(sprintf("Constraint not fulfilled.")) + return(self$check_dependencies(xs)) } - return(TRUE) # we passed all checks + TRUE # we passed all checks + }, + + #' @description + #' \pkg{checkmate}-like check-function. Takes a named list. + #' Checks that all individual param dependencies are satisfied. + #' + #' @param xs (named `list()`). + #' @return If successful `TRUE`, if not a string with an error message. + check_dependencies = function(xs) { + deps = self$deps + if (!nrow(deps)) return(TRUE) + params = private$.params + ns = names(xs) + errors = pmap(deps[id %in% ns], function(id, on, cond) { + onval = xs[[on]] + if (inherits(xs[[id]], "TuneToken") || inherits(onval, "TuneToken")) return(NULL) + + # we are ONLY ok if: + # - if 'id' is there, then 'on' must be there, and cond must be true + # - if 'id' is not there. but that is skipped (deps[id %in% ns] filter) + if (on %in% ns && condition_test(cond, onval)) return(NULL) + msg = sprintf("%s: can only be set if the following condition is met '%s'.", + id, condition_as_string(cond, on)) + if (is.null(onval)) { + msg = sprintf(paste("%s Instead the parameter value for '%s' is not set at all.", + "Try setting '%s' to a value that satisfies the condition"), msg, on, on) + } else { + msg = sprintf("%s Instead the current parameter value is: %s == %s", msg, on, as_short_string(onval)) + } + msg + }) + errors = unlist(errors) + if (!length(errors)) return(TRUE) + str_collapse(errors, sep = "\n") }, #' @description @@ -296,80 +390,230 @@ ParamSet = R6Class("ParamSet", #' A point x is feasible, if it configures a subset of params, #' all individual param constraints are satisfied and all dependencies are satisfied. #' Params for which dependencies are not satisfied should not be part of `x`. + #' Constraints and dependencies are not checked when `check_strict` is `FALSE`. #' #' @param xs (named `list()`). + #' @param check_strict (`logical(1)`)\cr + #' Whether to check that constraints and dependencies are satisfied. #' @return If successful `TRUE`, if not `FALSE`. - test = function(xs) makeTest(res = self$check(xs)), + test = function(xs, check_strict = TRUE) makeTest(self$check(xs, check_strict = check_strict)), #' @description #' \pkg{checkmate}-like assert-function. Takes a named list. #' A point x is feasible, if it configures a subset of params, #' all individual param constraints are satisfied and all dependencies are satisfied. #' Params for which dependencies are not satisfied should not be part of `x`. + #' Constraints and dependencies are not checked when `check_strict` is `FALSE`. #' #' @param xs (named `list()`). + #' @param check_strict (`logical(1)`)\cr + #' Whether to check that constraints and dependencies are satisfied. #' @param .var.name (`character(1)`)\cr #' Name of the checked object to print in error messages.\cr #' Defaults to the heuristic implemented in [vname][checkmate::vname]. #' @return If successful `xs` invisibly, if not an error message. - assert = function(xs, .var.name = vname(xs)) makeAssertion(xs, self$check(xs), .var.name, NULL), # nolint + assert = function(xs, check_strict = TRUE, .var.name = vname(xs)) makeAssertion(xs, self$check(xs, check_strict = check_strict), .var.name, NULL), # nolint #' @description #' \pkg{checkmate}-like check-function. Takes a [data.table::data.table] - #' where rows are points and columns are parameters. A point x is feasible, - #' if it configures a subset of params, all individual param constraints are - #' satisfied and all dependencies are satisfied. Params for which - #' dependencies are not satisfied should be set to `NA` in `xdt`. + #' where rows are points and columns are parameters. + #' A point x is feasible, if it configures a subset of params, + #' all individual param constraints are satisfied and all dependencies are satisfied. + #' Params for which dependencies are not satisfied should not be part of `x`. + #' Constraints and dependencies are not checked when `check_strict` is `FALSE`. #' #' @param xdt ([data.table::data.table] | `data.frame()`). + #' @param check_strict (`logical(1)`)\cr + #' Whether to check that constraints and dependencies are satisfied. #' @return If successful `TRUE`, if not a string with the error message. - check_dt = function(xdt) { + check_dt = function(xdt, check_strict = TRUE) { xss = map(transpose_list(xdt), discard, is.na) - for (xs in xss) { - ok = self$check(xs) + msgs = list() + for (i in seq_along(xss)) { + xs = xss[[i]] + ok = self$check(xs, check_strict = check_strict) if (!isTRUE(ok)) { return(ok) } } - - return(TRUE) + TRUE }, #' @description #' \pkg{checkmate}-like test-function (s. `$check_dt()`). #' #' @param xdt ([data.table::data.table]). + #' @param check_strict (`logical(1)`)\cr + #' Whether to check that constraints and dependencies are satisfied. #' @return If successful `TRUE`, if not `FALSE`. - test_dt = function(xdt) makeTest(res = self$check_dt(xdt)), + test_dt = function(xdt, check_strict = TRUE) makeTest(res = self$check_dt(xdt, check_strict = check_strict)), #' @description #' \pkg{checkmate}-like assert-function (s. `$check_dt()`). #' #' @param xdt ([data.table::data.table]). + #' @param check_strict (`logical(1)`)\cr + #' Whether to check that constraints and dependencies are satisfied. #' @param .var.name (`character(1)`)\cr #' Name of the checked object to print in error messages.\cr #' Defaults to the heuristic implemented in [vname][checkmate::vname]. - #' @return If successful `xs` invisibly, if not an error message. - assert_dt = function(xdt, .var.name = vname(xdt)) makeAssertion(xdt, self$check_dt(xdt), .var.name, NULL), # nolint + #' @return If successful `xs` invisibly, if not, an error is generated. + assert_dt = function(xdt, check_strict = TRUE, .var.name = vname(xdt)) makeAssertion(xdt, self$check_dt(xdt, check_strict = check_strict), .var.name, NULL), # nolint + + #' @description + #' Map a `matrix` or `data.frame` of values between 0 and 1 to proportional values inside the feasible intervals of individual parameters. + #' + #' @param x (`matrix` | `data.frame`)\cr + #' Values to map. Column names must be a subset of the names of parameters. + #' @return `data.table`. + qunif = function(x) { + assert(check_data_frame(x, types = "numeric", min.cols = 1), check_matrix(x, mode = "numeric", min.cols = 1)) + if (is.matrix(x)) { + qassert(x, "N[0,1]") + } else { + qassertr(x, "N[0,1]") + x = as.matrix(x) + } + assert_names(colnames(x), type = "unique", subset.of = private$.params$id) + + x = t(x) + params = private$.params[rownames(x), on = "id"] + params$result = list() + params[, result := list(as.list(as.data.frame(t(matrix(domain_qunif(recover_domain(.SD, .BY), x[id, ]), nrow = .N))))), + by = c("cls", "grouping")] + as.data.table(set_names(params$result, params$id)) + }, + + #' @description + #' get the [`Domain`] object that could be used to create a given parameter. + #' + #' @param id (`character(1)`). + #' @return [`Domain`]. + get_domain = function(id) { + assert_string(id) + paramrow = private$.params[id, on = "id", nomatch = NULL] + + if (!nrow(paramrow)) stopf("No param with id '%s'", id) + + vals = self$values + depstbl = self$deps[id, .(on, cond), on = "id", nomatch = 0] + paramrow[, `:=`( + .tags = list(private$.tags[id, tag, nomatch = 0]), + .trafo = private$.trafos[id, trafo], + .requirements = list(if (nrow(depstbl)) transpose_list(depstbl)), # NULL if no deps + .init_given = id %in% names(vals), + .init = unname(vals[id])) + ] + + set_class(paramrow, c(paramrow$cls, "Domain", class(paramrow))) + }, + + #' @description + #' Create a new `ParamSet` restricted to the passed IDs. + #' @param ids (`character()`). + #' @param allow_dangling_dependencies (`logical(1)`)\cr + #' Whether to allow subsets that cut across parameter dependencies. + #' Dependencies that point to dropped parameters are kept (but will be "dangling", i.e. their `"on"` will not be present). + #' @param keep_constraint (`logical(1)`)\cr + #' Whether to keep the `$constraint` function. + #' @return `ParamSet`. + subset = function(ids, allow_dangling_dependencies = FALSE, keep_constraint = TRUE) { + param_ids = private$.params$id + + assert_subset(ids, param_ids) + deps = self$deps + if (!allow_dangling_dependencies && nrow(deps)) { # check that all required / leftover parents are still in new ids + on = NULL + parents = unique(deps[ids, on, on = "id", nomatch = NULL]) + pids_not_there = setdiff(parents, ids) + if (length(pids_not_there) > 0L) { + stopf(paste0("Subsetting so that dependencies on params exist which would be gone: %s.", + "\nIf you still want to subset, set allow_dangling_dependencies to TRUE."), str_collapse(pids_not_there)) + } + } + result = ParamSet$new() + + + result$.__enclos_env__$private$.params = setindexv(private$.params[ids, on = "id"], c("id", "cls", "grouping")) + result$.__enclos_env__$private$.trafos = setkeyv(private$.trafos[ids, on = "id", nomatch = NULL], "id") + result$.__enclos_env__$private$.tags = setkeyv(private$.tags[ids, on = "id", nomatch = NULL], "id") + result$assert_values = FALSE + result$deps = deps[ids, on = "id", nomatch = NULL] + if (keep_constraint) result$constraint = self$constraint + # TODO: ParamSetCollection trafo currently drags along the entire original paramset in its environment + result$extra_trafo = self$extra_trafo + # restrict to ids already in pvals + values = self$values + result$values = values[match(ids, names(values), nomatch = 0)] + result$assert_values = TRUE + result + }, + + #' @description + #' Create new one-dimensional `ParamSet`s for each dimension. + #' @param ids (`character()`)\cr + #' IDs for which to create `ParamSet`s. Defaults to all IDs. + #' @return named `list()` of `ParamSet`. + subspaces = function(ids = private$.params$id) { + values = self$values + sapply(ids, simplify = FALSE, function(get_id) { + result = ParamSet$new() + result$extra_trafo = self$extra_trafo + # constraint make no sense here, basically by definition + result$.__enclos_env__$private$.params = setindexv(private$.params[get_id, on = "id"], c("id", "cls", "grouping")) + # setkeyv not strictly necessary since get_id is scalar, but we do it for consistency + result$.__enclos_env__$private$.trafos = setkeyv(private$.trafos[get_id, on = "id", nomatch = NULL], "id") + result$.__enclos_env__$private$.tags = setkeyv(private$.tags[get_id, on = "id", nomatch = NULL], "id") + result$assert_values = FALSE + result$values = values[match(get_id, names(values), nomatch = 0)] + result$assert_values = TRUE + result + }) + }, + + #' @description + #' Create a `ParamSet` from this object, even if this object itself is not + #' a `ParamSet` but e.g. a [`ParamSetCollection`]. + flatten = function() self$subset(private$.params$id, allow_dangling_dependencies = TRUE), + + #' @description + #' Construct a [`ParamSet`] to tune over. Constructed from [`TuneToken`] in `$values`, see [`to_tune()`]. + #' + #' @param values (`named list`): optional named list of [`TuneToken`] objects to convert, in place of `$values`. + search_space = function(values = self$values) { + assert_list(values) + assert_names(names(values), subset.of = self$ids()) + pars = private$get_tune_ps(values) + on = NULL # pacify static code check + dangling_deps = pars$deps[!pars$ids(), on = "on"] + if (nrow(dangling_deps)) { + stopf("Dangling dependencies not allowed: Dependencies on %s dangling.", str_collapse(dangling_deps$on)) + } + pars + }, #' @description #' Adds a dependency to this set, so that param `id` now depends on param `on`. #' #' @param id (`character(1)`). #' @param on (`character(1)`). + #' @param allow_dangling_dependencies (`logical(1)`): Whether to allow dependencies on parameters that are not present. #' @param cond ([Condition]). - add_dep = function(id, on, cond) { - params = self$params_unid - ids = names(params) + add_dep = function(id, on, cond, allow_dangling_dependencies = FALSE) { + params = private$.params + ids = params$id assert_choice(id, ids) - assert_choice(on, ids) - assert_r6(cond, "Condition") + if (allow_dangling_dependencies) assert_string(on) else assert_choice(on, ids) + assert_class(cond, "Condition") if (id == on) { stopf("A param cannot depend on itself!") } - feasible_on_values = map_lgl(cond$rhs, params[[on]]$test) - if (any(!feasible_on_values)) { - stopf("Condition has infeasible values for %s: %s", on, str_collapse(cond$rhs[!feasible_on_values])) + + if (on %in% ids) { # not necessarily true when allow_dangling_dependencies + feasible_on_values = map_lgl(cond$rhs, function(x) domain_test(self$get_domain(on), list(x))) + if (any(!feasible_on_values)) { + stopf("Condition has infeasible values for %s: %s", on, str_collapse(cond$rhs[!feasible_on_values])) + } } private$.deps = rbind(private$.deps, data.table(id = id, on = on, cond = list(cond))) invisible(self) @@ -378,13 +622,8 @@ ParamSet = R6Class("ParamSet", #' @description #' Helper for print outputs. #' @param ... (ignored). - format = function(...) { - set_id = self$set_id - if (!nzchar(set_id)) { - sprintf("<%s>", class(self)[1L]) - } else { - sprintf("<%s:%s>", class(self)[1L], set_id) - } + format = function() { + sprintf("<%s(%s)>", class(self)[[1L]], self$length) }, #' @description @@ -404,7 +643,8 @@ ParamSet = R6Class("ParamSet", assert_subset(hide_cols, names(d)) deps = self$deps if (nrow(deps)) { # add a nice extra charvec-col to the tab, which lists all parents-ids - dd = deps[, list(parents = list(unlist(get("on")))), by = "id"] + on = NULL + dd = deps[, list(parents = list(unlist(on))), by = "id"] d = merge(d, dd, on = "id", all.x = TRUE) } v = named_list(d$id) # add values to last col of print-dt as list col @@ -412,245 +652,243 @@ ParamSet = R6Class("ParamSet", d$value = list(v) print(d[, setdiff(colnames(d), hide_cols), with = FALSE]) } - if (!is.null(self$trafo)) { + if (self$has_trafo) { catf("Trafo is set.") } # printing the trafa functions sucks (can be very long). dont see a nother option then to suppress it for now } ), active = list( - #' @template field_params - params = function(rhs) { - if (!missing(rhs) && !identical(rhs, private$.params)) { - stop("$params is read-only.") - } - private$.params - }, - #' @template field_params_unid - params_unid = function(rhs) { - if (!missing(rhs) && !identical(rhs, private$.params)) { - stop("$params_unid is read-only.") - } - self$params - }, - #' @template field_deps - deps = function(v) { - if (missing(v)) { - private$.deps - } else { - private$.deps = assert_data_table(v) - } + #' @field data (`data.table`) `data.table` representation of the `ParamSet`. + data = function(v) { + if (!missing(v)) stop("data is read-only") + private$.params[, list(id, class = cls, lower, upper, levels, nlevels = self$nlevels, + is_bounded = self$is_bounded, special_vals, default, storage_type = self$storage_type, tags = self$tags)] }, - #' @field set_id (`character(1)`)\cr - #' ID of this param set. Default `""`. Settable. - set_id = function(v) { - if (missing(v)) { - private$.set_id - } else { - if (!identical(v, "")) { - assert_id(v) - assert_names(v, type = "strict") - } - private$.set_id = v + #' @template field_values + values = function(xs) { + if (missing(xs)) { + return(private$.values) } - }, - - #' @field length (`integer(1)`)\cr - #' Number of contained [Param]s. - length = function() { - length(self$params_unid) - }, + if (self$assert_values) { + self$assert(xs) + } + if (length(xs) == 0L) { + xs = named_list() + } else if (self$assert_values) { # this only makes sense when we have asserts on + # convert all integer params really to storage type int, move doubles to within bounds etc. + # solves issue #293, #317 + nontt = discard(xs, inherits, "TuneToken") - #' @field is_empty (`logical(1)`)\cr - #' Is the `ParamSet` empty? - is_empty = function() { - length(self$params_unid) == 0L + sanitized = set(private$.params[names(nontt), on = "id"], , "values", list(nontt))[ + !pmap_lgl(list(special_vals, values), has_element), + .(id, values = domain_sanitize(recover_domain(.SD, .BY), values)), by = c("cls", "grouping")] + xs = insert_named(xs, with(sanitized, set_names(values, id))) + } + # store with param ordering, return value with original ordering + private$.values = xs[match(private$.params$id, names(xs), nomatch = 0)] + xs + }, + + #' @template field_tags + tags = function(v) { + if (!missing(v)) { + assert_names(names(v), permutation.of = private$.params$id) + assert_list(v, any.missing = FALSE, types = "character") + private$.tags = data.table(id = rep(names(v), map_int(v, length)), tag = unlist(v), key = "id") + setindexv(private$.tags, "tag") + # return value with original ordering + return(v) + } + insert_named(named_list(private$.params$id, character(0)), with(private$.tags[, list(tag = list(tag)), by = "id"], set_names(tag, id))) }, - #' @field class (named `character()`)\cr - #' Classes of contained parameters, named with parameter IDs. - class = function() { - private$get_member_with_idnames("class", as.character) - }, + #' @template field_params + params = function(rhs) { + if (!missing(rhs)) { + stop("params is read-only.") + } - #' @field lower (named `double()`)\cr - #' Lower bounds of parameters (`NA` if parameter is not numeric). - #' Named with parameter IDs. - lower = function() { - private$get_member_with_idnames("lower", as.double) - }, + result = copy(private$.params) + result[, .tags := list(self$tags)] + result[private$.trafos, .trafo := list(trafo), on = "id"] + result[self$deps, .requirements := transpose_list(.(on, cond)), on = "id"] + vals = self$values + result[, `:=`( + .init_given = id %in% names(vals), + .init = unname(vals[id]) + )] - #' @field upper (named `double()`)\cr - #' Upper bounds of parameters (`NA` if parameter is not numeric). - #' Named with parameter IDs. - upper = function() { - private$get_member_with_idnames("upper", as.double) + result[] }, - #' @field levels (named `list()`)\cr - #' List of character vectors of allowed categorical values of contained parameters. - #' `NULL` if the parameter is not categorical. - #' Named with parameter IDs. - levels = function() { - private$get_member_with_idnames("levels", as.list) + #' @field domains (named `list` of [`Domain`]) + #' List of [`Domain`] objects that could be used to initialize this `ParamSet`. + domains = function(rhs) { + if (!missing(rhs)) { + stop("domains is read-only.") + } + nm = self$ids() + set_names(map(nm, self$get_domain), nm) }, - #' @field nlevels (named `integer()`)\cr - #' Number of categorical levels per parameter, `Inf` for double parameters or unbounded integer parameters. - #' Named with param IDs. - nlevels = function() { - private$get_member_with_idnames("nlevels", as.double) + #' @template field_extra_trafo + extra_trafo = function(f) { + if (missing(f)) { + private$.extra_trafo + } else { + assert(check_function(f, args = c("x", "param_set"), null.ok = TRUE), check_function(f, args = "x", null.ok = TRUE)) + private$.extra_trafo = f + } }, - #' @field is_bounded (named `logical()`)\cr - #' Do all parameters have finite bounds? - #' Named with parameter IDs. - is_bounded = function() { - all(map_lgl(self$params_unid, "is_bounded")) + #' @template field_constraint + constraint = function(f) { + if (missing(f)) { + private$.constraint + } else { + assert_function(f, args = "x", null.ok = TRUE) + private$.constraint = f + } }, - #' @field special_vals (named `list()` of `list()`)\cr - #' Special values for all parameters. - #' Named with parameter IDs. - special_vals = function() { - private$get_member_with_idnames("special_vals", as.list) - }, - #' @field default (named `list()`)\cr - #' Default values of all parameters. - #' If no default exists, element is not present. - #' Named with parameter IDs. - default = function() { - discard(private$get_member_with_idnames("default", as.list), is_nodefault) + #' @template field_deps + deps = function(v) { + if (missing(v)) { + private$.deps + } else { + assert_data_table(v) + if (nrow(v)) { + # only test for things without which things would seriously break + assert_names(colnames(v), identical.to = c("id", "on", "cond")) + assert_subset(v$id, private$.params$id) + assert_character(v$on, any.missing = FALSE) + assert_list(v$cond, types = "Condition", any.missing = FALSE) + } else { + v = data.table(id = character(0), on = character(0), cond = list()) # make sure we have the right columns + } + private$.deps = v + } }, - #' @field tags (named `list()` of `character()`)\cr - #' Can be used to group and subset parameters. + ############################ + # ParamSet flags + + #' @field length (`integer(1)`)\cr Number of contained parameters. + length = function() nrow(private$.params), + #' @field is_empty (`logical(1)`)\cr Is the `ParamSet` empty? Named with parameter IDs. + is_empty = function() nrow(private$.params) == 0L, + #' @field has_trafo (`logical(1)`)\cr Whether a `trafo` function is present, in parameters or in `extra_trafo`. + has_trafo = function() !is.null(self$extra_trafo) || nrow(private$.trafos), + #' @field has_extra_trafo (`logical(1)`)\cr Whether `extra_trafo` is set. + has_extra_trafo = function() !is.null(self$extra_trafo), + #' @field has_deps (`logical(1)`)\cr Whether the parameter dependencies are present + has_deps = function() nrow(self$deps) > 0L, + #' @field has_constraint (`logical(1)`)\cr Whether parameter constraint is set. + has_constraint = function() !is.null(private$.constraint), + #' @field all_numeric (`logical(1)`)\cr Is `TRUE` if all parameters are [`p_dbl()`] or [`p_int()`]. + all_numeric = function() all(self$is_number), + #' @field all_categorical (`logical(1)`)\cr Is `TRUE` if all parameters are [`p_fct()`] and [`p_lgl()`]. + all_categorical = function() all(self$is_categ), + #' @field all_bounded (`logical(1)`)\cr Is `TRUE` if all parameters are bounded. + all_bounded = function() all(self$is_bounded), + + ############################ + # Per-Parameter properties + + #' @field class (named `character()`)\cr Classes of contained parameters. Named with parameter IDs. + class = function() with(private$.params, set_names(cls, id)), + #' @field lower (named `double()`)\cr Lower bounds of numeric parameters (`NA` for non-numerics). Named with parameter IDs. + lower = function() with(private$.params, set_names(lower, id)), + #' @field upper (named `double()`)\cr Upper bounds of numeric parameters (`NA` for non-numerics). Named with parameter IDs. + upper = function() with(private$.params, set_names(upper, id)), + #' @field levels (named `list()` of `character`)\cr Allowed levels of categorical parameters (`NULL` for non-categoricals). #' Named with parameter IDs. - tags = function() { - private$get_member_with_idnames("tags", as.list) - }, - - #' @field storage_type (`character()`)\cr - #' Data types of parameters when stored in tables. + levels = function() with(private$.params, set_names(levels, id)), + #' @field storage_type (`character()`)\cr Data types of parameters when stored in tables. Named with parameter IDs. + storage_type = function() with(private$.params, set_names(storage_type, id)), + #' @field special_vals (named `list()` of `list()`)\cr Special values for all parameters. Named with parameter IDs. + special_vals = function() with(private$.params, set_names(special_vals, id)), + #' @field default (named `list()`)\cr Default values of all parameters. If no default exists, element is not present. #' Named with parameter IDs. - storage_type = function() { - private$get_member_with_idnames("storage_type", as.character) + default = function() with(private$.params[!map_lgl(default, is_nodefault), .(default, id)], set_names(default, id)), + #' @field has_trafo_param (`logical()`)\cr Whether `trafo` is set for any parameter. + has_trafo_param = function() with(private$.params, set_names(id %in% private$.trafos$id, id)), + #' @field is_logscale (`logical()`)\cr Whether `trafo` was set to `logscale` during construction.\cr + #' Note that this only refers to the `logscale` flag set during construction, e.g. `p_dbl(logscale = TRUE)`. + #' If the parameter was set to logscale manually, e.g. through `p_dbl(trafo = exp)`, + #' this `is_logscale` will be `FALSE`. + is_logscale = function() with(private$.params, set_names(cls %in% c("ParamDbl", "ParamInt") & cargo == "logscale", id)), + + ############################ + # Per-Parameter class properties (S3 method call) + + #' @field nlevels (named `integer()`)\cr Number of distinct levels of parameters. `Inf` for double parameters or unbounded integer parameters. + #' Named with param IDs. + nlevels = function() { + tmp = private$.params[, + list(id, nlevels = domain_nlevels(recover_domain(.SD, .BY))), + by = c("cls", "grouping") + ] + with(tmp[private$.params$id, on = "id"], set_names(nlevels, id)) }, - #' @field is_number (named `logical()`)\cr - #' Position is TRUE for [ParamDbl] and [ParamInt]. - #' Named with parameter IDs. + #' @field is_number (named `logical()`)\cr Whether parameter is [`p_dbl()`] or [`p_int()`]. Named with parameter IDs. is_number = function() { - private$get_member_with_idnames("is_number", as.logical) + tmp = private$.params[, + list(id, is_number = rep(domain_is_number(recover_domain(.SD, .BY)), .N)), + by = c("cls", "grouping") + ] + with(tmp[private$.params$id, on = "id"], set_names(is_number, id)) }, - #' @field is_categ (named `logical()`)\cr - #' Position is TRUE for [ParamFct] and [ParamLgl]. - #' Named with parameter IDs. + #' @field is_categ (named `logical()`)\cr Whether parameter is [`p_fct()`] or [`p_lgl()`]. Named with parameter IDs. is_categ = function() { - private$get_member_with_idnames("is_categ", as.logical) - }, - - #' @field all_numeric (`logical(1)`)\cr - #' Is `TRUE` if all parameters are [ParamDbl] or [ParamInt]. - all_numeric = function() { - all(self$is_number) - }, - - #' @field all_categorical (`logical(1)`)\cr - #' Is `TRUE` if all parameters are [ParamFct] and [ParamLgl]. - all_categorical = function() { - all(self$is_categ) - }, - - #' @field trafo (`function(x, param_set)`)\cr - #' Transformation function. Settable. - #' User has to pass a `function(x, param_set)`, of the form\cr - #' (named `list()`, [ParamSet]) -> named `list()`.\cr - #' The function is responsible to transform a feasible configuration into another encoding, - #' before potentially evaluating the configuration with the target algorithm. - #' For the output, not many things have to hold. - #' It needs to have unique names, and the target algorithm has to accept the configuration. - #' For convenience, the self-paramset is also passed in, if you need some info from it (e.g. tags). - #' Is NULL by default, and you can set it to NULL to switch the transformation off. - trafo = function(f) { - if (missing(f)) { - private$.trafo - } else { - assert_function(f, args = c("x", "param_set"), null.ok = TRUE) - private$.trafo = f - # is `TRUE` when function is passed to $trafo or .extra_trafo is set in ps() - # reset when trafo is set to NULL - private$.has_extra_trafo = !is.null(f) - } + tmp = private$.params[, + list(id, is_categ = rep(domain_is_categ(recover_domain(.SD, .BY)), .N)), + by = c("cls", "grouping") + ] + with(tmp[private$.params$id, on = "id"], set_names(is_categ, id)) }, - #' @field has_trafo (`logical(1)`)\cr - #' Has the set a `trafo` function? - has_trafo = function() { - !is.null(private$.trafo) - }, - - #' @template field_values - values = function(xs) { - if (missing(xs)) { - return(private$.values) - } - if (self$assert_values) { - self$assert(xs) - private$get_tune_ps(xs) # check that to_tune() are valid - } - if (length(xs) == 0L) { - xs = named_list() - } else if (self$assert_values) { # this only makes sense when we have asserts on - # convert all integer params really to storage type int, move doubles to within bounds etc. - # solves issue #293, #317 - params = self$params_unid # cache the AB - for (n in names(xs)) { - p = params[[n]] - x = xs[[n]] - if (inherits(x, "TuneToken")) next - if (has_element(p$special_vals, x)) next - xs[[n]] = p$convert(x) - } - } - private$.values = xs - }, - - #' @field has_deps (`logical(1)`)\cr - #' Has the set parameter dependencies? - has_deps = function() { - nrow(self$deps) > 0L + #' @field is_bounded (named `logical()`)\cr Whether parameters have finite bounds. Named with parameter IDs. + is_bounded = function() { + tmp = private$.params[, + list(id, is_bounded = domain_is_bounded(recover_domain(.SD, .BY))), + by = c("cls", "grouping") + ] + with(tmp[private$.params$id, on = "id"], set_names(is_bounded, id)) } ), private = list( - .set_id = NULL, - .trafo = NULL, + .extra_trafo = NULL, + .constraint = NULL, .params = NULL, .values = named_list(), - # is `TRUE` when function is passed to $trafo or .extra_trafo is set in ps() - .has_extra_trafo = FALSE, + .tags = data.table(id = character(0L), tag = character(0), key = "id"), .deps = data.table(id = character(0L), on = character(0L), cond = list()), - # return a slot / AB, as a named vec, named with id (and can enforce a certain vec-type) - get_member_with_idnames = function(member, astype) { - params = self$params - set_names(astype(map(params, member)), names(params)) - }, + .trafos = data.table(id = character(0L), trafo = list(), key = "id"), + get_tune_ps = function(values) { - selfparams = self$params_unid # cache to avoid performance hit in ParamSetCollection - partsets = imap(keep(values, inherits, "TuneToken"), function(value, pn) { - tunetoken_to_ps(value, selfparams[[pn]], pn) + values = keep(values, inherits, "TuneToken") + if (!length(values)) return(ParamSet$new()) + params = map(names(values), function(pn) { + domain = private$.params[pn, on = "id"] + set_class(domain, c(domain$cls, "Domain", class(domain))) }) - if (!length(partsets)) return(ParamSet$new()) + names(params) = names(values) + + # package-internal S3 fails if we don't call the function indirectly here + partsets = pmap(list(values, params), function(...) tunetoken_to_ps(...)) + pars = ps_union(partsets) # partsets does not have names here, wihch is what we want. + + names(partsets) = names(values) idmapping = map(partsets, function(x) x$ids()) - pars = ps_union(partsets) - pars$set_id = self$set_id - # tune_ps cannot contain an extra trafo because it is only constructed from TuneToken - pars[[".__enclos_env__"]][["private"]]$.has_extra_trafo = FALSE + # only add the dependencies that are also in the tuning PS on = id = NULL # pacify static code check pmap(self$deps[id %in% names(idmapping) & on %in% names(partsets), c("on", "id", "cond")], function(on, id, cond) { @@ -660,8 +898,7 @@ ParamSet = R6Class("ParamSet", return(NULL) } # remove infeasible values from condition - cond = cond$clone(deep = TRUE) - cond$rhs = keep(cond$rhs, pars$params[[on]]$test) + cond$rhs = keep(cond$rhs, function(x) partsets[[on]]$test(set_names(list(x), on))) if (!length(cond$rhs)) { # no value is feasible, but there may be a trafo that fixes this # so we are forgiving here. @@ -676,12 +913,7 @@ ParamSet = R6Class("ParamSet", deep_clone = function(name, value) { switch(name, - .params = map(value, function(x) x$clone(deep = TRUE)), - .deps = { - value = copy(value) - value$cond = lapply(value$cond, function(x) x$clone(deep = TRUE)) - value - }, + .deps = copy(value), .values = map(value, function(x) { # clones R6 objects in values, leave other things as they are @@ -699,18 +931,25 @@ ParamSet = R6Class("ParamSet", ) ) +recover_domain = function(sd, by) { + domain = as.data.table(c(by, sd)) + class(domain) = c(domain$cls, "Domain", class(domain)) + domain +} + #' @export as.data.table.ParamSet = function(x, ...) { # nolint - map_dtr(x$params, as.data.table) + x$data } #' @export rd_info.ParamSet = function(obj, descriptions = character(), ...) { # nolint - if (length(obj$params) == 0L) { + if (obj$length == 0L) { return("Empty ParamSet") } params = as.data.table(obj)[, c("id", "storage_type", "default", "lower", "upper", "levels"), with = FALSE] + cargo = obj$params$cargo if (length(descriptions)) { params = merge(params, enframe(descriptions, name = "id", value = "description"), all.x = TRUE, by = "id") @@ -721,7 +960,7 @@ rd_info.ParamSet = function(obj, descriptions = character(), ...) { # nolint is_default = map_lgl(params$default, inherits, "NoDefault") is_uty = params$storage_type == "list" set(params, i = which(is_uty & !is_default), j = "default", - value = map(obj$params[!is_default & is_uty], function(x) x$repr)) + value = map(cargo[!is_default & is_uty], function(x) x$repr)) set(params, i = which(is_uty), j = "storage_type", value = list("untyped")) set(params, i = which(is_default), j = "default", value = list("-")) diff --git a/R/ParamSetCollection.R b/R/ParamSetCollection.R index 7dd7567e..2d604245 100644 --- a/R/ParamSetCollection.R +++ b/R/ParamSetCollection.R @@ -1,16 +1,15 @@ #' @title ParamSetCollection #' #' @description -#' A collection of multiple [ParamSet] objects. +#' A collection of multiple [`ParamSet`] objects. #' * The collection is basically a light-weight wrapper / container around references to multiple sets. #' * In order to ensure unique param names, every param in the collection is referred to with -#' ".". Parameters from ParamSets with empty (i.e. `""`) `$set_id` are referenced -#' directly. Multiple ParamSets with `$set_id` `""` can be combined, but their parameter names -#' must be unique. -#' * Operation `subset` is currently not allowed. -#' * Operation `add` currently only works when adding complete sets not single params. +#' ".", where `` is the name of the entry a given [`ParamSet`] in the named list given during construction. +#' Parameters from [`ParamSet`] with empty (i.e. `""`) `set_id` are referenced +#' directly. Multiple [`ParamSet`]s with `set_id` `""` can be combined, but their parameter names +#' may not overlap to avoid name clashes. #' * When you either ask for 'values' or set them, the operation is delegated to the individual, -#' contained param set references. The collection itself does not maintain a `values` state. +#' contained [`ParamSet`] references. The collection itself does not maintain a `values` state. #' This also implies that if you directly change `values` in one of the referenced sets, #' this change is reflected in the collection. #' * Dependencies: It is possible to currently handle dependencies @@ -28,107 +27,142 @@ ParamSetCollection = R6Class("ParamSetCollection", inherit = ParamSet, #' @description #' Creates a new instance of this [R6][R6::R6Class] class. #' - #' @param sets (`list()` of [ParamSet])\cr - #' Parameter objects are cloned. - initialize = function(sets) { - + #' @param sets (named `list()` of [ParamSet])\cr + #' ParamSet objects are not cloned. + #' Names are used as "set_id" for the naming scheme of delegated parameters. + #' @param tag_sets (`logical(1)`)\cr + #' Whether to add tags of the form `"set_"` to each parameter originating from a given `ParamSet` given with name ``. + #' @param tag_params (`logical(1)`)\cr + #' Whether to add tags of the form `"param_"` to each parameter with original ID ``. + initialize = function(sets, tag_sets = FALSE, tag_params = FALSE) { assert_list(sets, types = "ParamSet") - split_sets = split(sets, map_lgl(sets, function(x) x$set_id == "")) - nameless_sets = split_sets$`TRUE` - named_sets = split_sets$`FALSE` - setids = map_chr(named_sets, "set_id") - assert_names(setids, type = "unique") - assert_names(unlist(map(nameless_sets, function(x) names(x$params_unid))) %??% character(0), type = "unique") - if (any(map_lgl(sets, "has_trafo"))) { - # we need to be able to have a trafo on the collection, not sure how to mix this with individual trafos yet. - stop("Building a collection out sets, where a ParamSet has a trafo is currently unsupported!") - } - private$.sets = sets - self$set_id = "" - pnames = names(self$params_unid) - dups = duplicated(pnames) + assert_flag(tag_sets) + assert_flag(tag_params) + + if (is.null(names(sets))) names(sets) = rep("", length(sets)) + + assert_names(names(sets)[names(sets) != ""], type = "strict") + + paramtbl = rbindlist(map(seq_along(sets), function(i) { + s = sets[[i]] + n = names(sets)[[i]] + params_child = s$params[, `:=`(original_id = id, owner_ps_index = i, owner_name = n)] + if (n != "") set(params_child, , "id", sprintf("%s.%s", n, params_child$id)) + params_child + })) + + dups = duplicated(paramtbl$id) if (any(dups)) { stopf("ParamSetCollection would contain duplicated parameter names: %s", - str_collapse(unique(pnames[dups]))) + str_collapse(unique(paramtbl$id[dups]))) } + + if (!nrow(paramtbl)) { + # when paramtbl is empty, use special setup to make sure information about the `.tags` column is present. + paramtbl = copy(empty_domain)[, `:=`(original_id = character(0), owner_ps_index = integer(0), owner_name = character(0))] + } + if (tag_sets) paramtbl[owner_name != "", .tags := pmap(list(.tags, owner_name), function(x, n) c(x, sprintf("set_%s", n)))] + if (tag_params) paramtbl[, .tags := pmap(list(.tags, original_id), function(x, n) c(x, sprintf("param_%s", n)))] + private$.tags = paramtbl[, .(tag = unique(unlist(.tags))), keyby = "id"] + + private$.trafos = setkeyv(paramtbl[!map_lgl(.trafo, is.null), .(id, trafo = .trafo)], "id") + + private$.translation = paramtbl[, c("id", "original_id", "owner_ps_index", "owner_name"), with = FALSE] + setkeyv(private$.translation, "id") + setindexv(private$.translation, "original_id") + + set(paramtbl, , setdiff(colnames(paramtbl), domain_names_permanent), NULL) + assert_names(colnames(paramtbl), identical.to = domain_names_permanent) + setindexv(paramtbl, c("id", "cls", "grouping")) + private$.params = paramtbl + + private$.children_with_trafos = which(!map_lgl(map(sets, "extra_trafo"), is.null)) + private$.children_with_constraints = which(!map_lgl(map(sets, "constraint"), is.null)) + + private$.sets = sets }, #' @description - #' Adds a set to this collection. + #' Adds a [`ParamSet`] to this collection. #' #' @param p ([ParamSet]). - add = function(p) { + #' @param n (`character(1)`)\cr + #' Name to use. Default `""`. + #' @param tag_sets (`logical(1)`)\cr + #' Whether to add tags of the form `"set_"` to the newly added parameters. + #' @param tag_params (`logical(1)`)\cr + #' Whether to add tags of the form `"param_"` to each parameter with original ID ``. + add = function(p, n = "", tag_sets = FALSE, tag_params = FALSE) { assert_r6(p, "ParamSet") - setnames = map_chr(private$.sets, "set_id") - if (p$set_id != "" && p$set_id %in% setnames) { - stopf("Setid '%s' already present in collection!", p$set_id) + if (n != "" && n %in% names(private$.sets)) { + stopf("Set name '%s' already present in collection!", n) } - if (p$has_trafo) { - stop("Building a collection out sets, where a ParamSet has a trafo is currently unsupported!") - } - pnames = names(p$params_unid) + pnames = p$ids() nameclashes = intersect( - ifelse(p$set_id != "", sprintf("%s.%s", p$set_id, pnames), pnames), - names(self$params_unid) + ifelse(n != "", sprintf("%s.%s", n, pnames), pnames), + self$ids() ) if (length(nameclashes)) { stopf("Adding parameter set would lead to nameclashes: %s", str_collapse(nameclashes)) } - private$.sets = c(private$.sets, list(p)) - invisible(self) - }, - #' @description - #' Removes sets of given ids from collection. - #' - #' @param ids (`character()`). - remove_sets = function(ids) { - setnames = map_chr(private$.sets, "set_id") - assert_subset(ids, setnames) - private$.sets[setnames %in% ids] = NULL - invisible(self) - }, + new_index = length(private$.sets) + 1 + paramtbl = p$params[, `:=`(original_id = id, owner_ps_index = new_index, owner_name = n)] + if (n != "") set(paramtbl, , "id", sprintf("%s.%s", n, paramtbl$id)) - #' @description - #' Only included for consistency. Not allowed to perform on [ParamSetCollection]s. - #' - #' @param ids (`character()`). - subset = function(ids) stop("not allowed") + if (!nrow(paramtbl)) { + # when paramtbl is empty, use special setup to make sure information about the `.tags` column is present. + paramtbl = copy(empty_domain)[, `:=`(original_id = character(0), owner_ps_index = integer(0), owner_name = character(0))] + } + if (tag_sets && n != "") paramtbl[, .tags := map(.tags, function(x) c(x, sprintf("set_%s", n)))] + if (tag_params) paramtbl[, .tags := pmap(list(.tags, original_id), function(x, n) c(x, sprintf("param_%s", n)))] + newtags = paramtbl[, .(tag = unique(unlist(.tags))), by = "id"] + if (nrow(newtags)) { + private$.tags = setkeyv(rbind(private$.tags, newtags), "id") + } + + newtrafos = paramtbl[!map_lgl(.trafo, is.null), .(id, trafo = .trafo)] + if (nrow(newtrafos)) { + private$.trafos = setkeyv(rbind(private$.trafos, newtrafos), "id") + } + + private$.translation = rbind(private$.translation, paramtbl[, c("id", "original_id", "owner_ps_index", "owner_name"), with = FALSE]) + setkeyv(private$.translation, "id") + setindexv(private$.translation, "original_id") + set(paramtbl, , setdiff(colnames(paramtbl), domain_names_permanent), NULL) + assert_names(colnames(paramtbl), identical.to = domain_names_permanent) + private$.params = rbind(private$.params, paramtbl) + setindexv(private$.params, c("id", "cls", "grouping")) + + if (!is.null(p$extra_trafo)) { + entry = if (n == "") length(private$.children_with_trafos) + 1 else n + private$.children_with_trafos[[entry]] = new_index + } + + if (!is.null(p$constraint)) { + entry = if (n == "") length(private$.children_with_constraints) + 1 else n + private$.children_with_constraints[[entry]] = new_index + } + + entry = if (n == "") length(private$.sets) + 1 else n + private$.sets[[n]] = p + invisible(self) + } ), active = list( - #' @template field_params - params = function(v) { - ps_all = self$params_unid - imap(ps_all, function(x, n) { - x = x$clone(deep = TRUE) - x$id = n - x - }) - }, - #' @template field_params_unid - params_unid = function(v) { - sets = private$.sets - names(sets) = map_chr(sets, "set_id") - if (length(sets) == 0L) { - return(named_list()) - } - private$.params = named_list() - # clone each param into new params-list and prefix id - ps_all = lapply(sets, function(s) s$params_unid) - ps_all = unlist(ps_all, recursive = FALSE) - if (!length(ps_all)) ps_all = named_list() - ps_all - }, #' @template field_deps deps = function(v) { - d_all = lapply(private$.sets, function(s) { + if (!missing(v)) { + stop("deps is read-only in ParamSetCollection.") + } + d_all = imap(private$.sets, function(s, id) { # copy all deps and rename ids to prefixed versions - dd = copy(s$deps) - ids_old = s$ids() - if (s$set_id != "" && nrow(dd)) { - ids_new = sprintf("%s.%s", s$set_id, ids_old) + dd = s$deps + if (id != "" && nrow(dd)) { + ids_old = s$ids() + ids_new = sprintf("%s.%s", id, ids_old) dd$id = map_values(dd$id, ids_old, ids_new) dd$on = map_values(dd$on, ids_old, ids_new) } @@ -140,32 +174,94 @@ ParamSetCollection = R6Class("ParamSetCollection", inherit = ParamSet, #' @template field_values values = function(xs) { sets = private$.sets - names(sets) = map_chr(sets, "set_id") if (!missing(xs)) { assert_list(xs) - self$assert(xs) # make sure everything is valid and feasible - - for (s in sets) { - # retrieve sublist for each set, then assign it in set (after removing prefix) - psids = names(s$params_unid) - if (s$set_id != "") { - psids = sprintf("%s.%s", s$set_id, psids) - } - pv = xs[intersect(psids, names(xs))] - if (s$set_id != "") { - names(pv) = substr(names(pv), nchar(s$set_id) + 2, nchar(names(pv))) - } - s$values = pv + # make sure everything is valid and feasible. + # We do this here because we don't want the loop to be aborted early and have half an update. + self$assert(xs) + + # %??% character(0) in case xs is an empty unnamed list + translate = private$.translation[names(xs) %??% character(0), list(original_id, owner_ps_index), on = "id"] + set(translate, , j = "values", list(xs)) + for (xtl in split(translate, by = "owner_ps_index")) { + sets[[xtl$owner_ps_index[[1]]]]$values = set_names(xtl$values, xtl$original_id) + } + # clear the values of all sets that are not touched by xs + for (clearing in setdiff(seq_along(sets), translate$owner_ps_index)) { + sets[[clearing]]$values = named_list() } } - vals = map(sets, "values") - vals = unlist(vals, recursive = FALSE) - if (!length(vals)) vals = named_list() + vals = unlist(map(sets, "values"), recursive = FALSE) + if (!length(vals)) return(named_list()) vals + }, + + #' @template field_extra_trafo + extra_trafo = function(f) { + if (!missing(f)) stop("extra_trafo is read-only in ParamSetCollection.") + if (!length(private$.children_with_trafos)) return(NULL) + private$.extra_trafo_explicit + + }, + + #' @template field_constraint + constraint = function(f) { + if (!missing(f)) stop("constraint is read-only in ParamSetCollection.") + if (!length(private$.children_with_constraints)) return(NULL) + private$.constraint_explicit + }, + + #' @field sets (named `list()`)\cr + #' Read-only `list` of of [`ParamSet`]s contained in this `ParamSetCollection`. + #' This field provides direct references to the [`ParamSet`] objects. + sets = function(v) { + if (!missing(v) && !identical(v, private$.sets)) stop("sets is read-only") + private$.sets } ), private = list( - .sets = NULL + .sets = NULL, + .translation = data.table(id = character(0), original_id = character(0), owner_ps_index = integer(0), owner_name = character(0), key = "id"), + .children_with_trafos = NULL, + .children_with_constraints = NULL, + .extra_trafo_explicit = function(x) { + changed = unlist(lapply(private$.children_with_trafos, function(set_index) { + changing_ids = private$.translation[J(set_index), id, on = "owner_ps_index"] + trafo = private$.sets[[set_index]]$extra_trafo + changing_values_in = x[names(x) %in% changing_ids] + names(changing_values_in) = private$.translation[names(changing_values_in), original_id] + # input of trafo() must not be changed after the call; otherwise the trafo would have to `force()` it in + # some circumstances. + changing_values = trafo(changing_values_in) + prefix = names(private$.sets)[[set_index]] + if (prefix != "") { + names(changing_values) = sprintf("%s.%s", prefix, names(changing_values)) + } + changing_values + }), recursive = FALSE) + unchanged_ids = private$.translation[!J(private$.children_with_trafos), id, on = "owner_ps_index"] + unchanged = x[names(x) %in% unchanged_ids] + c(unchanged, changed) + }, + .constraint_explicit = function(x) { + for (set_index in private$.children_with_constraints) { + constraining_ids = private$.translation[J(set_index), id, on = "owner_ps_index"] + constraint = private$.sets[[set_index]]$constraint + constraining_values = x[names(x) %in% changing_ids] + names(constraining_values) = private$.translation[names(constraining_values), original_id] + if (!constraint(x)) return(FALSE) + } + TRUE + }, + deep_clone = function(name, value) { + switch(name, + .deps = copy(value), + .sets = map(value, function(x) { + x$clone(deep = TRUE) + }), + value + ) + } ) ) diff --git a/R/ParamUty.R b/R/ParamUty.R index 5337dcee..61cbd143 100644 --- a/R/ParamUty.R +++ b/R/ParamUty.R @@ -1,72 +1,37 @@ -#' @title Untyped Parameter -#' -#' @description -#' A [Param] to describe untyped parameters. -#' -#' @template param_id -#' @template param_default -#' @template param_tags -#' @template param_custom_check -#' -#' @family Params -#' @include Param.R + +#' @rdname Domain #' @export -#' @examples -#' ParamUty$new("untyped", default = Inf) -ParamUty = R6Class("ParamUty", inherit = Param, - public = list( - #' @field custom_check (`function()`)\cr - #' Custom function to check the feasibility. - custom_check = NULL, - #' @field repr (`character(1)`)\cr - #' Custom field for printing the parameter table. - repr = NULL, +p_uty = function(custom_check = NULL, special_vals = list(), default = NO_DEF, tags = character(), depends = NULL, trafo = NULL, repr = substitute(default), init) { + assert_function(custom_check, null.ok = TRUE) + if (!is.null(custom_check)) { + custom_check_result = custom_check(1) + assert(check_true(custom_check_result), check_string(custom_check_result), .var.name = "The result of 'custom_check()'") + } + repr = if (!is_nodefault(default)) { + deparse(repr)[[1]] + } else { + "NoDefault" + } + Domain(cls = "ParamUty", grouping = "ParamUty", cargo = list(custom_check = custom_check, repr = repr), special_vals = special_vals, default = default, tags = tags, trafo = trafo, storage_type = "list", depends_expr = substitute(depends), init = init) +} - #' @description - #' Creates a new instance of this [R6][R6::R6Class] class. - #' - #' @param custom_check (`function()`)\cr - #' Custom function to check the feasibility. - #' Function which checks the input. - #' Must return 'TRUE' if the input is valid and a string with the error message otherwise. - #' Defaults to `NULL`, which means that no check is performed. - #' @param repr (`character(1)`)\cr - #' Custom representation string. Used for parameter table in help pages. - initialize = function(id, default = NO_DEF, tags = character(), custom_check = NULL, - repr = substitute(default)) { - # super class calls private$.check, so this must be set BEFORE - # we initialize the super class - if (is.null(custom_check)) { - self$custom_check = function(x) TRUE - } else { - self$custom_check = assert_function(custom_check, "x") - } - self$repr = if (!is_nodefault(default)) { - as.character(repr) - } else { - "NoDefault" - } - super$initialize(id, special_vals = list(), default = default, tags = tags) - } - ), +#' @export +domain_check.ParamUty = function(param, values) { + cargo = map(param$cargo, "custom_check") + subset = !map_lgl(cargo, is.null) + if (!any(subset)) return(TRUE) + values = values[subset] + check_domain_vectorize(param$id[subset], values, cargo[subset]) +} - active = list( - #' @template field_lower - lower = function() NA_real_, - #' @template field_upper - upper = function() NA_real_, - #' @template field_levels - levels = function() NULL, - #' @template field_nlevels - nlevels = function() Inf, - #' @template field_is_bounded - is_bounded = function() FALSE, - #' @template field_storage_type - storage_type = function() "list" - ), +#' @export +domain_nlevels.ParamUty = function(param) rep(Inf, nrow(param)) +#' @export +domain_is_bounded.ParamUty = function(param) rep(FALSE, nrow(param)) +#' @export +domain_qunif.ParamUty = function(param, x) stop("undefined") - private = list( - .check = function(x) self$custom_check(x), - .qunif = function(x) stop("undefined") - ) -) +#' @export +domain_is_number.ParamUty = function(param) FALSE +#' @export +domain_is_categ.ParamUty = function(param) FALSE diff --git a/R/Sampler.R b/R/Sampler.R index 74b42a09..80bf2f9e 100644 --- a/R/Sampler.R +++ b/R/Sampler.R @@ -9,7 +9,7 @@ #' @export Sampler = R6Class("Sampler", public = list( - #' @field param_set ([ParamSet])\cr + #' @field param_set ([`ParamSet`])\cr #' Domain / support of the distribution we want to sample from. param_set = NULL, @@ -18,6 +18,8 @@ Sampler = R6Class("Sampler", #' #' Note that this object is typically constructed via derived classes, #' e.g., [Sampler1D]. + #' @param param_set ([`ParamSet`])\cr + #' The [`ParamSet`] to associated with this `Sampler`. initialize = function(param_set) { assert_param_set(param_set, no_untyped = TRUE) self$param_set = param_set$clone(deep = TRUE) @@ -27,7 +29,7 @@ Sampler = R6Class("Sampler", #' Sample `n` values from the distribution. #' #' @param n (`integer(1)`). - #' @return [Design]. + #' @return [`Design`]. sample = function(n) { assert_count(n) # we do argcheck on toplevel Design$new(self$param_set, private$.sample(n), remove_dupl = FALSE) # user wants n points, dont remove diff --git a/R/Sampler1D.R b/R/Sampler1D.R index dc227944..5a69d1cd 100644 --- a/R/Sampler1D.R +++ b/R/Sampler1D.R @@ -15,29 +15,25 @@ Sampler1D = R6Class("Sampler1D", inherit = Sampler, # abstract base class #' Creates a new instance of this [R6][R6::R6Class] class. #' #' Note that this object is typically constructed via derived classes, - #' e.g., [Sampler1DUnif]. + #' e.g., [`Sampler1DUnif`]. initialize = function(param) { - assert(check_r6(param, "Param"), check_r6(param, "ParamSet")) - if (inherits(param, "Param")) { - super$initialize(ParamSet$new(list(param))) - } else { - if (param$length != 1) stopf("param must contain exactly 1 Param, but contains %s", param$length) - super$initialize(param) - } + assert_r6(param, "ParamSet") + if (param$length != 1) stopf("param must contain exactly 1 Param, but contains %s", param$length) + super$initialize(param) } ), active = list( - #' @field param ([Param])\cr - #' Returns the one Parameter that is sampled from. - param = function() self$param_set$params[[1]] + #' @field param ([`ParamSet`])\cr + #' Returns the one-dimensional [`ParamSet`] that is sampled from. + param = function() self$param_set ), private = list( # create a 1-col-dt, named by param-id, from a data vector (from sampling), and enforce storage type as_dt_col = function(x) { x = as_type(x, self$param$storage_type) - set_names(data.table(x), self$param$id) + set_names(data.table(x), self$param$ids()) } ) ) @@ -57,12 +53,12 @@ Sampler1DUnif = R6Class("Sampler1DUnif", inherit = Sampler1D, #' Creates a new instance of this [R6][R6::R6Class] class. initialize = function(param) { super$initialize(param) - assert_param(self$param, no_untyped = TRUE, must_bounded = TRUE) + assert_param_set(self$param, no_untyped = TRUE, must_bounded = TRUE) } ), private = list( - .sample = function(n) private$as_dt_col(self$param$qunif(runif(n))) # sample by doing qunif(u) + .sample = function(n) self$param_set$qunif(setnames(data.table(runif(n)), self$param$ids())) # sample by doing qunif(u) ) ) @@ -95,7 +91,7 @@ Sampler1DRfun = R6Class("Sampler1DRfun", inherit = Sampler1D, #' `TRUE` enables naive rejection sampling, so we stay inside of \[lower, upper\]. initialize = function(param, rfun, trunc = TRUE) { super$initialize(param) - assert_param(self$param, "ParamDbl") + assert_param_set(self$param, "ParamDbl") assert_function(rfun, args = "n") assert_flag(trunc) self$rfun = rfun @@ -136,7 +132,7 @@ Sampler1DRfun = R6Class("Sampler1DRfun", inherit = Sampler1D, #' @title Sampler1DCateg Class #' #' @description -#' Sampling from a discrete distribution, for a [ParamFct] or [ParamLgl]. +#' Sampling from a discrete distribution, for a [`ParamSet`] containing a single [`p_fct()`] or [`p_lgl()`]. #' #' @template param_param #' @@ -155,7 +151,7 @@ Sampler1DCateg = R6Class("Sampler1DCateg", inherit = Sampler1D, #' Numeric vector of `param$nlevels` probabilities, which is uniform by default. initialize = function(param, prob = NULL) { super$initialize(param) - assert_multi_class(self$param, c("ParamFct", "ParamLgl")) + assert_subset(self$param$class, c("ParamFct", "ParamLgl")) k = param$nlevels if (is.null(prob)) { prob = rep(1 / k, k) @@ -168,7 +164,7 @@ Sampler1DCateg = R6Class("Sampler1DCateg", inherit = Sampler1D, private = list( .sample = function(n) { - s = sample(self$param$levels, n, replace = TRUE, prob = self$prob) + s = sample(self$param$levels[[1]], n, replace = TRUE, prob = self$prob) super$as_dt_col(s) } ) @@ -177,7 +173,7 @@ Sampler1DCateg = R6Class("Sampler1DCateg", inherit = Sampler1D, #' @title Sampler1DNormal Class #' #' @description -#' Normal sampling (potentially truncated) for [ParamDbl]. +#' Normal sampling (potentially truncated) for [`p_dbl()`]. #' #' @template param_param #' @@ -198,7 +194,7 @@ Sampler1DNormal = R6Class("Sampler1DNormal", inherit = Sampler1DRfun, super$initialize(param, trunc = TRUE, # we always trunc, this should not hurt for unbounded params rfun = function(n) rnorm(n, mean = self$mean, sd = self$sd)) param = self$param - assert_param(param, "ParamDbl") + assert_param_set(param, "ParamDbl") if ((is.null(mean) || is.null(sd)) && !param$is_bounded) { stop("If 'mean' or 'sd' are not set, param must be bounded!") } diff --git a/R/SamplerHierarchical.R b/R/SamplerHierarchical.R index f5c9887e..668c1374 100644 --- a/R/SamplerHierarchical.R +++ b/R/SamplerHierarchical.R @@ -13,19 +13,21 @@ SamplerHierarchical = R6Class("SamplerHierarchical", inherit = Sampler, public = list( #' @field samplers (`list()`)\cr - #' List of [Sampler1D] objects that gives a Sampler for each [Param] in the `param_set`. + #' List of [`Sampler1D`] objects that gives a Sampler for each dimension in the `param_set`. samplers = NULL, #' @description #' Creates a new instance of this [R6][R6::R6Class] class. #' + #' @param param_set ([`ParamSet`])\cr + #' The [`ParamSet`] to associated with this `SamplerHierarchical`. #' @param samplers (`list()`)\cr - #' List of [Sampler1D] objects that gives a Sampler for each [Param] in the `param_set`. + #' List of [`Sampler1D`] objects that gives a Sampler for each dimension in the `param_set`. initialize = function(param_set, samplers) { assert_param_set(param_set, no_untyped = TRUE) assert_list(samplers, types = "Sampler1D") ids1 = param_set$ids() - ids2 = map_chr(samplers, function(s) s$param$id) + ids2 = map_chr(samplers, function(s) s$param$ids()) if (!setequal(ids1, ids2)) { stop("IDs of params in samplers to not correspond to IDs of params in set!") } diff --git a/R/SamplerJointIndep.R b/R/SamplerJointIndep.R index c26efd6f..c5216f29 100644 --- a/R/SamplerJointIndep.R +++ b/R/SamplerJointIndep.R @@ -9,21 +9,20 @@ SamplerJointIndep = R6Class("SamplerJointIndep", inherit = Sampler, public = list( #' @field samplers (`list()`)\cr - #' List of [Sampler] objects. + #' List of [`Sampler`] objects. samplers = NULL, #' @description #' Creates a new instance of this [R6][R6::R6Class] class. #' #' @param samplers (`list()`)\cr - #' List of [Sampler] objects. + #' List of [`Sampler`] objects. initialize = function(samplers) { assert_list(samplers, types = "Sampler") self$samplers = samplers pss = map(samplers, "param_set") # FIXME: maybe we should use a paramset collection here? - pss[[1L]] = pss[[1]]$clone() # we need to clone, add will clone later, too, otherwise we change the 1set in place - self$param_set = Reduce(function(ps1, ps2) ps1$add(ps2), pss) + self$param_set = ps_union(pss) # must_bounded and untyped should be check by the sapler, or if the sampler still works, then ok assert_param_set(self$param_set, no_deps = TRUE) } diff --git a/R/SamplerUnif.R b/R/SamplerUnif.R index f7a80c26..5f7f902a 100644 --- a/R/SamplerUnif.R +++ b/R/SamplerUnif.R @@ -2,7 +2,7 @@ #' #' @description #' Uniform random sampling for an arbitrary (bounded) [ParamSet]. -#' Constructs 1 uniform sampler per [Param], then passes them to [SamplerHierarchical]. +#' Constructs 1 uniform sampler per parameter, then passes them to [SamplerHierarchical]. #' Hence, also works for [ParamSet]s sets with dependencies. #' #' @template param_param_set @@ -14,9 +14,11 @@ SamplerUnif = R6Class("SamplerUnif", inherit = SamplerHierarchical, public = list( #' @description #' Creates a new instance of this [R6][R6::R6Class] class. + #' @param param_set ([`ParamSet`])\cr + #' The [`ParamSet`] to associated with this `SamplerUnif`. initialize = function(param_set) { assert_param_set(param_set, must_bounded = TRUE, no_deps = FALSE, no_untyped = TRUE) - samplers = lapply(param_set$params, Sampler1DUnif$new) + samplers = lapply(param_set$subspaces(), Sampler1DUnif$new) super$initialize(param_set, samplers) } ) diff --git a/R/asserts.R b/R/asserts.R index 2a520671..b5bf6468 100644 --- a/R/asserts.R +++ b/R/asserts.R @@ -1,35 +1,22 @@ #' @title Assertions for Params and ParamSets #' -#' @param param ([Param]). +#' @param param_set ([`ParamSet`]). #' @param cl (`character()`)\cr #' Allowed subclasses. #' @param no_untyped (`logical(1)`)\cr -#' Are untyped [Param]s allowed? +#' Are untyped [`Domain`]s allowed? #' @param must_bounded (`logical(1)`)\cr -#' Only bounded [Param]s allowed? -#' -#' @return The checked object, invisibly. -#' @export -assert_param = function(param, cl = "Param", no_untyped = FALSE, must_bounded = FALSE) { - assert_multi_class(param, cl) - if (no_untyped && (param$class == "ParamUty")) { - stop("Param is untyped!") - } - if (must_bounded && !param$is_bounded) { - stop("Param is unbounded!") - } - invisible(param) -} - -#' @param param_set ([ParamSet]). +#' Only bounded [`Domain`]s allowed? #' @param no_deps (`logical(1)`)\cr #' Are dependencies allowed? -#' @rdname assert_param +#' @return The checked object, invisibly. #' @export -assert_param_set = function(param_set, cl = "Param", no_untyped = FALSE, must_bounded = FALSE, no_deps = FALSE) { +assert_param_set = function(param_set, cl = NULL, no_untyped = FALSE, must_bounded = FALSE, no_deps = FALSE) { assert_r6(param_set, "ParamSet") - assert_list(param_set$params, types = cl) - if (no_untyped && ("ParamUty" %in% param_set$class)) { + if (!is.null(cl)) { + if (!all(param_set$class %in% cl)) stopf("Only classes %s allowed", str_collapse(cl)) + } + if (no_untyped && !all(param_set$class %in% c("ParamLgl", "ParamInt", "ParamFct", "ParamDbl"))) { stop("ParamSet contains untyped params!") } if (must_bounded && !all(param_set$is_bounded)) { @@ -40,8 +27,3 @@ assert_param_set = function(param_set, cl = "Param", no_untyped = FALSE, must_bo } invisible(param_set) } - -# assert that we can use the string in list, tables, formulas -assert_id = function(id) { - assert_string(id, pattern = "^[[:alpha:]]+[[:alnum:]_.]*$") -} diff --git a/R/generate_design_grid.R b/R/generate_design_grid.R index 8b887194..e8c783d7 100644 --- a/R/generate_design_grid.R +++ b/R/generate_design_grid.R @@ -6,21 +6,21 @@ #' always produce a grid over all their valid levels. #' For number params the endpoints of the params are always included in the grid. #' -#' @param param_set ([ParamSet]). +#' @param param_set ([`ParamSet`]). #' @param resolution (`integer(1)`)\cr -#' Global resolution for all [Param]s. +#' Global resolution for all parameters. #' @param param_resolutions (named `integer()`)\cr -#' Resolution per [Param], named by parameter ID. -#' @return [Design]. +#' Resolution per [`Domain`], named by parameter ID. +#' @return [`Design`]. #' #' @family generate_design #' @export #' @examples -#' ps = ParamSet$new(list( -#' ParamDbl$new("ratio", lower = 0, upper = 1), -#' ParamFct$new("letters", levels = letters[1:3]) -#' )) -#' generate_design_grid(ps, 10) +#' pset = ps( +#' ratio = p_dbl(lower = 0, upper = 1), +#' letters = p_fct(levels = letters[1:3]) +#' ) +#' generate_design_grid(pset, 10) generate_design_grid = function(param_set, resolution = NULL, param_resolutions = NULL) { assert_param_set(param_set, no_untyped = TRUE) @@ -54,7 +54,7 @@ generate_design_grid = function(param_set, resolution = NULL, param_resolutions # generate regular grid from 0,1 then map it to the values of the param, # then do a crossproduct grid_vec = lapply(par_res, function(r) seq(0, 1, length.out = r)) - res = imap(grid_vec, function(value, id) param_set$params[[id]]$qunif(x = value)) + res = imap(grid_vec, function(value, id) param_set$qunif(setnames(data.table(value), id))[[1]]) res = cross_join(res, sorted = FALSE) Design$new(param_set, res, remove_dupl = TRUE) # user wants no dupls, remove } diff --git a/R/generate_design_lhs.R b/R/generate_design_lhs.R index 1d01fd14..80d65df0 100644 --- a/R/generate_design_lhs.R +++ b/R/generate_design_lhs.R @@ -5,24 +5,24 @@ #' parameters whose constraints are unsatisfied generate `NA` entries in #' their respective columns. #' -#' @param param_set ([ParamSet]). +#' @param param_set ([`ParamSet`]). #' @param n (`integer(1)`) \cr #' Number of points to sample. #' @param lhs_fun (`function(n, k)`)\cr #' Function to use to generate a LHS sample, with n samples and k values per param. #' LHS functions are implemented in package \pkg{lhs}, default is to use [lhs::maximinLHS()]. -#' @return [Design]. +#' @return [`Design`]. #' #' @family generate_design #' @export #' @examples -#' ps = ParamSet$new(list( -#' ParamDbl$new("ratio", lower = 0, upper = 1), -#' ParamFct$new("letters", levels = letters[1:3]) -#' )) +#' pset = ps( +#' ratio = p_dbl(lower = 0, upper = 1), +#' letters = p_fct(levels = letters[1:3]) +#' ) #' #' if (requireNamespace("lhs", quietly = TRUE)) { -#' generate_design_lhs(ps, 10) +#' generate_design_lhs(pset, 10) #' } generate_design_lhs = function(param_set, n, lhs_fun = NULL) { if (is.null(lhs_fun)) { @@ -35,11 +35,11 @@ generate_design_lhs = function(param_set, n, lhs_fun = NULL) { ids = param_set$ids() if (n == 0) { - d = matrix(nrow = 0, ncol = param_set$length) + d = matrix(numeric(0), nrow = 0, ncol = param_set$length) } else { d = lhs_fun(n, k = param_set$length) } colnames(d) = ids - d = map_dtc(ids, function(id) param_set$params[[id]]$qunif(d[, id])) - Design$new(param_set, set_names(d, ids), remove_dupl = FALSE) # user wants n-points, dont remove + d = param_set$qunif(d) + Design$new(param_set, d, remove_dupl = FALSE) # user wants n-points, dont remove } diff --git a/R/generate_design_random.R b/R/generate_design_random.R index 8b1305cd..862d531f 100644 --- a/R/generate_design_random.R +++ b/R/generate_design_random.R @@ -2,22 +2,22 @@ #' #' @description #' Generates a design with randomly drawn points. -#' Internally uses [SamplerUnif], hence, also works for [ParamSet]s with dependencies. +#' Internally uses [`SamplerUnif`], hence, also works for [ParamSet]s with dependencies. #' If dependencies do not hold, values are set to `NA` in the resulting data.table. #' -#' @param param_set ([ParamSet]). +#' @param param_set ([`ParamSet`]). #' @param n (`integer(1)`)\cr #' Number of points to draw randomly. -#' @return [Design]. +#' @return [`Design`]. #' #' @family generate_design #' @export #' @examples -#' ps = ParamSet$new(list( -#' ParamDbl$new("ratio", lower = 0, upper = 1), -#' ParamFct$new("letters", levels = letters[1:3]) -#' )) -#' generate_design_random(ps, 10) +#' pset = ps( +#' ratio = p_dbl(lower = 0, upper = 1), +#' letters = p_fct(levels = letters[1:3]) +#' ) +#' generate_design_random(pset, 10) generate_design_random = function(param_set, n) { # arg checks done by SamplerUnif and sample SamplerUnif$new(param_set)$sample(n) diff --git a/R/generate_design_sobol.R b/R/generate_design_sobol.R index 01b86353..de67c98a 100644 --- a/R/generate_design_sobol.R +++ b/R/generate_design_sobol.R @@ -10,21 +10,21 @@ #' Note that non determinism is achieved by sampling the seed argument via #' `sample(.Machine$integer.max, size = 1L)`. #' -#' @param param_set ([ParamSet]). +#' @param param_set ([`ParamSet`]). #' @param n (`integer(1)`) \cr #' Number of points to sample. -#' @return [Design]. +#' @return [`Design`]. #' #' @family generate_design #' @export #' @examples -#' ps = ParamSet$new(list( -#' ParamDbl$new("ratio", lower = 0, upper = 1), -#' ParamFct$new("letters", levels = letters[1:3]) -#' )) +#' pset = ps( +#' ratio = p_dbl(lower = 0, upper = 1), +#' letters = p_fct(levels = letters[1:3]) +#' ) #' #' if (requireNamespace("spacefillr", quietly = TRUE)) { -#' generate_design_sobol(ps, 10) +#' generate_design_sobol(pset, 10) #' } generate_design_sobol = function(param_set, n) { require_namespaces("spacefillr") @@ -33,12 +33,12 @@ generate_design_sobol = function(param_set, n) { ids = param_set$ids() if (n == 0) { - d = matrix(nrow = 0, ncol = param_set$length) + d = matrix(numeric(0), nrow = 0, ncol = param_set$length) } else { seed = sample(.Machine$integer.max, size = 1L) d = spacefillr::generate_sobol_set(n, dim = param_set$length, seed = seed) } colnames(d) = ids - d = map_dtc(ids, function(id) param_set$params[[id]]$qunif(d[, id])) + d = param_set$qunif(d) Design$new(param_set, set_names(d, ids), remove_dupl = FALSE) # user wants n-points, dont remove } diff --git a/R/helper.R b/R/helper.R index d0702df7..53ca3f44 100644 --- a/R/helper.R +++ b/R/helper.R @@ -8,7 +8,7 @@ #' @param data ([data.table::data.table])\cr #' Rows are points and columns are parameters. #' -#' @param ps ([ParamSet])\cr +#' @param ps ([`ParamSet`])\cr #' If `trafo = TRUE`, used to call trafo function. #' #' @param filter_na (`logical(1)`)\cr @@ -32,126 +32,6 @@ transpose = function(data, ps = NULL, filter_na = TRUE, trafo = TRUE) { return(xs) } -# Create a ParamSet from a list of ParamSets -# This emulates `ParamSetCollection$new(sets)`, except that -# - The result is a `ParamSet`, not a `ParamSetCollection` -# - The ParamSets are allowed to have `$trafo`, which are collected together into a single function. -# This emulates `ParamSetCollection$new(sets)`, which in particular means that the resulting ParamSet has all the Params -# from the input `sets`, but some `$id`s are changed: If the ParamSet has a non-empty `set_id`, then the Params will -# have their changed to .. This is also reflected in deps and in `$trafo`. -# @param sets: list of ParamSet -ps_union = function(sets) { - assert_list(sets, types = "ParamSet") - assert_names(discard(map_chr(sets, "set_id"), `==`, ""), type = "unique") - - psc = ParamSetCollection$new(map(sets, function(x) { - if (x$has_trafo) { - # PSC can not use ParamSet with a `$trafo` that is set. - x = x$clone() - x$trafo = NULL - } - x - })) - - newps = ParamSet$new()$add(psc) - - # This loop collects information that is needed by the trafo. - # Resulting is a list of named lists, with one element per `sets` entry. Elements of the named lists are: - # - trafo: trafo of the given ParamSet - # - set_id: set_id of the given ParamSet - # - forward_name_translation: named `character`. Names are the Param IDs of the resulting newps, - # values are the Param IDs of the original Params in the `sets` argument. - # E.g. if a single ParamSet with set_id "sid" and with one Param with id "pid" is given, - # then this is a `c(sid.pid = "pid")`. - # Why is this needed? If the $trafo() is given a value `list(sid.pid = 1)`, then - # `forward_name_translation` can be used to rename this to `list(pid = 1)`, which is what the - # original trafo expects. - setinfo = map(unname(sets), function(s) { - sparams = s$params # avoid slow ParamSetCollection $params active binding - sinfo = list( - trafo = s$trafo, - set_id = s$set_id, - forward_name_translation = names2(sparams) - ) - psids = names2(sparams) - if (s$set_id != "") { - psids = sprintf("%s.%s", s$set_id, psids) - } - names(sinfo$forward_name_translation) = psids - sinfo - }) - - if (any(map_lgl(sets, "has_trafo"))) { - # allnames: names of all parameters, as seen from the outside - allnames = names2(unlist(map(setinfo, "forward_name_translation"))) - assert_set_equal(allnames, names2(newps$params)) # this should always be the case - - newps$trafo = crate(function(x, param_set) { - res = unlist(mlr3misc::map(setinfo, function(s) { - trafo = s$trafo - # get the parameter values that the current trafo should operate on, - # as identified by the names in forward_name_translation - pv = x[match(names(s$forward_name_translation), names(x), nomatch = 0)] - if (!is.null(trafo)) { - # translate name from "." to "" - names(pv) = s$forward_name_translation[names(pv)] - pv = trafo(pv) - - # append prefix again. trafo() could have changed parameter names, so - # we can't use any cached name_translation magic here - if (s$set_id != "") { - names(pv) = sprintf("%s.%s", s$set_id, names(pv)) - } - } - pv - }), recursive = FALSE) - - # add the Params that were not translated at all, because the ParamSet doesn't know about them. - res = c(mlr3misc::remove_named(x, allnames), res) - - res[c(intersect(names(res), names(x)), setdiff(names(res), names(x)))] # unchanged parameter names stay in order - }, setinfo, allnames) - } - newps -} - -# Get the R6ClassGenerator (constructor) by class name, even if the generator itself is not directly visible. -# This is necessary to create new instances of a `Param`, because the `Param` only contains a link to its class -# name, not its constructor. -# @param name: name of R6 class to be found -# @param env: environment (and its parents) to prefer -# Uses `getAnywhere()` to find objects named `name` with a `$new` slot that is a function. An error is thrown if nothing -# is found. -# If multiple objects are found, the order in which they are returned is: -# 1. object found in `env` (or its parents) -# 2. objects that are "visible" from the global environment -# 3. objects that are actually R6-objects (and do not just have a `$new()` function -get_r6_constructor = function(name, env = parent.frame()) { - found_in_env = dups = visible = isr6 = objs = NULL # pacify static check - # data.table with , , , , - candidates = do.call(data.table, utils::getAnywhere(name)) - # reducing to columns: , - candidates = candidates[!dups | visible, list(objs, visible)] - - # prefer object we find directly where the call expects it - candidates[, found_in_env := FALSE] - direct_found = tryCatch(get(name, envir = env), error = function(e) NULL) - if (!is.null(direct_found)) { - candidates = rbind(candidates, data.table(objs = list(direct_found), visible = TRUE, found_in_env = TRUE)) - } - - # throw away objects without a `$new()` - candidates = candidates[map_lgl(objs, function(o) "new" %in% names(o) && is.function(o$new))] - candidates[, isr6 := map_lgl(objs, is.R6Class)] - - if (!nrow(candidates)) { - stopf("Could not find R6ClassGenerator (or any object with $new() function) named %s.", name) - } - # Order of preference: - # found_in_env, then visible, then isr6 - candidates[order(found_in_env, visible, isr6, decreasing = TRUE)]$objs[[1]] -} - repr = function(x) { str_collapse(utils::capture.output(print(x)), "\n") } @@ -162,6 +42,14 @@ as_type = function(x, type) { integer = as.integer(x), numeric = as.numeric(x), character = as.character(x), + list = as.list(x), stopf("Invalid storage type '%s'", type) ) } + +# column to named list +col_to_nl = function(dt, col = 1, idcol = 2) { + data = dt[[col]] + names(data) = dt[[idcol]] + data +} diff --git a/R/ps.R b/R/ps.R index 8ec80e23..1901ffd9 100644 --- a/R/ps.R +++ b/R/ps.R @@ -8,13 +8,16 @@ #' #' For more specifics also see the documentation of [`Domain`]. #' -#' @param ... ([`Domain`] | [`Param`])\cr -#' Named arguments of [`Domain`] or [`Param`] objects. The [`ParamSet`] will be constructed of the given [`Param`]s, -#' or of [`Param`]s constructed from the given domains. The names of the arguments will be used as `$id` -#' (the `$id` of [`Param`] arguments are ignored). +#' @param ... ([`Domain`])\cr +#' Named arguments of [`Domain`] objects. The [`ParamSet`] will be constructed of the given [`Domain`]s, +#' The names of the arguments will be used as `$id()` in the resulting [`ParamSet`]. #' @param .extra_trafo (`function(x, param_set)`)\cr #' Transformation to set the resulting [`ParamSet`]'s `$trafo` value to. This is in addition to any `trafo` of #' [`Domain`] objects given in `...`, and will be run *after* transformations of individual parameters were performed. +#' @param .constraint (`function(x)`)\cr +#' Constraint function. +#' When given, this function must evaluate a named `list()` of values and determine whether it satisfies +#' constraints, returning a scalar `logical(1)` value. #' @param .allow_dangling_dependencies (`logical`)\cr #' Whether dependencies depending on parameters that are not present should be allowed. A parameter `x` having #' `depends = y == 0` if `y` is not present in the `ps()` call would usually throw an error, but if dangling @@ -58,65 +61,13 @@ #' pars$search_space() #' @family ParamSet construction helpers #' @export -ps = function(..., .extra_trafo = NULL, .allow_dangling_dependencies = FALSE) { - args = list(...) - assert_list(args, names = "unique", types = c("Param", "Domain")) - assert_function(.extra_trafo, null.ok = TRUE) - - # generate Params (with correct id) from Domain objects - params = imap(args, function(p, name) { - if (inherits(p, "Param")) { - p = p$clone(deep = TRUE) - } else { - p = p$param$clone(deep = TRUE) - } - p$id = name - p - }) - - paramset = ParamSet$new(params) - - # add Dependencies - imap(args, function(p, name) { - if (inherits(p, "Param") || is.null(p$requirements)) return(NULL) - map(p$requirements, function(req) { - if (!req$on %in% names(args) || req$on == name) { - if (.allow_dangling_dependencies) { - if (name == req$on) stop("A param cannot depend on itself!") - paramset$deps = rbind(paramset$deps, data.table(id = name, on = req$on, cond = list(req$cond))) - } else { - stopf("Parameter %s can not depend on %s.", name, req$on) - } - } else { - invoke(paramset$add_dep, id = name, .args = req) - } - }) - }) - - # add trafos - trafos = map(discard(args, function(x) inherits(x, "Param") || is.null(x$trafo)), - function(p) { - assert_function(p$trafo) - }) - if (length(trafos) || !is.null(.extra_trafo)) { - # the $trafo function iterates through the trafos and applies them - # We put the $trafo in a crate() (helper.R) to avoid having a function - # with lots of things in its environment. - paramset$trafo = crate(function(x, param_set) { - for (trafoing in names(trafos)) { - if (!is.null(x[[trafoing]])) { - x[[trafoing]] = trafos[[trafoing]](x[[trafoing]]) - } - } - if (!is.null(.extra_trafo)) x = .extra_trafo(x, param_set) - x - }, trafos, .extra_trafo) - } - paramset[[".__enclos_env__"]][["private"]]$.has_extra_trafo = !is.null(.extra_trafo) - paramset +ps = function(..., .extra_trafo = NULL, .constraint = NULL, .allow_dangling_dependencies = FALSE) { + param_set = ParamSet$new(list(...), allow_dangling_dependencies = .allow_dangling_dependencies) + param_set$extra_trafo = .extra_trafo + param_set$constraint = .constraint + param_set } - #' @title Create a ParamSet Collection #' #' @description diff --git a/R/ps_replicate.R b/R/ps_replicate.R new file mode 100644 index 00000000..cf79919e --- /dev/null +++ b/R/ps_replicate.R @@ -0,0 +1,60 @@ +#' @title Create a ParamSet by Repeating a Given ParamSet +#' +#' @description +#' Repeat a [`ParamSet`] a given number of times and thus create a larger [`ParamSet`]. +#' By default, the resulting parameters are prefixed with the string `"repX.", where `X` counts up from 1. +#' It is also possible to tag parameters by their original name and by their prefix, making grouped retrieval e.g. using `$get_values()` easier. +#' +#' @param set ([`ParamSet`])\cr +#' [`ParamSet`] to use as template. +#' @param times (`integer(1)`)\cr +#' Number of times to repeat `set`. +#' Should not be given if `prefixes` is provided. +#' @param prefixes (`character`)\cr +#' A `character` vector indicating the prefixes to use for each repetition of `set`. +#' If this is given, `times` is inferred from `length(prefixes)` and should not be given separately. +#' If `times` is given, this defaults to `"repX"`, with `X` counting up from 1. +#' @param tag_sets (`logical(1)`)\cr +#' Whether to add a tag of the form `"set_"` to each parameter in the result, indicating the repetition each parameter belongs to. +#' @param tag_params (`logical(1)`)\cr +#' Whether to add a tag of the form `"param_"` to each parameter in the result, indicating the original parameter ID inside `set`. +#' @examples +#' pset = ps( +#' i = p_int(), +#' z = p_lgl() +#' ) +#' +#' ps_replicate(pset, 3) +#' +#' ps_replicate(pset, prefixes = c("first", "last")) +#' +#' pset$values = list(i = 1, z = FALSE) +#' +#' psr = ps_replicate(pset, 2, tag_sets = TRUE, tag_params = TRUE) +#' +#' # observe the effect of tag_sets, tag_params: +#' psr$tags +#' +#' # note that values are repeated as well +#' psr$values +#' +#' psr$set_values(rep1.i = 10, rep2.z = TRUE) +#' psr$values +#' +#' # use `any_tags` to get subset of values. +#' # `any_tags = ` is preferable to `tags = `, since parameters +#' # could also have other tags. `tags = ` would require the +#' # selected params to have the given tags exclusively. +#' +#' # get all values associated with the original parameter `i` +#' psr$get_values(any_tags = "param_i") +#' +#' # get all values associated with the first repetition "rep1" +#' psr$get_values(any_tags = "set_rep1") +#' @export +ps_replicate = function(set, times = length(prefixes), prefixes = sprintf("rep%s", seq_len(times)), tag_sets = FALSE, tag_params = FALSE) { + assert_count(times) + assert_character(prefixes, any.missing = FALSE, unique = TRUE, len = times) + + ps_union(named_list(prefixes, set), tag_sets = tag_sets, tag_params = tag_params) +} diff --git a/R/ps_union.R b/R/ps_union.R new file mode 100644 index 00000000..a751d6f1 --- /dev/null +++ b/R/ps_union.R @@ -0,0 +1,56 @@ +#' @title Create a ParamSet from a list of ParamSets +#' +#' @description +#' This emulates `ParamSetCollection$new(sets)`, except that the result is a flat [`ParamSet`], not a [`ParamSetCollection`]. +#' The resulting object is decoupled from the input [`ParamSet`] objects: Unlike [`ParamSetCollection`], changing `$values` of +#' the resulting object will not change the input [`ParamSet`] `$values` by reference. +#' +#' This emulates `ParamSetCollection$new(sets)`, which in particular means that the resulting [`ParamSet`] has all the [`Domain`]s +#' from the input `sets`, but some `$id`s are changed: If the [`ParamSet`] is given in `sets` with a name, then the [`Domain`]s will +#' have their `` changed to `.`. This is also reflected in deps. +#' +#' The `c()` operator, applied to [`ParamSet`]s, is a synony for `ps_union()`. +#' @param sets (`list` of [`ParamSet`])\cr +#' This may be a named list, in which case non-empty names are prefixed to parameters in the corresponding [`ParamSet`]. +#' @param tag_sets (`logical(1)`)\cr +#' Whether to add tags of the form `"set_"` to each parameter originating from a given `ParamSet` given with name ``. +#' @param tag_params (`logical(1)`)\cr +#' Whether to add tags of the form `"param_"` to each parameter with original ID ``. +#' @examples +#' ps1 = ps(x = p_dbl()) +#' ps1$values = list(x = 1) +#' +#' ps2 = ps(y = p_lgl()) +#' +#' pu = ps_union(list(ps1, ps2)) +#' # same as: +#' pu = c(ps1, ps2) +#' +#' pu +#' +#' pu$values +#' +#' pu$values$x = 2 +#' pu$values +#' +#' # p1 is unchanged: +#' ps1$values +#' +#' # Prefixes automatically created for named elements. +#' # This allows repeating components. +#' pu2 = c(one = ps1, two = ps1, ps2) +#' pu2 +#' +#' pu2$values +#' +#' @export +ps_union = function(sets, tag_sets = FALSE, tag_params = FALSE) { + assert_list(sets, types = "ParamSet") + if (!length(sets)) return(ParamSet$new()) + ParamSetCollection$new(sets, tag_sets = tag_sets, tag_params = tag_params)$flatten() +} + +#' @export +c.ParamSet = function(..., .tag_sets = FALSE, .tag_params = FALSE) { + ps_union(list(...), tag_sets = .tag_sets, tag_params = .tag_params) +} diff --git a/R/to_tune.R b/R/to_tune.R index c3aefe14..9c41e6ea 100644 --- a/R/to_tune.R +++ b/R/to_tune.R @@ -21,42 +21,41 @@ #' * **`to_tune(lower, upper, logscale)`**: Indicates a numeric parameter should be tuned in the inclusive interval spanning #' `lower` to `upper`, possibly on a log scale if `logscale` is se to `TRUE`. All parameters are optional, and the #' parameter's own lower / upper bounds are used without log scale, by default. Depending on the parameter, -#' integer (if it is a [`ParamInt`]) or real values (if it is a [`ParamDbl`]) are used.\cr +#' integer (if it is a [`p_int()`]) or real values (if it is a [`p_dbl()`]) are used.\cr #' `lower`, `upper`, and `logscale` can be given by position, except when only one of them is given, in which case #' it must be named to disambiguate from the following cases.\cr #' When `logscale` is `TRUE`, then a `trafo` is generated automatically that transforms to the given bounds. The #' bounds are log()'d pre-trafo (see examples). See the `logscale` argument of [`Domain`] functions for more info.\cr -#' Note that "logscale" is *not* inherited from the [`Param`] that the `TuneToken` belongs to! Defining a parameter +#' Note that "logscale" is *not* inherited from the [`Domain`] that the `TuneToken` belongs to! Defining a parameter #' with `p_dbl(... logscale = TRUE)` will *not* automatically give the `to_tune()` assigned to it log-scale. #' * **`to_tune(levels)`**: Indicates a parameter should be tuned through the given discrete values. `levels` can be any #' named or unnamed atomic vector or list (although in the unnamed case it must be possible to construct a #' corresponding `character` vector with distinct values using `as.character`). #' * **`to_tune()`**: The given [`Domain`] object (constructed e.g. with [`p_int()`] or [`p_fct()`]) indicates #' the range which should be tuned over. The supplied `trafo` function is used for parameter transformation. -#' * **`to_tune()`**: The given [`Param`] object indicates the range which should be tuned over. -#' * **`to_tune()`**: The given [`ParamSet`] is used to tune over a single `Param`. This is useful for cases -#' where a single evaluation-time parameter value (e.g. [`ParamUty`]) is constructed from multiple tuner-visible -#' parameters (which may not be `ParamUty`). The supplied [`ParamSet`] should always contain a `$trafo` function, -#' which must always return a `list` with a single entry. +#' * **`to_tune()`**: The given [`ParamSet`] is used to tune over a single dimension. This is useful for cases +#' where a single evaluation-time parameter value (e.g. [`p_uty()`]) is constructed from multiple tuner-visible +#' parameters (which may not be [`p_uty()`]). If not one-dimensional, the supplied [`ParamSet`] should always contain a `$extra_trafo` function, +#' which must then always return a `list` with a single entry. #' #' The `TuneToken` object's internals are subject to change and should not be relied upon. `TuneToken` objects should #' only be constructed via `to_tune()`, and should only be used by giving them to `$values` of a [`ParamSet`]. #' @param ... if given, restricts the range to be tuning over, as described above. #' @return A `TuneToken` object. #' @examples -#' params = ParamSet$new(list( -#' ParamInt$new("int", 0, 10), -#' ParamInt$new("int_unbounded"), -#' ParamDbl$new("dbl", 0, 10), -#' ParamDbl$new("dbl_unbounded"), -#' ParamDbl$new("dbl_bounded_below", lower = 1), -#' ParamFct$new("fct", c("a", "b", "c")), -#' ParamUty$new("uty1"), -#' ParamUty$new("uty2"), -#' ParamUty$new("uty3"), -#' ParamUty$new("uty4"), -#' ParamUty$new("uty5") -#' )) +#' params = ps( +#' int = p_int(0, 10), +#' int_unbounded = p_int(), +#' dbl = p_dbl(0, 10), +#' dbl_unbounded = p_dbl(), +#' dbl_bounded_below = p_dbl(lower = 1), +#' fct = p_fct(c("a", "b", "c")), +#' uty1 = p_uty(), +#' uty2 = p_uty(), +#' uty3 = p_uty(), +#' uty4 = p_uty(), +#' uty5 = p_uty() +#' ) #' #' params$values = list( #' @@ -116,7 +115,7 @@ #' print(params$search_space()) #' #' # Notice how `logscale` applies `log()` to lower and upper bound pre-trafo: -#' params = ParamSet$new(list(ParamDbl$new("x"))) +#' params = ps(x = p_dbl()) #' #' params$values$x = to_tune(1, 100, logscale = TRUE) #' @@ -165,9 +164,9 @@ to_tune = function(...) { content = p_fct(levels = content) } else { if (inherits(content, "Domain")) { - bounded = ps(x = content, .allow_dangling_dependencies = TRUE)$is_bounded + bounded = domain_is_bounded(content) } else { - bounded = content$is_bounded + bounded = content$all_bounded } if (!bounded) { stop("tuning range must be bounded.") @@ -203,86 +202,78 @@ print.ObjectTuneToken = function(x, ...) { } # tunetoken_to_ps: Convert a `TuneToken` to a `ParamSet` that tunes over this. -# Needs the corresponding `Param` to which the `TuneToken` refers, both to +# Needs the corresponding `Domain` to which the `TuneToken` refers, both to # get the range (e.g. if `to_tune()` was used) and to verify that the `TuneToken` # does not go out of range. # # Makes liberal use to `pslike_to_ps` (converting Param, ParamSet, Domain to ParamSet) -tunetoken_to_ps = function(tt, param, id) { +# param is a data.table that is potentially modified by reference using data.table set() methods. +tunetoken_to_ps = function(tt, param) { UseMethod("tunetoken_to_ps") } -tunetoken_to_ps.FullTuneToken = function(tt, param, id) { - if (!param$is_bounded) { - stopf("%s must give a range for unbounded parameter %s.", tt$call, id) +tunetoken_to_ps.FullTuneToken = function(tt, param) { + if (!domain_is_bounded(param)) { + stopf("%s must give a range for unbounded parameter %s.", tt$call, param$id) } if (isTRUE(tt$content$logscale)) { - if (!param$is_number) stop("%s (%s): logscale only valid for numeric / integer parameters.", tt$call, id) - tunetoken_to_ps.RangeTuneToken(list(content = list(logscale = tt$content$logscale), tt$call), param, id) + if (!domain_is_number(param)) stop("%s (%s): logscale only valid for numeric / integer parameters.", tt$call, param$id) + tunetoken_to_ps.RangeTuneToken(list(content = list(logscale = tt$content$logscale), tt$call), param) } else { - pslike_to_ps(param, tt$call, param, id) + pslike_to_ps(param, tt$call, param) } } -tunetoken_to_ps.RangeTuneToken = function(tt, param, id) { - if (!param$is_number) { +tunetoken_to_ps.RangeTuneToken = function(tt, param) { + if (!domain_is_number(param)) { stopf("%s for non-numeric param must have zero or one argument.", tt$call) } - invalidpoints = discard(tt$content, function(x) is.null(x) || param$test(x)) + invalidpoints = discard(tt$content, function(x) is.null(x) || domain_test(param, set_names(list(x), param$id))) invalidpoints$logscale = NULL if (length(invalidpoints)) { stopf("%s range not compatible with param %s.\nBad value(s):\n%s\nParameter:\n%s", - tt$call, id, repr(invalidpoints), repr(param)) + tt$call, param$id, repr(invalidpoints), repr(param)) } - lower = tt$content$lower %??% param$lower - upper = tt$content$upper %??% param$upper - - if (!is.finite(lower) || !is.finite(upper)) stopf("%s range must be bounded, but is [%s, %s]", id, lower, upper) + bound_lower = tt$content$lower %??% param$lower + bound_upper = tt$content$upper %??% param$upper - if (isTRUE(tt$content$logscale)) { - # for logscale: create p_int / p_dbl object. Doesn't work if there is a numeric param class that we don't know about. - constructor = switch(param$class, ParamInt = p_int, ParamDbl = p_dbl, - stopf("%s: logscale for parameter %s of class %s not supported", tt$call, id, param$class)) - content = constructor(lower = lower, upper = upper, logscale = tt$content$logscale) - } else { - # general approach: create Param object - content = get_r6_constructor(param$class)$new(id = id, lower = lower, upper = upper) + if (!is.finite(bound_lower) || !is.finite(bound_upper)) { + stopf("%s range must be bounded, but is [%s, %s]", param$id, bound_lower, bound_upper) } - pslike_to_ps(content, tt$call, param, id) + + # create p_int / p_dbl object. Doesn't work if there is a numeric param class that we don't know about :-/ + constructor = switch(param$cls, ParamInt = p_int, ParamDbl = p_dbl, + stopf("%s: logscale for parameter %s of class %s not supported", tt$call, param$id, param$class)) + content = constructor(lower = bound_lower, upper = bound_upper, logscale = tt$content$logscale) + pslike_to_ps(content, tt$call, param) } -tunetoken_to_ps.ObjectTuneToken = function(tt, param, id) { - pslike_to_ps(tt$content, tt$call, param, id) +tunetoken_to_ps.ObjectTuneToken = function(tt, param) { + pslike_to_ps(tt$content, tt$call, param) } -# Convert something that is `ParamSet`-like (ParamSet, Param, or Domain) to a `ParamSet`. -# * content is ParamSet --> verify that it is compatible with given `Param` -# * content is Param --> Wrap in ParamSet +# Convert something that is `ParamSet`-like (ParamSet or Domain) to a `ParamSet`. +# * content is ParamSet --> verify that it is compatible with given `Domain` # * content is Domain --> Wrap in ParamSet, using ps() # @param pslike: thing to convert # @param call: to_tune()-call, for better debug message -# @param param: `Param`, that the `pslike` refers to, and therefore needs to be compatible to +# @param param: `Domain`, that the `pslike` refers to, and therefore needs to be compatible to # @param usersupplied: whether the `pslike` is supplied by the user (and should therefore be checked more thoroughly) # This is currently used for user-supplied ParamSets, for which the trafo must be adjusted. -pslike_to_ps = function(pslike, call, param, id, usersupplied = TRUE) { +pslike_to_ps = function(pslike, call, param, usersupplied = TRUE) { UseMethod("pslike_to_ps") } -pslike_to_ps.Domain = function(pslike, call, param, id, usersupplied = TRUE) { - pslike = invoke(ps, .allow_dangling_dependencies = TRUE, .args = set_names(list(pslike), id)) - pslike_to_ps(pslike, call, param, id, usersupplied = FALSE) -} - -pslike_to_ps.Param = function(pslike, call, param, id, usersupplied = TRUE) { - pslike = pslike$clone(deep = TRUE) - pslike$id = id - pslike = ParamSet$new(list(pslike)) - pslike_to_ps(pslike, call, param, id, usersupplied = FALSE) +pslike_to_ps.Domain = function(pslike, call, param, usersupplied = TRUE) { + # 'pslike' could be the same as 'param', i.e. a Domain with some cols missing. + # We could consider allowing construction of ParamSet from these unfinished domains instead. + pslike = ParamSet$new(structure(list(pslike), names = param$id), allow_dangling_dependencies = TRUE) + pslike_to_ps(pslike, call, param, usersupplied = FALSE) } -pslike_to_ps.ParamSet = function(pslike, call, param, id, usersupplied = TRUE) { - pslike = pslike$clone(deep = TRUE) +pslike_to_ps.ParamSet = function(pslike, call, param, usersupplied = TRUE) { + pslike = pslike$flatten() alldeps = pslike$deps # temporarily hide dangling deps on = NULL # pacify static code check @@ -292,23 +283,26 @@ pslike_to_ps.ParamSet = function(pslike, call, param, id, usersupplied = TRUE) { invalidpoints = discard(testpoints, function(x) length(x) == 1) if (length(invalidpoints)) { stopf("%s for param %s does not have a trafo that reduces output to one dimension.\nExample:\n%s", - call, id, repr(invalidpoints[[1]])) + call, param$id, repr(invalidpoints[[1]])) } - invalidpoints = discard(testpoints, function(x) param$test(x[[1]])) + + # do set_names because we ignore the name generated by the trafo + invalidpoints = discard(testpoints, function(x) domain_test(param, set_names(x, param$id))) if (length(invalidpoints)) { stopf("%s generates points that are not compatible with param %s.\nBad value:\n%s\nParameter:\n%s", - call, id, repr(invalidpoints[[1]][[1]]), repr(param)) + call, param$id, repr(invalidpoints[[1]][[1]]), repr(param)) } if (usersupplied) { - trafo = pslike$trafo %??% identity - pname = id - pslike$trafo = crate(function(x, param_set) { + # if the user gave us a paramset, then we need to make sure the resulting name is correct. + # we therefore always add a trafo here, even if the user-supplied ParamSet does not have a trafo itself + trafo = pslike$extra_trafo %??% identity + pname = param$id + pslike$extra_trafo = crate(function(x, param_set) { mlr3misc::set_names( checkmate::assert_list(trafo(x), len = 1, .var.name = sprintf("Trafo for tuning ParamSet for parameter %s", pname)), pname ) }, trafo, pname) } - pslike$set_id = "" pslike } diff --git a/R/zzz.R b/R/zzz.R index c0c0fe58..660cc995 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -6,6 +6,11 @@ #' @importFrom methods is "_PACKAGE" + + +# data.table-variables to announce: +# .init_given, .trafo + .onLoad = function(libname, pkgname) { # nolint # nocov start backports::import(pkgname) @@ -15,4 +20,4 @@ }) } # nocov end -leanify_package() +# leanify_package() diff --git a/attic/ParamS6.R b/attic/ParamS6.R new file mode 100644 index 00000000..f37bd866 --- /dev/null +++ b/attic/ParamS6.R @@ -0,0 +1,71 @@ + +#' @rdname Domain +#' @export +p_s6 = function(support, special_vals = list(), default = NO_DEF, tags = character(), depends = NULL, trafo = NULL, init) { + set = S6Cache$canonicalize(support) + support_description = if (is.character(support)) support else S6Cache$set6_sane_repr(object) + + if ((("power" %in% names(set)) && set$power != 1) || set$class %nin% c("numeric", "integer")) { + storage_type = "list" + } else { + storage_type = set$class + } + + Domain(cls = "ParamSet6", grouping = support_description, + cargo = set, + lower = suppressWarnings(as.numeric(set$lower)), + upper = suppressWarnings(as.numeric(set$upper)), + levels = as.list(set$elements), + special_vals = special_vals, + default = default, + tags = tags, + trafo = trafo, + storage_type = storage_type, + depends_expr = substitute(depends), + init = init) +} + +#' @export +domain_check.ParamSet6 = function(param, values) { + # we can rely on 'grouping' always giving us the same class + set = set6_cache_get(param$grouping[[1]]) + if (set$contains(values, all = TRUE)) { + return(TRUE) + } + nomatches = param$id[!set$contains(values, all = FALSE)] + sprintf("%s: not contained in %s.", str_collapse(nomatches, sep = ", "), set$strprint()) +} + +#' @export +domain_nlevels.ParamSet6 = function(param) { + # we can rely on 'grouping' always giving us the same class + set = set6_cache_get(param$grouping[[1]]) + card = set$properties$cardinality + card = if (!is.numeric(card)) Inf + rep(card, nrow(param)) +} +#' @export +domain_is_bounded.ParamSet6 = function(param) { + # we can rely on 'grouping' always giving us the same class + set = set6_cache_get(param$grouping[[1]]) + card = set$properties$cardinality + card = if (!is.numeric(card)) Inf + boundedness = is.finite(card) || (is.finite(set$lower) && is.finite(set$upper)) + rep(boundedness, nrow(param)) +} +#' @export +domain_qunif.ParamSet6 = function(param, x) stop("undefined") + + +#' @export +domain_is_number.ParamSet6 = function(param) { + param$storage_type[[1]] != "list" +} +#' @export +domain_is_categ.ParamSet6 = function(param) { + set = set6_cache_get(param$grouping[[1]]) + categness = ("power" %nin% names(set) || set$power == 1) && + set$class %nin% c("numeric", "integer") && is.finite(set$properties$cardinality) + + categness +} diff --git a/attic/ParamSet_add.R b/attic/ParamSet_add.R new file mode 100644 index 00000000..de160f6a --- /dev/null +++ b/attic/ParamSet_add.R @@ -0,0 +1,73 @@ + + #' @description + #' Adds a single param or another set to this set, all params are cloned on-demand, + #' so the input does not need to be cloned. + #' + #' @param p ([Param] | [ParamSet]). + add = function(p) { + + assert_multi_class(p, c("Param", "ParamSet")) + if (inherits(p, "Param")) { # level-up param to set + pparams = structure(list(p), names = p$id) + if (!is.null(private$.tags)) ptags = structure(list(p$param_tags), names = p$id) + ptrafo = NULL + pvalues = NULL + pdeps = NULL + } else { + pparams = p$params_unid + if (!is.null(private$.tags)) ptags = p$tags + ptrafo = p$trafo + pvalues = p$values + pdeps = p$deps + } + + nn = c(names(private$.params_unid), names(pparams)) + assert_names(nn, type = "strict") + if (!is.null(ptrafo)) { + stop("Cannot add a param set with a trafo.") + } + private$.params_unid = c(private$.params_unid, pparams) + private$.values = c(private$.values, pvalues) + if (!is.null(private$.tags)) private$.tags = c(private$.tags, ptags) + private$.deps = rbind(private$.deps, pdeps) + invisible(self) + }, + +############## ParamSetCollection + + #' @description + #' Adds a set to this collection. + #' + #' @param p ([ParamSet]). + add = function(p) { + assert_r6(p, "ParamSet") + setnames = names(private$.sets) %??% map_chr(private$.sets, "set_id") + if (p$set_id == "") { + unnamed_set_parnames = map(private$.sets[setnames == ""], function(x) names(x$params_unid)) + } else if (p$set_id %in% setnames) { + stopf("Setid '%s' already present in collection!", p$set_id) + } + if (p$has_trafo) { + stop("Building a collection out sets, where a ParamSet has a trafo is currently unsupported!") + } + pnames = names(p$params_unid) + nameclashes = intersect( + ifelse(p$set_id != "", sprintf("%s.%s", p$set_id, pnames), pnames), + names(self$params_unid) + ) + if (length(nameclashes)) { + stopf("Adding parameter set would lead to nameclashes: %s", str_collapse(nameclashes)) + } + set_addition = list(p) + if (!is.null(names(private$.sets))) { + # ignoring the other ParamSet's set_id in favor of names(private$.sets), so add the name here as well. + names(set_addition) = p$set_id + } + + tagsaddition = p$tags + names(tagsaddition) = sprintf("%s.%s", p$set_id, names(tagsaddition)) + private$.tags = c(private$.tags, tagsaddition) + + private$.sets = c(private$.sets, set_addition) + invisible(self) + }, diff --git a/attic/S6ObjectCache.R b/attic/S6ObjectCache.R new file mode 100644 index 00000000..618ddebd --- /dev/null +++ b/attic/S6ObjectCache.R @@ -0,0 +1,170 @@ + +S6Cache = R6Class("S6Cache", + cloneable = FALSE, + public = list( + initialize = function(cachesize) { + private$.cache = new.env(parent = emptyenv()) + private$.evictable = list() + private$.insertpointer = 1 + private$.evictpointer = 1 + private$.size = 0 + private$.maxsize = cachesize + private$.s6ns = asNamespace("set6") + private$.settypes = keep(names(private$.s6ns), function(n) { + obj = private$.s6ns[[n]] + if (!is.environment(obj) || !is.function(obj[["get_inherit"]])) return(FALSE) + repeat { + if (identical(obj, set6::Set)) return(TRUE) + obj = obj$get_inherit() + if (is.null(obj)) return(FALSE) + } + }) + + }, + get = function(description) { + assert_string(description) + description = trimws(description) + set = private$.cache[[description]] + if (!is.null(set)) return(set) + set = + private$.infer_interval(description) %??% + private$.infer_discrete(description) %??% + private$.infer_settype(description) %??% + if (grepl("^n", description)) { + stype = private$.infer_settype(description) + if (!is.null(stype)) { + set6::setpower(stype, "n") + } + } %??% stopf("Description '%s' not in set6_cache and could not be constructed.", description) # how do we automatically generate a set from a string? + self$enter(self$canonicalize(set), description) + set + }, + canonicalize = function(object) { + if (test_string(object, pattern = "[^ ]")) return(self$get(object) %??% stopf("Could not get object from string '%s'", object)) + assert_class(object, "Set") + repr = self$set6_sane_repr(object) + private$.cache[[repr]] %??% object # don't use the given object when one with the same representation is already present. + }, + enter = function(object, description = NULL) { + # if we were able to get the object from the description, then we mark it as evictable + private$.enter_lowlevel(object, c(description, self$set6_sane_repr(object)), evictable = TRUE) + }, + set6_sane_repr = function(object) { + assert_r6(object, "Set") + using_unicode_for_whatever_reason = set6::useUnicode() + on.exit(set6::useUnicode(using_unicode_for_whatever_reason)) + set6::useUnicode(FALSE) + object$strprint(n = 1e10) + } + ), + private = list( + .cache = NULL, + .size = NULL, + .maxsize = NULL, + + .evictable = NULL, # list indicating names of objects that can be evicted + .insertpointer = NULL, + .evictpointer = NULL, + + .s6ns = NULL, # namespace of set6, from where we get the Set constructors + .settypes = NULL, # names of the set6 constructors + .enter_lowlevel = function(object, descriptions, evictable) { + while (private$.size >= private$.maxsize) { + # evict + if (private$.evictpointer == private$.insertpointer) { # can't evict + if (evictable) { + return(FALSE) # we are full, have nothing to evict, but *this object* is evictable, so don't bother. + } else { + break + } + } + if (private$.evictpointer > private$.maxsize + 1) { + private$.evictpointer = 1 + private$.evictable = private$.evictable[seq_len(min(private$.maxsize, 1.5 * (private$.insertpointer - 1)))] + } + evp = private$.evictpointer + evicting = private$.evictable[[evp]] + assert_character(evicting, min.len = 1, any.missing = FALSE) + rm(list = evicting, envir = private$.cache) + private$.size = private$.size - 1 + private$.evictpointer = evp + 1 + private$.evictable[evp] = list(NULL) # remove list element, but don't shorten list + } + + for (desc in descriptions) { + private$.cache[[desc]] = object + } + + private$.size = private$.size + 1 # even if it has multiple descriptions, the object only counts for one. + if (evictable) { + ins = private$.insertpointer + if (ins > private$.maxsize + 1) { + ins = 1 + } + private$.evictable[[ins]] = descriptions + private$.insertpointer = ins + 1 + } + }, + .get_settype = function(st, description, error_on_not_found = TRUE, construction_args = list()) { + matches = private$.settypes[match(tolower(st), tolower(private$.settypes), nomatch = 0)] + if (!length(matches)) { + if (error_on_not_found) { + stopf("Unknown settype '%s' in description '%s'", st, description) + } else { + return(NULL) + } + } + if (length(matches) > 1) { + matches = private$.settypes[match(st, private$.settypes, nomatch = 0)] + # even error if error_on_not_found is FALSE, because this is a special message + if (length(matches) != 1) stopf("Settype '%s' in description '%s' matched multiple set6 classes, but none of them matches by case.",st, description) + } + do.call(private$.s6ns[[matches]]$new, construction_args) + }, + .infer_interval = function(description) { + intervaldef = regmatches(description, regexec("^([[(])(([^,]*),([^,|]*))?(\\| *([a-zA-Z]+))? *([])]) *(^ *[0-9n]+)?$", description))[[1]] + if (!length(intervaldef)) return(NULL) + type = paste0(intervaldef[[2]], intervaldef[[8]]) + lower = if (intervaldef[[4]] == "") -Inf else suppressWarnings(as.numeric(intervaldef[[4]])) + upper = if (intervaldef[[5]] == "") Inf else suppressWarnings(as.numeric(intervaldef[[5]])) + if (is.na(lower) || is.na(upper)) stopf("Description '%s' is ill-formed interval expression.", description) + universe = if (intervaldef[[7]] == "") set6::ExtendedReals$new() else private$.get_settype(intervaldef[[7]], description) + result = set6::Interval$new(lower = lower, upper = upper, type = type, class = universe$class, universe = universe) + private$.make_power(result, intervaldef[[9]], description) + }, + .infer_discrete = function(description) { + discretedef = regmatches(description, regexec("^\\{([^{}|]*)(\\| *([a-zA-Z]+))? *\\} *(^ *[0-9n]+)?$", description))[[1]] + if (!length(discretedef)) return(NULL) + if (discretedef[[2]] == "") { + entries = character(0) + } else { + entries = strsplit(discretedef[[2]], " *, *")[[1]] + if ("" %in% entries) stopf("Empty string element not allowed in description '%s'", description) + } + universe = if (discretedef[[4]] == "") set6::Universal$new() else private$.get_settype(discretedef[[4]], description) + result = set6::Set$new(elements = entries, universe = universe) + private$.make_power(result, discretedef[[5]], description) + }, + .infer_settype = function(description) { + typedef = regmatches(description, regexec("^([^^ ]*) *(^ *[0-9n]+)?$", description))[[1]] + if (!length(typedef)) return(NULL) + result = private$.get_settype(typedef[[2]], description, error_on_not_found = FALSE) + if (is.null(result)) return(NULL) + private$.make_power(result, typedef[[3]], description) + }, + .make_power = function(set, powerexp, description) { + if (powerexp == "") { + return(set) + } + power = substr(powerexp, 2, nchar(powerexp)) + if (trimws(power) == "n") { + power = "n" + } else { + power = suppressWarnings(as.numeric(power)) + if (is.na(power)) stopf("Ill-formatted power expression in %s", description) + } + return(set6::setpower(set, power)) + } + ) +)$new(cachesize = 2^20) + diff --git a/attic/demo.R b/attic/demo.R new file mode 100644 index 00000000..89d78565 --- /dev/null +++ b/attic/demo.R @@ -0,0 +1,12 @@ + +p_dbl(0, 1, init = 1) + +p = ps(prob = p_dbl(0, 1, init = 1), param = p_int(0, logscale = TRUE)) + +p$values +p$values$prob = 0.5 +p$values +p$values$param = 0 +p$values$param = -100 + + diff --git a/attic/helper_r6.R b/attic/helper_r6.R new file mode 100644 index 00000000..21b655d3 --- /dev/null +++ b/attic/helper_r6.R @@ -0,0 +1,78 @@ +# Create a ParamSet from a list of ParamSets +# This emulates `ParamSetCollection$new(sets)`, except that +# - The result is a `ParamSet`, not a `ParamSetCollection` +# - The ParamSets are allowed to have `$trafo`, which are collected together into a single function. +# This emulates `ParamSetCollection$new(sets)`, which in particular means that the resulting ParamSet has all the Params +# from the input `sets`, but some `$id`s are changed: If the ParamSet has a non-empty `set_id`, then the Params will +# have their changed to .. This is also reflected in deps and in `$trafo`. +# @param sets: list of ParamSet +ps_union = function(sets, tag_set = FALSE, tag_params = FALSE) { + assert_list(sets, types = "ParamSet") + + if (!ignore_ids) { + names(sets) = map(sets, "set_id") + } + + psc = ParamSetCollection$new(sets, ignore_ids = TRUE) + + newps = ParamSet$new()$add(psc) + + # This loop collects information that is needed by the trafo. + # Resulting is a list of named lists, with one element per `sets` entry. Elements of the named lists are: + # - trafo: trafo of the given ParamSet + # - set_id: set_id of the given ParamSet + # - forward_name_translation: named `character`. Names are the Param IDs of the resulting newps, + # values are the Param IDs of the original Params in the `sets` argument. + # E.g. if a single ParamSet with set_id "sid" and with one Param with id "pid" is given, + # then this is a `c(sid.pid = "pid")`. + # Why is this needed? If the $trafo() is given a value `list(sid.pid = 1)`, then + # `forward_name_translation` can be used to rename this to `list(pid = 1)`, which is what the + # original trafo expects. + setinfo = unname(imap(keep(sets, function(x) x$has_trafo), function(s, n) { + sparams = s$params_unid # avoid slow ParamSetCollection $params active binding + sinfo = list( + trafo = s$trafo, + set_id = n, + forward_name_translation = names2(sparams) + ) + psids = names2(sparams) + if (n != "") { + psids = sprintf("%s.%s", n, psids) + } + names(sinfo$forward_name_translation) = psids + sinfo + })) + + if (length(setinfo)) { + # allnames: names of all parameters, as seen from the outside + allnames = names2(unlist(map(setinfo, "forward_name_translation"))) + assert_subset(allnames, names2(newps$params_unid)) # just check, this should always be the case + + newps$trafo = crate(function(x, param_set) { + res = unlist(mlr3misc::map(setinfo, function(s) { + trafo = s$trafo + # get the parameter values that the current trafo should operate on, + # as identified by the names in forward_name_translation + pv = x[match(names(s$forward_name_translation), names(x), nomatch = 0)] + + # translate name from "." to "" + names(pv) = s$forward_name_translation[names(pv)] + pv = trafo(pv) + + # append prefix again. trafo() could have changed parameter names, so + # we can't use any cached name_translation magic here + if (s$set_id != "") { + names(pv) = sprintf("%s.%s", s$set_id, names(pv)) + } + + pv + }), recursive = FALSE) + + # add the Params that were not translated at all, because the ParamSet doesn't know about them. + res = c(mlr3misc::remove_named(x, allnames), res) + + res[c(intersect(names(res), names(x)), setdiff(names(res), names(x)))] # unchanged parameter names stay in order + }, setinfo, allnames) + } + newps +} diff --git a/attic/vectoralgorithm.R b/attic/vectoralgorithm.R new file mode 100644 index 00000000..f59458bc --- /dev/null +++ b/attic/vectoralgorithm.R @@ -0,0 +1,130 @@ +library("R6") +library("paradox") +library("checkmate") + + +Strategy = R6Class("Strategy", + public = list( + initialize = function(param_set) { + private$.param_set = param_set + }, + run = function(x) stop("abstract") + ), + active = list( + param_set = function(v) { + if (!missing(v) && !identical(v, private$.param_set)) stop("param_set is read-only") + private$.param_set + } + ), + private = list( + .param_set = NULL + ) +) + +StrategyVector = R6Class("StrategyVector", inherit = Strategy, + public = list( + components = NULL, + initialize = function(components) { + components = lapply(components, function(x) x$clone(deep = TRUE)) + self$components = components + params = lapply(seq_along(components), function(ci) { + comp = components[[ci]] + p = comp$param_set + p$set_id = paste0("element", ci) + p + }) + param_set = ParamSetCollection$new(params) + super$initialize(param_set) + }, + run = function(x) { + lapply(self$components, function(comp) comp$run(x)) + }, + run_vector = function(x) { + assert_list(x, len = length(self$components)) + Map(function(comp, xcomp) comp$run(xcomp), self$components, x) + } + ) +) + +c.Strategy = function(...) { + components = list(...) + assert_list(components, types = "Strategy") + components = unlist(lapply(unname(components), function(cmp) { + if (inherits(cmp, "StrategyVector")) cmp$components else list(cmp) + }), recursive = FALSE) + StrategyVector$new(components) +} + + +StrategyAdd = R6Class("StrategyAdd", inherit = Strategy, + public = list( + initialize = function() { + super$initialize(ps(summand = p_dbl())) + }, + run = function(x) { + self$param_set$get_values()$summand + x + } + ) +) + +StrategyMultiply = R6Class("StrategyMultiply", inherit = Strategy, + public = list( + initialize = function() { + super$initialize(ps(factor = p_dbl())) + }, + run = function(x) { + self$param_set$get_values()$factor * x + } + ) +) + +StrategyMultiplyAdd = R6Class("StrategyMultiplyAdd", inherit = Strategy, + public = list( + initialize = function() { + super$initialize(ps(factor = p_dbl(), summand = p_dbl())) + }, + run = function(x) { + self$param_set$get_values()$factor * x + self$param_set$get_values()$summand + } + ) +) + + + +sa = StrategyAdd$new() +sa$param_set$values$summand = 10 + +sm = StrategyMultiply$new() +sm$param_set$values$factor = 2 + +sam = StrategyMultiplyAdd$new() +sam$param_set$values$summand = -1 +sam$param_set$values$factor = 4 + +sa$run(100) # 110 +sm$run(100) # 200 +sam$run(100) # 399 + +svec = StrategyVector$new(list(sa, sm, sam)) +svec$run(100) # list(110, 200, 399) +svec$run_vector(list(100, 200, 300)) # list(110, 400, 1199) + +c(svec, sa, sm)$run_vector(list(100, 200, 300, 400, 500)) # list(110, 400, 1199, 410, 1000) + + + +svec_long = StrategyVector$new(c( + lapply(1:2000, function(x) { + sa = StrategyAdd$new() + sa$param_set$values$summand = x + sa + }), + list(sm, sam) +)) + +svec_long$run(100) + # as.list(c(101:2100, 200, 399)) +svec_long$run_vector(as.list(1:2002)) + # as.list(c((1:2000) * 2, 4002, 8007)) + + diff --git a/attic/vectoralgorithm_ii.R b/attic/vectoralgorithm_ii.R new file mode 100644 index 00000000..9a8b83d6 --- /dev/null +++ b/attic/vectoralgorithm_ii.R @@ -0,0 +1,174 @@ +library("R6") +library("paradox") +library("checkmate") + +Strategy = R6Class("Strategy", + public = list( + is_scalar = NULL, + multiplicity = NULL, + initialize = function(param_set, is_scalar = TRUE, multiplicity = FALSE) { + self$is_scalar = assert_flag(is_scalar) + self$multiplicity = assert_count(multiplicity, positive = TRUE) + assert_true(!is_scalar || multiplicity == 1) + private$param_set = param_set + }, + run = function(x) stop("abstract"), + run_vector = function(x) { + if (self$is_scalar) { + stop("Scalar strategy does not vectorize.") + } else { + stop("abstract") + } + } + ), + active = list( + param_set = function(v) { + if (!missing(v) && !identical(v, private$.param_set)) stop("param_set is read-only") + private$.param_set + } + ), + private = list( + .param_set = NULL + ) +) + + +StrategyHybridVector = R6Class("StrategyHybridVector", inherits = Strategy, + public = list( + initialize = function(param_set, multi_init = NULL) { + assert_data_table(multi_init, min.rows = 1, null.ok = TRUE) + if (!is.null(multi_init)) { + param_set$vectorize = TRUE + param_set$multiplicity = nrow(multi_init) + param_set$values = multi_init + is_scalar = FALSE + multiplicity = param_set$multiplicity + } else { + is_scalar = TRUE + multiplicity = 1 + } + super$initialize(param_set, is_scalar = is_scalar, multiplicity = multiplicity) + } + ) +) + +######## Making use of possible multiplicities +StrategyVector = R6Class("Strategy", inherits = Strategy, + public = list( + components = NULL, + chunksizes = NULL, + initialize = function(components) { + assert_list(components, types = "Strategy") + self$components = unname(components) + self$chunksizes = sapply(self$components, `[[`, "multiplicity") + super$initialize(param_set = NULL, is_scalar = FALSE, multiplicity = sum(self$chunksizes) + }, + run = function(x) { + result_listlist = lapply(self$components, function(comp) { + if (comp$is_scalar) list(comp$run(x)) else comp$run(x) + }) + unlist(result_listlist, recursive = FALSE) + }, + run_vector = function(x) { + assert_list(x, len = self$multiplicity) + x = split(x, unname(rep(seq_along(x), self$chunksizes))) + result_listlist = Map(self$components, x, f = function(comp, x) { + if (comp$is_scalar) list(comp$run(x)) else comp$run(x) + }) + unlist(result_listlist, recursive = FALSE) + } + ) +) + +######## as before +c.Strategy = function(...) { + components = list(...) + assert_list(components, types = "Strategy") + components = unlist(lapply(unname(components), function(cmp) { + if (inherits(cmp, "StrategyVector")) cmp$components else list(cmp) + }), recursive = FALSE) + StrategyVector$new(components) +} + +StrategyAdd = R6Class("StrategyAdd", inherit = StrategyHybridVector, + public = list( + initialize = function(multi_init = NULL) { + super$initizlize(ps(summand = p_dbl()), multi_init = multi_init) + }, + run = function(x) { + result = self$get_values()$summand + x + if (!self$is_scalar) result = as.list(result) + result + }, + run_vector = function(x) { + if (self$is_scalar) stop("Scalar strategy does not vectorize.") + self$run(x) + } + ) +) + +######## quality of life +c.StrategyAdd = function(...) { + components = list(...) + if (!test_list(components, types = "StrategyAdd")) NextMethod() + StrategyAdd$new(multi_init = data.table::rbindlist(lapply(components, function(x) x$param_set$get_values(as_dt = TRUE)))) +} + +######## as before +StrategyMultiply = R6Class("StrategyMultiply", inherit = Strategy, + public = list( + initialize = function() { + super$initialize(ps(factor = p_dbl())) + }, + run = function(x) { + self$get_values()$factor * x + } + ) +) + +######## as before +StrategyMultiplyAdd = R6Class("StrategyMultiplyAdd", inherit = Strategy, + public = list( + initialize = function() { + super$initialize(ps(factor = p_dbl(), summand = p_dbl())) + }, + run = function(x) { + self$get_values()$factor * x + self$get_values()$summand + } + ) +) + + +sa = StrategyAdd$new() +sa$param_set$values$summand = 10 + +sm = StrategyMultiply$new() +sm$param_set$values$factor = 2 + +sam = StrategyMultiplyAdd$new() +sam$param_set$values$summand = -1 +sam$param_set$values$factor = 4 + +sa$run(100) # 110 +sm$run(100) # 200 +sam$run(100) # 399 + +svec = StrategyVector$new(list(sa, sm, sam)) +svec$run(100) # list(110, 200, 399) +svec$run_vector(c(100, 200, 300)) # list(110, 400, 1199) + +c(svec, sa, sm)$run_vector(c(100, 200, 300, 400, 500)) # list(110, 400, 1199, 410, 1000) + + + +svec_long = StrategyVector$new(c( + StrategyAdd$new(multi_init = data.table(summand = 1:2000)), + list(sm, sam) +)) + +svec_long$run(100) + # as.list(c(101:2100, 200, 399)) +svec_long$run_vector(1:2002) + # as.list(c((1:2000) * 2, 4002, 8007)) + + diff --git a/man-roxygen/field_constraint.R b/man-roxygen/field_constraint.R new file mode 100644 index 00000000..6eb19870 --- /dev/null +++ b/man-roxygen/field_constraint.R @@ -0,0 +1,4 @@ +#' @field constraint (`function(x)`)\cr +#' Constraint function. Settable. +#' This function must evaluate a named `list()` of values and determine whether it satisfies +#' constraints, returning a scalar `logical(1)` value. diff --git a/man-roxygen/field_extra_trafo.R b/man-roxygen/field_extra_trafo.R new file mode 100644 index 00000000..13adc367 --- /dev/null +++ b/man-roxygen/field_extra_trafo.R @@ -0,0 +1,10 @@ +#' @field extra_trafo (`function(x, param_set)`)\cr +#' Transformation function. Settable. +#' User has to pass a `function(x)`, of the form\cr +#' (named `list()`, [ParamSet]) -> named `list()`.\cr +#' The function is responsible to transform a feasible configuration into another encoding, +#' before potentially evaluating the configuration with the target algorithm. +#' For the output, not many things have to hold. +#' It needs to have unique names, and the target algorithm has to accept the configuration. +#' For convenience, the self-paramset is also passed in, if you need some info from it (e.g. tags). +#' Is NULL by default, and you can set it to NULL to switch the transformation off. diff --git a/man-roxygen/field_is_bounded.R b/man-roxygen/field_is_bounded.R index 3a98a97b..135a2cd7 100644 --- a/man-roxygen/field_is_bounded.R +++ b/man-roxygen/field_is_bounded.R @@ -1,4 +1,4 @@ #' @field is_bounded (`logical(1)`)\cr #' Are the bounds finite? -#' Always `TRUE` for [ParamFct] and [ParamLgl]. -#' Always `FALSE` for [ParamUty]. +#' Always `TRUE` for [`p_fct()`] and [`p_lgl()`]. +#' Always `FALSE` for [`p_uty()`]. diff --git a/man-roxygen/field_levels.R b/man-roxygen/field_levels.R index ff983042..ab48188b 100644 --- a/man-roxygen/field_levels.R +++ b/man-roxygen/field_levels.R @@ -1,4 +1,4 @@ #' @field levels (`character()` | `NULL`)\cr #' Set of allowed levels. -#' Always `NULL` for [ParamDbl], [ParamInt] and [ParamUty]. -#' Always `c(TRUE, FALSE)` for [ParamLgl]. +#' Always `NULL` for [`p_dbl()`], [`p_int()`] and [`p_uty()`]. +#' Always `c(TRUE, FALSE)` for [`p_lgl()`]. diff --git a/man-roxygen/field_lower.R b/man-roxygen/field_lower.R index 23fa0795..a68a7929 100644 --- a/man-roxygen/field_lower.R +++ b/man-roxygen/field_lower.R @@ -1,3 +1,3 @@ #' @field lower (`numeric(1)`)\cr #' Lower bound. -#' Always `NA` for [ParamFct], [ParamLgl] and [ParamUty]. +#' Always `NA` for [`p_fct()`], [`p_lgl()`] and [`p_uty()`]. diff --git a/man-roxygen/field_nlevels.R b/man-roxygen/field_nlevels.R index d41c0b6a..8fd24f81 100644 --- a/man-roxygen/field_nlevels.R +++ b/man-roxygen/field_nlevels.R @@ -1,5 +1,5 @@ #' @field nlevels (`integer(1)` | `Inf`)\cr #' Number of categorical levels. -#' Always `Inf` for [ParamDbl] and [ParamUty]. -#' The number of integers in the range `[lower, upper]`, or `Inf` if unbounded for [ParamInt]. -#' Always `2` for [ParamLgl]. +#' Always `Inf` for [`p_dbl()`] and [`p_uty()`]. +#' The number of integers in the range `[lower, upper]`, or `Inf` if unbounded for [`p_int()`]. +#' Always `2` for [`p_lgl()`]. diff --git a/man-roxygen/field_params.R b/man-roxygen/field_params.R index 1e95c510..062b43cb 100644 --- a/man-roxygen/field_params.R +++ b/man-roxygen/field_params.R @@ -1,2 +1,4 @@ #' @field params (named `list()`)\cr -#' List of [Param], named with their respective ID. +#' `data.table` representing the combined [`Domain`] objects used to construct the [`ParamSet`]. +#' Used for internal purpuses. +#' Its use by external code is deprecated. diff --git a/man-roxygen/field_params_unid.R b/man-roxygen/field_params_unid.R deleted file mode 100644 index 5fcf3b61..00000000 --- a/man-roxygen/field_params_unid.R +++ /dev/null @@ -1,5 +0,0 @@ -#' @field params_unid (named `list()`)\cr -#' List of [Param], named with their true ID. However, -#' this field has the [Param]'s `$id` value set to a -#' potentially invalid value. This active binding should -#' only be used internally. diff --git a/man-roxygen/field_storage_type.R b/man-roxygen/field_storage_type.R index 216fe15e..9e4b0552 100644 --- a/man-roxygen/field_storage_type.R +++ b/man-roxygen/field_storage_type.R @@ -1,7 +1,7 @@ #' @field storage_type (`character(1)`)\cr #' Data type when values of this parameter are stored in a data table or sampled. -#' Always `"numeric"` for [ParamDbl]. -#' Always `"character"` for [ParamFct]. -#' Always `"integer"` for [ParamInt]. -#' Always `"logical"` for [ParamLgl]. -#' Always `"list"` for [ParamUty]. +#' Always `"numeric"` for [`p_dbl()`]. +#' Always `"character"` for [`p_fct()`]. +#' Always `"integer"` for [`p_int()`]. +#' Always `"logical"` for [`p_lgl()`]. +#' Always `"list"` for [`p_uty()`]. diff --git a/man-roxygen/field_tags.R b/man-roxygen/field_tags.R new file mode 100644 index 00000000..6072a2c4 --- /dev/null +++ b/man-roxygen/field_tags.R @@ -0,0 +1,4 @@ +#' @field tags (named `list()` of `character()`)\cr +#' Can be used to group and subset parameters. +#' Named with parameter IDs. + diff --git a/man-roxygen/field_upper.R b/man-roxygen/field_upper.R index 482503fe..41d61008 100644 --- a/man-roxygen/field_upper.R +++ b/man-roxygen/field_upper.R @@ -1,3 +1,3 @@ #' @field upper (`numeric(1)`)\cr #' Upper bound. -#' Always `NA` for [ParamFct], [ParamLgl] and [ParamUty]. +#' Always `NA` for [`p_fct()`], [`p_lgl()`] and [`p_uty()`]. diff --git a/man-roxygen/param_param.R b/man-roxygen/param_param.R index c5add0b7..287fe08d 100644 --- a/man-roxygen/param_param.R +++ b/man-roxygen/param_param.R @@ -1,2 +1,3 @@ -#' @param param ([Param])\cr +#' @param param ([`ParamSet`])\cr #' Domain / support of the distribution we want to sample from. +#' Must be one-dimensional. diff --git a/man/Condition.Rd b/man/Condition.Rd index 4ae2a9dd..f80d3f75 100644 --- a/man/Condition.Rd +++ b/man/Condition.Rd @@ -1,153 +1,58 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/Condition.R -\name{Condition} +\name{condition_test} +\alias{condition_test} +\alias{condition_as_string} \alias{Condition} \alias{CondEqual} \alias{CondAnyOf} \title{Dependency Condition} -\description{ -Condition object, to specify the condition in a dependency. -} -\section{Currently implemented simple conditions}{ +\usage{ +condition_test(cond, x) -\itemize{ -\item \code{CondEqual$new(rhs)} \cr -Parent must be equal to \code{rhs}. -\item \code{CondAnyOf$new(rhs)} \cr -Parent must be any value of \code{rhs}. -} -} - -\section{Public fields}{ -\if{html}{\out{
}} -\describe{ -\item{\code{type}}{(\code{character(1)})\cr -Name / type of the condition.} +condition_as_string(cond, lhs_chr = "x") -\item{\code{rhs}}{(\code{any})\cr -Right-hand-side of the condition.} -} -\if{html}{\out{
}} -} -\section{Methods}{ -\subsection{Public methods}{ -\itemize{ -\item \href{#method-Condition-new}{\code{Condition$new()}} -\item \href{#method-Condition-test}{\code{Condition$test()}} -\item \href{#method-Condition-as_string}{\code{Condition$as_string()}} -\item \href{#method-Condition-format}{\code{Condition$format()}} -\item \href{#method-Condition-print}{\code{Condition$print()}} -\item \href{#method-Condition-clone}{\code{Condition$clone()}} -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-Condition-new}{}}} -\subsection{Method \code{new()}}{ -Creates a new instance of this \link[R6:R6Class]{R6} class. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{Condition$new(type, rhs)}\if{html}{\out{
}} +Condition(rhs, condition_format_string) } +\arguments{ +\item{cond}{(\code{Condition})\cr +\code{Condition} to use} -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{type}}{(\code{character(1)})\cr -Name / type of the condition.} +\item{x}{(\code{any})\cr +Value to test} -\item{\code{rhs}}{(\code{any})\cr +\item{lhs_chr}{(\code{character(1)})\cr +Symbolic representation to use for \verb{} in the returned string.} + +\item{rhs}{(\code{any})\cr Right-hand-side of the condition.} -} -\if{html}{\out{
}} -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-Condition-test}{}}} -\subsection{Method \code{test()}}{ -Checks if condition is satisfied. -Called on a vector of parent param values. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{Condition$test(x)}\if{html}{\out{
}} -} -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{x}}{(\code{vector()}).} -} -\if{html}{\out{
}} -} -\subsection{Returns}{ -\code{logical(1)}. +\item{condition_format_string}{(\code{character(1)})\cr +Format-string for representing the condition when pretty-printing +in \code{\link[=condition_as_string]{condition_as_string()}}. +Should contain two \verb{\%s}, as it is used in an \code{sprintf()}-call with +two further string values.} } +\description{ +Condition object, to specify the condition in a dependency. } -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-Condition-as_string}{}}} -\subsection{Method \code{as_string()}}{ -Conversion helper for print outputs. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{Condition$as_string(lhs_chr = "x")}\if{html}{\out{
}} -} +\section{Functions}{ +\itemize{ +\item \code{condition_test()}: Used internally. Tests whether a value satisfies a given condition. +Vectorizes when \code{x} is atomic. -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{lhs_chr}}{(\code{character(1)})} -} -\if{html}{\out{
}} -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-Condition-format}{}}} -\subsection{Method \code{format()}}{ -Helper for print outputs. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{Condition$format(...)}\if{html}{\out{
}} -} +\item \code{condition_as_string()}: Used internally. Returns a string that represents the condition for pretty +printing, in the form \code{" "}, e.g. \code{"x == 3"} or +\code{"param \%in\% {1, 2, 10}"}. -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{...}}{(ignored).} -} -\if{html}{\out{
}} -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-Condition-print}{}}} -\subsection{Method \code{print()}}{ -Printer. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{Condition$print(...)}\if{html}{\out{
}} -} +}} +\section{Currently implemented simple conditions}{ -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{...}}{(ignored).} -} -\if{html}{\out{
}} -} +\itemize{ +\item \code{CondEqual(rhs)} \cr +Value must be equal to \code{rhs}. +\item \code{CondAnyOf(rhs)} \cr +Value must be any value of \code{rhs}. } -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-Condition-clone}{}}} -\subsection{Method \code{clone()}}{ -The objects of this class are cloneable with this method. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{Condition$clone(deep = FALSE)}\if{html}{\out{
}} } -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{deep}}{Whether to make a deep clone.} -} -\if{html}{\out{
}} -} -} -} diff --git a/man/Domain.Rd b/man/Domain.Rd index 37c7dfce..d0c25a03 100644 --- a/man/Domain.Rd +++ b/man/Domain.Rd @@ -1,43 +1,49 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/domain.R +% Please edit documentation in R/Domain.R, R/ParamDbl.R, R/ParamFct.R, +% R/ParamInt.R, R/ParamLgl.R, R/ParamUty.R \name{Domain} \alias{Domain} -\alias{p_int} \alias{p_dbl} -\alias{p_uty} -\alias{p_lgl} \alias{p_fct} +\alias{p_int} +\alias{p_lgl} +\alias{p_uty} \title{Domain: Parameter Range without an Id} \usage{ -p_int( +p_dbl( lower = -Inf, upper = Inf, special_vals = list(), default = NO_DEF, tags = character(), + tolerance = sqrt(.Machine$double.eps), depends = NULL, trafo = NULL, - logscale = FALSE + logscale = FALSE, + init ) -p_dbl( - lower = -Inf, - upper = Inf, +p_fct( + levels, special_vals = list(), default = NO_DEF, tags = character(), - tolerance = sqrt(.Machine$double.eps), depends = NULL, trafo = NULL, - logscale = FALSE + init ) -p_uty( +p_int( + lower = -Inf, + upper = Inf, + special_vals = list(), default = NO_DEF, tags = character(), - custom_check = NULL, + tolerance = sqrt(.Machine$double.eps), depends = NULL, - trafo = NULL + trafo = NULL, + logscale = FALSE, + init ) p_lgl( @@ -45,16 +51,19 @@ p_lgl( default = NO_DEF, tags = character(), depends = NULL, - trafo = NULL + trafo = NULL, + init ) -p_fct( - levels, +p_uty( + custom_check = NULL, special_vals = list(), default = NO_DEF, tags = character(), depends = NULL, - trafo = NULL + trafo = NULL, + repr = substitute(default), + init ) } \arguments{ @@ -87,12 +96,15 @@ purpose:\cr \code{values} in \link{ParamSet}. }} +\item{tolerance}{(\code{numeric(1)})\cr +Initializes the \verb{$tolerance} field that determines the} + \item{depends}{(\code{call} | \code{expression})\cr An expression indicating a requirement for the parameter that will be constructed from this. Can be given as an expression (using \code{quote()}), or the expression can be entered directly and will be parsed using NSE (see examples). The expression may be of the form \verb{ == } or \verb{ \%in\% }, which will result in -dependencies according to \verb{ParamSet$add_dep(on = "", cond = CondEqual$new())} or -\verb{ParamSet$add_dep(on = "", cond = CondAnyOf$new())}, respectively (see \code{\link{CondEqual}}, +dependencies according to \verb{ParamSet$add_dep(on = "", cond = CondEqual())} or +\verb{ParamSet$add_dep(on = "", cond = CondAnyOf())}, respectively (see \code{\link{CondEqual}}, \code{\link{CondAnyOf}}). The expression may also contain multiple conditions separated by \code{&&}.} \item{trafo}{(\code{function})\cr @@ -107,10 +119,10 @@ defining domains or hyperparameter ranges of learning algorithms, because these Put numeric domains on a log scale. Default \code{FALSE}. Log-scale \code{Domain}s represent parameter ranges where lower and upper bounds are logarithmized, and where a \code{trafo} is added that exponentiates sampled values to the original scale. This is \emph{not} the same as setting \code{trafo = exp}, because \code{logscale = TRUE} will handle parameter bounds internally: -a \code{p_dbl(1, 10, logscale = TRUE)} results in a \code{\link{ParamDbl}} that has lower bound \code{0}, upper bound \code{log(10)}, +a \code{p_dbl(1, 10, logscale = TRUE)} results in a parameter that has lower bound \code{0}, upper bound \code{log(10)}, and uses \code{exp} transformation on these. Therefore, the given bounds represent the bounds \emph{after} the transformation. (see examples).\cr -\code{p_int()} with \code{logscale = TRUE} results in a \code{\link{ParamDbl}}, not a \code{\link{ParamInt}}, but with bounds \code{log(max(lower, 0.5))} ... +\code{p_int()} with \code{logscale = TRUE} results in a continuous parameter similar to \code{p_dbl()}, not an integer-valued parameter, with bounds \code{log(max(lower, 0.5))} ... \code{log(upper + 1)} and a trafo similar to "\code{as.integer(exp(x))}" (with additional bounds correction). The lower bound is lifted to \code{0.5} if \code{lower} 0 to handle the \code{lower == 0} case. The upper bound is increased to \code{log(upper + 1)} because the trafo would otherwise almost never generate a value of \code{upper}.\cr @@ -123,8 +135,14 @@ defining domains or hyperparameter ranges of learning algorithms, because these \code{logscale} happens on a natural (\verb{e == 2.718282...}) basis. Be aware that using a different base (\code{log10()}/\verb{10^}, \code{log2()}/\verb{2^}) is completely equivalent and does not change the values being sampled after transformation.} -\item{tolerance}{(\code{numeric(1)})\cr -Initializes the \verb{$tolerance} field that determines the} +\item{init}{(\code{any})\cr +Initial value. When this is given, then the corresponding entry in \code{ParamSet$values} is initialized with this +value upon construction.} + +\item{levels}{(\code{character} | \code{atomic} | \code{list})\cr +Allowed categorical values of the parameter. If this is not a \code{character}, then a \code{trafo} is generated that +converts the names (if not given: \code{as.character()} of the values) of the \code{levels} argument to the values. +This trafo is then performed \emph{before} the function given as the \code{trafo} argument.} \item{custom_check}{(\verb{function()})\cr Custom function to check the feasibility. @@ -133,31 +151,30 @@ Must return 'TRUE' if the input is valid and a \code{character(1)} with the erro This function should \emph{not} throw an error. Defaults to \code{NULL}, which means that no check is performed.} -\item{levels}{(\code{character} | \code{atomic} | \code{list})\cr -Allowed categorical values of the parameter. If this is not a \code{character}, then a \code{trafo} is generated that -converts the names (if not given: \code{as.character()} of the values) of the \code{levels} argument to the values. -This trafo is then performed \emph{before} the function given as the \code{trafo} argument.} +\item{repr}{(\code{language})\cr +Symbol to use to represent the value given in \code{default}. +The \code{deparse()} of this object is used when printing the domain, in some cases.} } \value{ A \code{Domain} object. } \description{ A \code{Domain} object is a representation of a single dimension of a \code{\link{ParamSet}}. \code{Domain} objects are used to construct -\code{\link{ParamSet}}s, either through the \code{\link[=ps]{ps()}} short form, or through the \code{\link{ParamSet}}\verb{$search_space()} mechanism (see -\code{\link[=to_tune]{to_tune()}}). \code{Domain} corresponds to a \code{\link{Param}} object, except it does not have an \verb{$id}, and it \emph{does} have a -\code{trafo} and dependencies (\code{depends}) associated with it. For each of the basic \code{\link{Param}} classes (\code{\link{ParamInt}}, -\code{\link{ParamDbl}}, \code{\link{ParamLgl}}, \code{\link{ParamFct}}, and \code{\link{ParamUty}}) there is a function constructing a \code{Domain} object -(\code{p_int()}, \code{p_dbl()}, \code{p_lgl()}, \code{p_fct()}, \code{p_uty()}). They each have the same arguments as the corresponding -\code{\link{Param}} \verb{$new()} function, except without the \code{id} argument, and with the the additional parameters \code{trafo}, and -\code{depends}. +\code{\link{ParamSet}}s, either through the \code{\link[=ps]{ps()}} short form, through the \code{\link{ParamSet}} constructor itself, +or through the \code{\link{ParamSet}}\verb{$search_space()} mechanism (see +\code{\link[=to_tune]{to_tune()}}). +For each of the basic parameter classes (\code{"ParamInt"}, \code{"ParamDbl"}, \code{"ParamLgl"}, \code{"ParamFct"}, and \code{"ParamUty"}) there is a function constructing a \code{Domain} object +(\code{p_int()}, \code{p_dbl()}, \code{p_lgl()}, \code{p_fct()}, \code{p_uty()}). They each have fitting construction arguments that control their +bounds and behavior. \code{Domain} objects are representations of parameter ranges and are intermediate objects to be used in short form -constructions in \code{\link[=to_tune]{to_tune()}} and \code{\link[=ps]{ps()}}. Because of their nature, they should not be modified by the user. +constructions in \code{\link[=to_tune]{to_tune()}} and \code{\link[=ps]{ps()}}. Because of their nature, they should not be modified by the user, once constructed. The \code{Domain} object's internals are subject to change and should not be relied upon. } \details{ -The \code{p_fct} function admits a \code{levels} argument that goes beyond the \code{levels} accepted by \code{\link{ParamFct}}\verb{$new()}. -Instead of a \code{character} vector, any atomic vector or list (optionally named) may be given. (If the value is a list +Although the \code{levels} values of a constructed \code{p_fct()} will always be \code{character}-valued, the \code{p_fct} function admits +a \code{levels} argument that goes beyond this: +Besides a \code{character} vector, any atomic vector or list (optionally named) may be given. (If the value is a list that is not named, the names are inferred using \code{as.character()} on the values.) The resulting \code{Domain} will correspond to a range of values given by the names of the \code{levels} argument with a \code{trafo} that maps the \code{character} names to the arbitrary values of the \code{levels} argument. @@ -195,7 +212,7 @@ print(grid) # But the values are on a log scale with desired bounds after trafo print(grid$transpose()) -# Integer parameters with logscale are `ParamDbl`s pre-trafo +# Integer parameters with logscale are `p_dbl()`s pre-trafo params = ps(x = p_int(0, 10, logscale = TRUE)) print(params) diff --git a/man/NO_DEF.Rd b/man/NO_DEF.Rd index 3051f92c..e5308b7c 100644 --- a/man/NO_DEF.Rd +++ b/man/NO_DEF.Rd @@ -9,8 +9,7 @@ Special new data type for no-default. Not often needed by the end-user, mainly internal. \itemize{ -\item \code{NoDefault}: R6 factory. -\item \code{NO_DEF}: R6 Singleton object for type, used in \link{Param}. -\item \code{is_nodefault()}: Is an object of type 'no default'? +\item \code{NO_DEF}: Singleton object for type, used in \code{\link{Domain}} when no default is given. +\item \code{is_nodefault()}: Is an object the 'no default' object? } } diff --git a/man/Param.Rd b/man/Param.Rd deleted file mode 100644 index 27dbb43d..00000000 --- a/man/Param.Rd +++ /dev/null @@ -1,317 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/Param.R -\name{Param} -\alias{Param} -\title{Param Class} -\description{ -This is the abstract base class for parameter objects like \link{ParamDbl} and -\link{ParamFct}. -} -\section{S3 methods}{ - -\itemize{ -\item \code{as.data.table()}\cr -\link{Param} -> \code{\link[data.table:data.table]{data.table::data.table()}}\cr -Converts param to \code{\link[data.table:data.table]{data.table::data.table()}} with 1 row. See \link{ParamSet}. -} -} - -\seealso{ -Other Params: -\code{\link{ParamDbl}}, -\code{\link{ParamFct}}, -\code{\link{ParamInt}}, -\code{\link{ParamLgl}}, -\code{\link{ParamUty}} -} -\concept{Params} -\section{Public fields}{ -\if{html}{\out{
}} -\describe{ -\item{\code{id}}{(\code{character(1)})\cr -Identifier of the object.} - -\item{\code{description}}{(\code{character(1)})\cr -String to describe this parameter. Used, for example, in \code{\link[mlr3misc:rd_info]{mlr3misc::rd_info()}} to automatically -generate documentation for parameter sets.} - -\item{\code{special_vals}}{(\code{list()})\cr -Arbitrary special values this parameter is allowed to take.} - -\item{\code{default}}{(\code{any})\cr -Default value.} - -\item{\code{tags}}{(\code{character()})\cr -Arbitrary tags to group and subset parameters.} -} -\if{html}{\out{
}} -} -\section{Active bindings}{ -\if{html}{\out{
}} -\describe{ -\item{\code{class}}{(\code{character(1)})\cr -R6 class name. Read-only.} - -\item{\code{is_number}}{(\code{logical(1)})\cr -\code{TRUE} if the parameter is of type \code{"dbl"} or \code{"int"}.} - -\item{\code{is_categ}}{(\code{logical(1)})\cr -\code{TRUE} if the parameter is of type \code{"fct"} or \code{"lgl"}.} - -\item{\code{has_default}}{(\code{logical(1)})\cr -Is there a default value?} -} -\if{html}{\out{
}} -} -\section{Methods}{ -\subsection{Public methods}{ -\itemize{ -\item \href{#method-Param-new}{\code{Param$new()}} -\item \href{#method-Param-check}{\code{Param$check()}} -\item \href{#method-Param-assert}{\code{Param$assert()}} -\item \href{#method-Param-test}{\code{Param$test()}} -\item \href{#method-Param-rep}{\code{Param$rep()}} -\item \href{#method-Param-format}{\code{Param$format()}} -\item \href{#method-Param-print}{\code{Param$print()}} -\item \href{#method-Param-qunif}{\code{Param$qunif()}} -\item \href{#method-Param-convert}{\code{Param$convert()}} -\item \href{#method-Param-clone}{\code{Param$clone()}} -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-Param-new}{}}} -\subsection{Method \code{new()}}{ -Creates a new instance of this \link[R6:R6Class]{R6} class. - -Note that this object is typically constructed via derived classes, -e.g., \link{ParamDbl}. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{Param$new(id, special_vals, default, tags)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{id}}{(\code{character(1)})\cr -Identifier of the object.} - -\item{\code{special_vals}}{(\code{list()})\cr -Arbitrary special values this parameter is allowed to take, to make it -feasible. This allows extending the domain of the parameter. Note that -these values are only used in feasibility checks, neither in generating -designs nor sampling.} - -\item{\code{default}}{(\code{any})\cr -Default value. Can be from the domain of the parameter or an element of -\code{special_vals}. Has value \link{NO_DEF} if no default exists. \code{NULL} can be a -valid default. -The value has no effect on \code{ParamSet$values} or the behavior of -\code{ParamSet$check()}, \verb{$test()} or \verb{$assert()}. -The \code{default} is intended to be used for documentation purposes. -`} - -\item{\code{tags}}{(\code{character()})\cr -Arbitrary tags to group and subset parameters. Some tags serve a special -purpose:\cr -\itemize{ -\item \code{"required"} implies that the parameters has to be given when setting -\code{values} in \link{ParamSet}. -}} -} -\if{html}{\out{
}} -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-Param-check}{}}} -\subsection{Method \code{check()}}{ -\pkg{checkmate}-like check-function. Take a value from the domain of the -parameter, and check if it is feasible. A value is feasible if it is of -the same \code{storage_type}, inside of the bounds or element of -\code{special_vals}. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{Param$check(x)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{x}}{(\code{any}).} -} -\if{html}{\out{
}} -} -\subsection{Returns}{ -If successful \code{TRUE}, if not a string with the error message. -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-Param-assert}{}}} -\subsection{Method \code{assert()}}{ -\pkg{checkmate}-like assert-function. Take a value from the domain of -the parameter, and assert if it is feasible. A value is feasible if it -is of the same \code{storage_type}, inside of the bounds or element of -\code{special_vals}. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{Param$assert(x)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{x}}{(\code{any}).} -} -\if{html}{\out{
}} -} -\subsection{Returns}{ -If successful \code{x} invisibly, if not an exception is raised. -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-Param-test}{}}} -\subsection{Method \code{test()}}{ -\pkg{checkmate}-like test-function. Take a value from the domain of the -parameter, and test if it is feasible. A value is feasible if it is of -the same \code{storage_type}, inside of the bounds or element of -\code{special_vals}. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{Param$test(x)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{x}}{(\code{any}).} -} -\if{html}{\out{
}} -} -\subsection{Returns}{ -If successful \code{TRUE}, if not \code{FALSE}. -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-Param-rep}{}}} -\subsection{Method \code{rep()}}{ -Repeats this parameter n-times (by cloning). -Each parameter is named "[id]\emph{rep}[k]" and gets the additional tag "[id]_rep". -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{Param$rep(n)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{n}}{(\code{integer(1)}).} -} -\if{html}{\out{
}} -} -\subsection{Returns}{ -\link{ParamSet}. -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-Param-format}{}}} -\subsection{Method \code{format()}}{ -Helper for print outputs. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{Param$format(...)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{...}}{(ignored).} -} -\if{html}{\out{
}} -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-Param-print}{}}} -\subsection{Method \code{print()}}{ -Printer. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{Param$print( - ..., - hide_cols = c("nlevels", "is_bounded", "special_vals", "tags", "storage_type") -)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{...}}{(ignored).} - -\item{\code{hide_cols}}{(\code{character()})\cr -Which fields should not be printed? Default is \code{"nlevels"}, -\code{"is_bounded"}, \code{"special_vals"}, \code{"tags"}, and \code{"storage_type"}.} -} -\if{html}{\out{
}} -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-Param-qunif}{}}} -\subsection{Method \code{qunif()}}{ -Takes values from [0,1] and maps them, regularly distributed, to the -domain of the parameter. Think of: quantile function or the use case to -map a uniform-[0,1] random variable into a uniform sample from this -param. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{Param$qunif(x)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{x}}{(\code{numeric(1)}).} -} -\if{html}{\out{
}} -} -\subsection{Returns}{ -Value of the domain of the parameter. -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-Param-convert}{}}} -\subsection{Method \code{convert()}}{ -Converts a value to the closest valid param. Only for values that -pass \verb{$check()} and mostly used internally. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{Param$convert(x)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{x}}{(\code{any}).} -} -\if{html}{\out{
}} -} -\subsection{Returns}{ -\code{x} converted to a valid type for the \code{Param}. -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-Param-clone}{}}} -\subsection{Method \code{clone()}}{ -The objects of this class are cloneable with this method. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{Param$clone(deep = FALSE)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{deep}}{Whether to make a deep clone.} -} -\if{html}{\out{
}} -} -} -} diff --git a/man/ParamDbl.Rd b/man/ParamDbl.Rd deleted file mode 100644 index 02a0c5ae..00000000 --- a/man/ParamDbl.Rd +++ /dev/null @@ -1,191 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/ParamDbl.R -\name{ParamDbl} -\alias{ParamDbl} -\title{Numerical Parameter} -\description{ -A \link{Param} to describe real-valued parameters. -} -\note{ -The upper and lower bounds in \verb{$check()} are expanded by -\code{sqrt(.Machine$double.eps)} to prevent errors due to the precision of double -values. -} -\examples{ -ParamDbl$new("ratio", lower = 0, upper = 1, default = 0.5) -} -\seealso{ -Other Params: -\code{\link{ParamFct}}, -\code{\link{ParamInt}}, -\code{\link{ParamLgl}}, -\code{\link{ParamUty}}, -\code{\link{Param}} -} -\concept{Params} -\section{Super class}{ -\code{\link[paradox:Param]{paradox::Param}} -> \code{ParamDbl} -} -\section{Public fields}{ -\if{html}{\out{
}} -\describe{ -\item{\code{lower}}{(\code{numeric(1)})\cr -Lower bound. -Always \code{NA} for \link{ParamFct}, \link{ParamLgl} and \link{ParamUty}.} - -\item{\code{upper}}{(\code{numeric(1)})\cr -Upper bound. -Always \code{NA} for \link{ParamFct}, \link{ParamLgl} and \link{ParamUty}.} - -\item{\code{tolerance}}{(\code{numeric(1)})\cr -tolerance of values to accept beyond \verb{$lower} and \verb{$upper}. -Used both for relative and absolute tolerance.} -} -\if{html}{\out{
}} -} -\section{Active bindings}{ -\if{html}{\out{
}} -\describe{ -\item{\code{levels}}{(\code{character()} | \code{NULL})\cr -Set of allowed levels. -Always \code{NULL} for \link{ParamDbl}, \link{ParamInt} and \link{ParamUty}. -Always \code{c(TRUE, FALSE)} for \link{ParamLgl}.} - -\item{\code{nlevels}}{(\code{integer(1)} | \code{Inf})\cr -Number of categorical levels. -Always \code{Inf} for \link{ParamDbl} and \link{ParamUty}. -The number of integers in the range \verb{[lower, upper]}, or \code{Inf} if unbounded for \link{ParamInt}. -Always \code{2} for \link{ParamLgl}.} - -\item{\code{is_bounded}}{(\code{logical(1)})\cr -Are the bounds finite? -Always \code{TRUE} for \link{ParamFct} and \link{ParamLgl}. -Always \code{FALSE} for \link{ParamUty}.} - -\item{\code{storage_type}}{(\code{character(1)})\cr -Data type when values of this parameter are stored in a data table or sampled. -Always \code{"numeric"} for \link{ParamDbl}. -Always \code{"character"} for \link{ParamFct}. -Always \code{"integer"} for \link{ParamInt}. -Always \code{"logical"} for \link{ParamLgl}. -Always \code{"list"} for \link{ParamUty}.} -} -\if{html}{\out{
}} -} -\section{Methods}{ -\subsection{Public methods}{ -\itemize{ -\item \href{#method-ParamDbl-new}{\code{ParamDbl$new()}} -\item \href{#method-ParamDbl-convert}{\code{ParamDbl$convert()}} -\item \href{#method-ParamDbl-clone}{\code{ParamDbl$clone()}} -} -} -\if{html}{\out{ -
Inherited methods - -
-}} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-ParamDbl-new}{}}} -\subsection{Method \code{new()}}{ -Creates a new instance of this \link[R6:R6Class]{R6} class. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamDbl$new( - id, - lower = -Inf, - upper = Inf, - special_vals = list(), - default = NO_DEF, - tags = character(), - tolerance = sqrt(.Machine$double.eps) -)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{id}}{(\code{character(1)})\cr -Identifier of the object.} - -\item{\code{lower}}{(\code{numeric(1)})\cr -Lower bound, can be \code{-Inf}.} - -\item{\code{upper}}{(\code{numeric(1)})\cr -Upper bound can be \code{+Inf}.} - -\item{\code{special_vals}}{(\code{list()})\cr -Arbitrary special values this parameter is allowed to take, to make it -feasible. This allows extending the domain of the parameter. Note that -these values are only used in feasibility checks, neither in generating -designs nor sampling.} - -\item{\code{default}}{(\code{any})\cr -Default value. Can be from the domain of the parameter or an element of -\code{special_vals}. Has value \link{NO_DEF} if no default exists. \code{NULL} can be a -valid default. -The value has no effect on \code{ParamSet$values} or the behavior of -\code{ParamSet$check()}, \verb{$test()} or \verb{$assert()}. -The \code{default} is intended to be used for documentation purposes. -`} - -\item{\code{tags}}{(\code{character()})\cr -Arbitrary tags to group and subset parameters. Some tags serve a special -purpose:\cr -\itemize{ -\item \code{"required"} implies that the parameters has to be given when setting -\code{values} in \link{ParamSet}. -}} - -\item{\code{tolerance}}{(\code{numeric(1)})\cr -Initializes the \verb{$tolerance} field that determines the} -} -\if{html}{\out{
}} -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-ParamDbl-convert}{}}} -\subsection{Method \code{convert()}}{ -Restrict the value to within the allowed range. This works -in conjunction with \verb{$tolerance}, which accepts values -slightly out of this range. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamDbl$convert(x)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{x}}{(\code{numeric(1)})\cr -Value to convert.} -} -\if{html}{\out{
}} -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-ParamDbl-clone}{}}} -\subsection{Method \code{clone()}}{ -The objects of this class are cloneable with this method. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamDbl$clone(deep = FALSE)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{deep}}{Whether to make a deep clone.} -} -\if{html}{\out{
}} -} -} -} diff --git a/man/ParamFct.Rd b/man/ParamFct.Rd deleted file mode 100644 index f27abe83..00000000 --- a/man/ParamFct.Rd +++ /dev/null @@ -1,154 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/ParamFct.R -\name{ParamFct} -\alias{ParamFct} -\title{Factor Parameter} -\description{ -A \link{Param} to describe categorical (factor) parameters. -} -\examples{ -ParamFct$new("f", levels = letters[1:3]) -} -\seealso{ -Other Params: -\code{\link{ParamDbl}}, -\code{\link{ParamInt}}, -\code{\link{ParamLgl}}, -\code{\link{ParamUty}}, -\code{\link{Param}} -} -\concept{Params} -\section{Super class}{ -\code{\link[paradox:Param]{paradox::Param}} -> \code{ParamFct} -} -\section{Public fields}{ -\if{html}{\out{
}} -\describe{ -\item{\code{levels}}{(\code{character()} | \code{NULL})\cr -Set of allowed levels. -Always \code{NULL} for \link{ParamDbl}, \link{ParamInt} and \link{ParamUty}. -Always \code{c(TRUE, FALSE)} for \link{ParamLgl}.} -} -\if{html}{\out{
}} -} -\section{Active bindings}{ -\if{html}{\out{
}} -\describe{ -\item{\code{lower}}{(\code{numeric(1)})\cr -Lower bound. -Always \code{NA} for \link{ParamFct}, \link{ParamLgl} and \link{ParamUty}.} - -\item{\code{upper}}{(\code{numeric(1)})\cr -Upper bound. -Always \code{NA} for \link{ParamFct}, \link{ParamLgl} and \link{ParamUty}.} - -\item{\code{nlevels}}{(\code{integer(1)} | \code{Inf})\cr -Number of categorical levels. -Always \code{Inf} for \link{ParamDbl} and \link{ParamUty}. -The number of integers in the range \verb{[lower, upper]}, or \code{Inf} if unbounded for \link{ParamInt}. -Always \code{2} for \link{ParamLgl}.} - -\item{\code{is_bounded}}{(\code{logical(1)})\cr -Are the bounds finite? -Always \code{TRUE} for \link{ParamFct} and \link{ParamLgl}. -Always \code{FALSE} for \link{ParamUty}.} - -\item{\code{storage_type}}{(\code{character(1)})\cr -Data type when values of this parameter are stored in a data table or sampled. -Always \code{"numeric"} for \link{ParamDbl}. -Always \code{"character"} for \link{ParamFct}. -Always \code{"integer"} for \link{ParamInt}. -Always \code{"logical"} for \link{ParamLgl}. -Always \code{"list"} for \link{ParamUty}.} -} -\if{html}{\out{
}} -} -\section{Methods}{ -\subsection{Public methods}{ -\itemize{ -\item \href{#method-ParamFct-new}{\code{ParamFct$new()}} -\item \href{#method-ParamFct-clone}{\code{ParamFct$clone()}} -} -} -\if{html}{\out{ -
Inherited methods - -
-}} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-ParamFct-new}{}}} -\subsection{Method \code{new()}}{ -Creates a new instance of this \link[R6:R6Class]{R6} class. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamFct$new( - id, - levels, - special_vals = list(), - default = NO_DEF, - tags = character() -)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{id}}{(\code{character(1)})\cr -Identifier of the object.} - -\item{\code{levels}}{(\code{character()})\cr -Set of allowed levels.} - -\item{\code{special_vals}}{(\code{list()})\cr -Arbitrary special values this parameter is allowed to take, to make it -feasible. This allows extending the domain of the parameter. Note that -these values are only used in feasibility checks, neither in generating -designs nor sampling.} - -\item{\code{default}}{(\code{any})\cr -Default value. Can be from the domain of the parameter or an element of -\code{special_vals}. Has value \link{NO_DEF} if no default exists. \code{NULL} can be a -valid default. -The value has no effect on \code{ParamSet$values} or the behavior of -\code{ParamSet$check()}, \verb{$test()} or \verb{$assert()}. -The \code{default} is intended to be used for documentation purposes. -`} - -\item{\code{tags}}{(\code{character()})\cr -Arbitrary tags to group and subset parameters. Some tags serve a special -purpose:\cr -\itemize{ -\item \code{"required"} implies that the parameters has to be given when setting -\code{values} in \link{ParamSet}. -}} -} -\if{html}{\out{
}} -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-ParamFct-clone}{}}} -\subsection{Method \code{clone()}}{ -The objects of this class are cloneable with this method. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamFct$clone(deep = FALSE)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{deep}}{Whether to make a deep clone.} -} -\if{html}{\out{
}} -} -} -} diff --git a/man/ParamInt.Rd b/man/ParamInt.Rd deleted file mode 100644 index 50647d55..00000000 --- a/man/ParamInt.Rd +++ /dev/null @@ -1,181 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/ParamInt.R -\name{ParamInt} -\alias{ParamInt} -\title{Integer Parameter} -\description{ -A \link{Param} to describe integer parameters. -} -\section{Methods}{ - -See \link{Param}. -} - -\examples{ -ParamInt$new("count", lower = 0, upper = 10, default = 1) -} -\seealso{ -Other Params: -\code{\link{ParamDbl}}, -\code{\link{ParamFct}}, -\code{\link{ParamLgl}}, -\code{\link{ParamUty}}, -\code{\link{Param}} -} -\concept{Params} -\section{Super class}{ -\code{\link[paradox:Param]{paradox::Param}} -> \code{ParamInt} -} -\section{Public fields}{ -\if{html}{\out{
}} -\describe{ -\item{\code{lower}}{(\code{numeric(1)})\cr -Lower bound. -Always \code{NA} for \link{ParamFct}, \link{ParamLgl} and \link{ParamUty}.} - -\item{\code{upper}}{(\code{numeric(1)})\cr -Upper bound. -Always \code{NA} for \link{ParamFct}, \link{ParamLgl} and \link{ParamUty}.} -} -\if{html}{\out{
}} -} -\section{Active bindings}{ -\if{html}{\out{
}} -\describe{ -\item{\code{levels}}{(\code{character()} | \code{NULL})\cr -Set of allowed levels. -Always \code{NULL} for \link{ParamDbl}, \link{ParamInt} and \link{ParamUty}. -Always \code{c(TRUE, FALSE)} for \link{ParamLgl}.} - -\item{\code{nlevels}}{(\code{integer(1)} | \code{Inf})\cr -Number of categorical levels. -Always \code{Inf} for \link{ParamDbl} and \link{ParamUty}. -The number of integers in the range \verb{[lower, upper]}, or \code{Inf} if unbounded for \link{ParamInt}. -Always \code{2} for \link{ParamLgl}.} - -\item{\code{is_bounded}}{(\code{logical(1)})\cr -Are the bounds finite? -Always \code{TRUE} for \link{ParamFct} and \link{ParamLgl}. -Always \code{FALSE} for \link{ParamUty}.} - -\item{\code{storage_type}}{(\code{character(1)})\cr -Data type when values of this parameter are stored in a data table or sampled. -Always \code{"numeric"} for \link{ParamDbl}. -Always \code{"character"} for \link{ParamFct}. -Always \code{"integer"} for \link{ParamInt}. -Always \code{"logical"} for \link{ParamLgl}. -Always \code{"list"} for \link{ParamUty}.} -} -\if{html}{\out{
}} -} -\section{Methods}{ -\subsection{Public methods}{ -\itemize{ -\item \href{#method-ParamInt-new}{\code{ParamInt$new()}} -\item \href{#method-ParamInt-convert}{\code{ParamInt$convert()}} -\item \href{#method-ParamInt-clone}{\code{ParamInt$clone()}} -} -} -\if{html}{\out{ -
Inherited methods - -
-}} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-ParamInt-new}{}}} -\subsection{Method \code{new()}}{ -Creates a new instance of this \link[R6:R6Class]{R6} class. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamInt$new( - id, - lower = -Inf, - upper = Inf, - special_vals = list(), - default = NO_DEF, - tags = character() -)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{id}}{(\code{character(1)})\cr -Identifier of the object.} - -\item{\code{lower}}{(\code{numeric(1)})\cr -Lower bound, can be \code{-Inf}.} - -\item{\code{upper}}{(\code{numeric(1)})\cr -Upper bound can be \code{+Inf}.} - -\item{\code{special_vals}}{(\code{list()})\cr -Arbitrary special values this parameter is allowed to take, to make it -feasible. This allows extending the domain of the parameter. Note that -these values are only used in feasibility checks, neither in generating -designs nor sampling.} - -\item{\code{default}}{(\code{any})\cr -Default value. Can be from the domain of the parameter or an element of -\code{special_vals}. Has value \link{NO_DEF} if no default exists. \code{NULL} can be a -valid default. -The value has no effect on \code{ParamSet$values} or the behavior of -\code{ParamSet$check()}, \verb{$test()} or \verb{$assert()}. -The \code{default} is intended to be used for documentation purposes. -`} - -\item{\code{tags}}{(\code{character()})\cr -Arbitrary tags to group and subset parameters. Some tags serve a special -purpose:\cr -\itemize{ -\item \code{"required"} implies that the parameters has to be given when setting -\code{values} in \link{ParamSet}. -}} -} -\if{html}{\out{
}} -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-ParamInt-convert}{}}} -\subsection{Method \code{convert()}}{ -Converts a value to an integer. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamInt$convert(x)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{x}}{(\code{numeric(1)})\cr -Value to convert.} -} -\if{html}{\out{
}} -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-ParamInt-clone}{}}} -\subsection{Method \code{clone()}}{ -The objects of this class are cloneable with this method. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamInt$clone(deep = FALSE)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{deep}}{Whether to make a deep clone.} -} -\if{html}{\out{
}} -} -} -} diff --git a/man/ParamLgl.Rd b/man/ParamLgl.Rd deleted file mode 100644 index 243d27d1..00000000 --- a/man/ParamLgl.Rd +++ /dev/null @@ -1,140 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/ParamLgl.R -\name{ParamLgl} -\alias{ParamLgl} -\title{Logical Parameter} -\description{ -A \link{Param} to describe logical parameters. -} -\examples{ -ParamLgl$new("flag", default = TRUE) -} -\seealso{ -Other Params: -\code{\link{ParamDbl}}, -\code{\link{ParamFct}}, -\code{\link{ParamInt}}, -\code{\link{ParamUty}}, -\code{\link{Param}} -} -\concept{Params} -\section{Super class}{ -\code{\link[paradox:Param]{paradox::Param}} -> \code{ParamLgl} -} -\section{Active bindings}{ -\if{html}{\out{
}} -\describe{ -\item{\code{lower}}{(\code{numeric(1)})\cr -Lower bound. -Always \code{NA} for \link{ParamFct}, \link{ParamLgl} and \link{ParamUty}.} - -\item{\code{upper}}{(\code{numeric(1)})\cr -Upper bound. -Always \code{NA} for \link{ParamFct}, \link{ParamLgl} and \link{ParamUty}.} - -\item{\code{levels}}{(\code{character()} | \code{NULL})\cr -Set of allowed levels. -Always \code{NULL} for \link{ParamDbl}, \link{ParamInt} and \link{ParamUty}. -Always \code{c(TRUE, FALSE)} for \link{ParamLgl}.} - -\item{\code{nlevels}}{(\code{integer(1)} | \code{Inf})\cr -Number of categorical levels. -Always \code{Inf} for \link{ParamDbl} and \link{ParamUty}. -The number of integers in the range \verb{[lower, upper]}, or \code{Inf} if unbounded for \link{ParamInt}. -Always \code{2} for \link{ParamLgl}.} - -\item{\code{is_bounded}}{(\code{logical(1)})\cr -Are the bounds finite? -Always \code{TRUE} for \link{ParamFct} and \link{ParamLgl}. -Always \code{FALSE} for \link{ParamUty}.} - -\item{\code{storage_type}}{(\code{character(1)})\cr -Data type when values of this parameter are stored in a data table or sampled. -Always \code{"numeric"} for \link{ParamDbl}. -Always \code{"character"} for \link{ParamFct}. -Always \code{"integer"} for \link{ParamInt}. -Always \code{"logical"} for \link{ParamLgl}. -Always \code{"list"} for \link{ParamUty}.} -} -\if{html}{\out{
}} -} -\section{Methods}{ -\subsection{Public methods}{ -\itemize{ -\item \href{#method-ParamLgl-new}{\code{ParamLgl$new()}} -\item \href{#method-ParamLgl-clone}{\code{ParamLgl$clone()}} -} -} -\if{html}{\out{ -
Inherited methods - -
-}} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-ParamLgl-new}{}}} -\subsection{Method \code{new()}}{ -Creates a new instance of this \link[R6:R6Class]{R6} class. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamLgl$new(id, special_vals = list(), default = NO_DEF, tags = character())}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{id}}{(\code{character(1)})\cr -Identifier of the object.} - -\item{\code{special_vals}}{(\code{list()})\cr -Arbitrary special values this parameter is allowed to take, to make it -feasible. This allows extending the domain of the parameter. Note that -these values are only used in feasibility checks, neither in generating -designs nor sampling.} - -\item{\code{default}}{(\code{any})\cr -Default value. Can be from the domain of the parameter or an element of -\code{special_vals}. Has value \link{NO_DEF} if no default exists. \code{NULL} can be a -valid default. -The value has no effect on \code{ParamSet$values} or the behavior of -\code{ParamSet$check()}, \verb{$test()} or \verb{$assert()}. -The \code{default} is intended to be used for documentation purposes. -`} - -\item{\code{tags}}{(\code{character()})\cr -Arbitrary tags to group and subset parameters. Some tags serve a special -purpose:\cr -\itemize{ -\item \code{"required"} implies that the parameters has to be given when setting -\code{values} in \link{ParamSet}. -}} -} -\if{html}{\out{
}} -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-ParamLgl-clone}{}}} -\subsection{Method \code{clone()}}{ -The objects of this class are cloneable with this method. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamLgl$clone(deep = FALSE)}\if{html}{\out{
}} -} - -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{deep}}{Whether to make a deep clone.} -} -\if{html}{\out{
}} -} -} -} diff --git a/man/ParamSet.Rd b/man/ParamSet.Rd index 917c60aa..b74daebc 100644 --- a/man/ParamSet.Rd +++ b/man/ParamSet.Rd @@ -4,26 +4,35 @@ \alias{ParamSet} \title{ParamSet} \description{ -A set of \link{Param} objects. -Please note that when creating a set or adding to it, the parameters of the -resulting set have to be uniquely named with IDs with valid R names. -The set also contains a member variable \code{values} which can be used to store an active configuration / -or to partially fix -some parameters to constant values (regarding subsequent sampling or generation of designs). +An object representing the space of possible parametrizations of a function or another object. +\code{ParamSet}s are used on the side of objects being parameterized, where they function as a configuration space determining the set of possible configurations accepted by these objects. +They can also be used to specify search spaces for optimization, indicating the set of legal configurations to try out. +It is often convenient to generate search spaces from configuration spaces, which can be done using the \verb{$search_space()} method in combination with \code{to_tune()} / \code{\link{TuneToken}} objects. + +Individual dimensions of a \code{ParamSet} are specified by \code{\link{Domain}} objects, created as \code{\link[=p_dbl]{p_dbl()}}, \code{\link[=p_lgl]{p_lgl()}} etc. +The field \verb{$values} can be used to store an active configuration or to partially fix +some parameters to constant values -- the precise effect can be determined by the object being parameterized. + +Constructing a \code{ParamSet} can be done using \code{ParamSet$new()} in combination with a named list of \code{\link{Domain}} objects. +This route is recommended when the set of dimensions (i.e. the members of this named list) is dynamically created, such as when the number of parameters is variable. +\code{ParamSet}s can also be created using the \code{\link[=ps]{ps()}} shorthand, which is the recommended way when the set of parameters is fixed. +In practice, the majority of cases where a \code{ParamSet} is created, the \code{\link[=ps]{ps()}} should be used. } \section{S3 methods and type converters}{ \itemize{ \item \code{as.data.table()}\cr -\link{ParamSet} -> \code{\link[data.table:data.table]{data.table::data.table()}}\cr +\code{ParamSet} -> \code{\link[data.table:data.table]{data.table::data.table()}}\cr Compact representation as datatable. Col types are:\cr \itemize{ \item id: character -\item lower, upper: double +\item class: character +\item lower, upper: numeric \item levels: list col, with NULL elements -\item special_vals: list col of list +\item nlevels: integer valued numeric \item is_bounded: logical -\item default: list col, with NULL elements +\item special_vals: list col of list +\item default: list col \item storage_type: character \item tags: list col of character vectors } @@ -31,21 +40,23 @@ Compact representation as datatable. Col types are:\cr } \examples{ -ps = ParamSet$new( +pset = ParamSet$new( params = list( - ParamDbl$new("d", lower = -5, upper = 5, default = 0), - ParamFct$new("f", levels = letters[1:3]) + d = p_dbl(lower = -5, upper = 5, default = 0, trafo = function(x) 2^x), + f = p_fct(levels = letters[1:3]) ) ) -ps$trafo = function(x, param_set) { - x$d = 2^x$d - return(x) -} +# alternative, recommended way of construction in this case since the +# parameter list is not dynamic: +pset = ps( + d = p_dbl(lower = -5, upper = 5, default = 0, trafo = function(x) 2^x), + f = p_fct(levels = letters[1:3]) +) -ps$add(ParamInt$new("i", lower = 0L, upper = 16L)) +pset$check(list(d = 2.1, f = "a")) -ps$check(list(d = 2.1, f = "a", i = 3L)) +pset$check(list(d = 2.1, f = "d")) } \section{Public fields}{ \if{html}{\out{
}} @@ -59,14 +70,41 @@ Default is \code{TRUE}, only switch this off if you know what you are doing.} \section{Active bindings}{ \if{html}{\out{
}} \describe{ +\item{\code{data}}{(\code{data.table}) \code{data.table} representation of the \code{ParamSet}.} + +\item{\code{values}}{(named \code{list()})\cr +Currently set / fixed parameter values. +Settable, and feasibility of values will be checked when you set them. +You do not have to set values for all parameters, but only for a subset. +When you set values, all previously set values will be unset / removed.} + +\item{\code{tags}}{(named \code{list()} of \code{character()})\cr +Can be used to group and subset parameters. +Named with parameter IDs.} + \item{\code{params}}{(named \code{list()})\cr -List of \link{Param}, named with their respective ID.} +\code{data.table} representing the combined \code{\link{Domain}} objects used to construct the \code{\link{ParamSet}}. +Used for internal purpuses. +Its use by external code is deprecated.} + +\item{\code{domains}}{(named \code{list} of \code{\link{Domain}}) +List of \code{\link{Domain}} objects that could be used to initialize this \code{ParamSet}.} + +\item{\code{extra_trafo}}{(\verb{function(x, param_set)})\cr +Transformation function. Settable. +User has to pass a \verb{function(x)}, of the form\cr +(named \code{list()}, \link{ParamSet}) -> named \code{list()}.\cr +The function is responsible to transform a feasible configuration into another encoding, +before potentially evaluating the configuration with the target algorithm. +For the output, not many things have to hold. +It needs to have unique names, and the target algorithm has to accept the configuration. +For convenience, the self-paramset is also passed in, if you need some info from it (e.g. tags). +Is NULL by default, and you can set it to NULL to switch the transformation off.} -\item{\code{params_unid}}{(named \code{list()})\cr -List of \link{Param}, named with their true ID. However, -this field has the \link{Param}'s \verb{$id} value set to a -potentially invalid value. This active binding should -only be used internally.} +\item{\code{constraint}}{(\verb{function(x)})\cr +Constraint function. Settable. +This function must evaluate a named \code{list()} of values and determine whether it satisfies +constraints, returning a scalar \code{logical(1)} value.} \item{\code{deps}}{(\code{\link[data.table:data.table]{data.table::data.table()}})\cr Table has cols \code{id} (\code{character(1)}) and \code{on} (\code{character(1)}) and \code{cond} (\link{Condition}). @@ -74,92 +112,55 @@ Lists all (direct) dependency parents of a param, through parameter IDs. Internally created by a call to \code{add_dep}. Settable, if you want to remove dependencies or perform other changes.} -\item{\code{set_id}}{(\code{character(1)})\cr -ID of this param set. Default \code{""}. Settable.} +\item{\code{length}}{(\code{integer(1)})\cr Number of contained parameters.} -\item{\code{length}}{(\code{integer(1)})\cr -Number of contained \link{Param}s.} +\item{\code{is_empty}}{(\code{logical(1)})\cr Is the \code{ParamSet} empty? Named with parameter IDs.} -\item{\code{is_empty}}{(\code{logical(1)})\cr -Is the \code{ParamSet} empty?} +\item{\code{has_trafo}}{(\code{logical(1)})\cr Whether a \code{trafo} function is present, in parameters or in \code{extra_trafo}.} -\item{\code{class}}{(named \code{character()})\cr -Classes of contained parameters, named with parameter IDs.} +\item{\code{has_extra_trafo}}{(\code{logical(1)})\cr Whether \code{extra_trafo} is set.} -\item{\code{lower}}{(named \code{double()})\cr -Lower bounds of parameters (\code{NA} if parameter is not numeric). -Named with parameter IDs.} +\item{\code{has_deps}}{(\code{logical(1)})\cr Whether the parameter dependencies are present} -\item{\code{upper}}{(named \code{double()})\cr -Upper bounds of parameters (\code{NA} if parameter is not numeric). -Named with parameter IDs.} +\item{\code{has_constraint}}{(\code{logical(1)})\cr Whether parameter constraint is set.} -\item{\code{levels}}{(named \code{list()})\cr -List of character vectors of allowed categorical values of contained parameters. -\code{NULL} if the parameter is not categorical. -Named with parameter IDs.} +\item{\code{all_numeric}}{(\code{logical(1)})\cr Is \code{TRUE} if all parameters are \code{\link[=p_dbl]{p_dbl()}} or \code{\link[=p_int]{p_int()}}.} -\item{\code{nlevels}}{(named \code{integer()})\cr -Number of categorical levels per parameter, \code{Inf} for double parameters or unbounded integer parameters. -Named with param IDs.} +\item{\code{all_categorical}}{(\code{logical(1)})\cr Is \code{TRUE} if all parameters are \code{\link[=p_fct]{p_fct()}} and \code{\link[=p_lgl]{p_lgl()}}.} -\item{\code{is_bounded}}{(named \code{logical()})\cr -Do all parameters have finite bounds? -Named with parameter IDs.} +\item{\code{all_bounded}}{(\code{logical(1)})\cr Is \code{TRUE} if all parameters are bounded.} -\item{\code{special_vals}}{(named \code{list()} of \code{list()})\cr -Special values for all parameters. -Named with parameter IDs.} +\item{\code{class}}{(named \code{character()})\cr Classes of contained parameters. Named with parameter IDs.} -\item{\code{default}}{(named \code{list()})\cr -Default values of all parameters. -If no default exists, element is not present. -Named with parameter IDs.} +\item{\code{lower}}{(named \code{double()})\cr Lower bounds of numeric parameters (\code{NA} for non-numerics). Named with parameter IDs.} -\item{\code{tags}}{(named \code{list()} of \code{character()})\cr -Can be used to group and subset parameters. -Named with parameter IDs.} +\item{\code{upper}}{(named \code{double()})\cr Upper bounds of numeric parameters (\code{NA} for non-numerics). Named with parameter IDs.} -\item{\code{storage_type}}{(\code{character()})\cr -Data types of parameters when stored in tables. +\item{\code{levels}}{(named \code{list()} of \code{character})\cr Allowed levels of categorical parameters (\code{NULL} for non-categoricals). Named with parameter IDs.} -\item{\code{is_number}}{(named \code{logical()})\cr -Position is TRUE for \link{ParamDbl} and \link{ParamInt}. -Named with parameter IDs.} +\item{\code{storage_type}}{(\code{character()})\cr Data types of parameters when stored in tables. Named with parameter IDs.} + +\item{\code{special_vals}}{(named \code{list()} of \code{list()})\cr Special values for all parameters. Named with parameter IDs.} -\item{\code{is_categ}}{(named \code{logical()})\cr -Position is TRUE for \link{ParamFct} and \link{ParamLgl}. +\item{\code{default}}{(named \code{list()})\cr Default values of all parameters. If no default exists, element is not present. Named with parameter IDs.} -\item{\code{all_numeric}}{(\code{logical(1)})\cr -Is \code{TRUE} if all parameters are \link{ParamDbl} or \link{ParamInt}.} +\item{\code{has_trafo_param}}{(\code{logical()})\cr Whether \code{trafo} is set for any parameter.} -\item{\code{all_categorical}}{(\code{logical(1)})\cr -Is \code{TRUE} if all parameters are \link{ParamFct} and \link{ParamLgl}.} +\item{\code{is_logscale}}{(\code{logical()})\cr Whether \code{trafo} was set to \code{logscale} during construction.\cr +Note that this only refers to the \code{logscale} flag set during construction, e.g. \code{p_dbl(logscale = TRUE)}. +If the parameter was set to logscale manually, e.g. through \code{p_dbl(trafo = exp)}, +this \code{is_logscale} will be \code{FALSE}.} -\item{\code{trafo}}{(\verb{function(x, param_set)})\cr -Transformation function. Settable. -User has to pass a \verb{function(x, param_set)}, of the form\cr -(named \code{list()}, \link{ParamSet}) -> named \code{list()}.\cr -The function is responsible to transform a feasible configuration into another encoding, -before potentially evaluating the configuration with the target algorithm. -For the output, not many things have to hold. -It needs to have unique names, and the target algorithm has to accept the configuration. -For convenience, the self-paramset is also passed in, if you need some info from it (e.g. tags). -Is NULL by default, and you can set it to NULL to switch the transformation off.} +\item{\code{nlevels}}{(named \code{integer()})\cr Number of distinct levels of parameters. \code{Inf} for double parameters or unbounded integer parameters. +Named with param IDs.} -\item{\code{has_trafo}}{(\code{logical(1)})\cr -Has the set a \code{trafo} function?} +\item{\code{is_number}}{(named \code{logical()})\cr Whether parameter is \code{\link[=p_dbl]{p_dbl()}} or \code{\link[=p_int]{p_int()}}. Named with parameter IDs.} -\item{\code{values}}{(named \code{list()})\cr -Currently set / fixed parameter values. -Settable, and feasibility of values will be checked when you set them. -You do not have to set values for all parameters, but only for a subset. -When you set values, all previously set values will be unset / removed.} +\item{\code{is_categ}}{(named \code{logical()})\cr Whether parameter is \code{\link[=p_fct]{p_fct()}} or \code{\link[=p_lgl]{p_lgl()}}. Named with parameter IDs.} -\item{\code{has_deps}}{(\code{logical(1)})\cr -Has the set parameter dependencies?} +\item{\code{is_bounded}}{(named \code{logical()})\cr Whether parameters have finite bounds. Named with parameter IDs.} } \if{html}{\out{
}} } @@ -167,18 +168,25 @@ Has the set parameter dependencies?} \subsection{Public methods}{ \itemize{ \item \href{#method-ParamSet-new}{\code{ParamSet$new()}} -\item \href{#method-ParamSet-add}{\code{ParamSet$add()}} \item \href{#method-ParamSet-ids}{\code{ParamSet$ids()}} \item \href{#method-ParamSet-get_values}{\code{ParamSet$get_values()}} \item \href{#method-ParamSet-set_values}{\code{ParamSet$set_values()}} -\item \href{#method-ParamSet-subset}{\code{ParamSet$subset()}} -\item \href{#method-ParamSet-search_space}{\code{ParamSet$search_space()}} +\item \href{#method-ParamSet-trafo}{\code{ParamSet$trafo()}} +\item \href{#method-ParamSet-test_constraint}{\code{ParamSet$test_constraint()}} +\item \href{#method-ParamSet-test_constraint_dt}{\code{ParamSet$test_constraint_dt()}} \item \href{#method-ParamSet-check}{\code{ParamSet$check()}} +\item \href{#method-ParamSet-check_dependencies}{\code{ParamSet$check_dependencies()}} \item \href{#method-ParamSet-test}{\code{ParamSet$test()}} \item \href{#method-ParamSet-assert}{\code{ParamSet$assert()}} \item \href{#method-ParamSet-check_dt}{\code{ParamSet$check_dt()}} \item \href{#method-ParamSet-test_dt}{\code{ParamSet$test_dt()}} \item \href{#method-ParamSet-assert_dt}{\code{ParamSet$assert_dt()}} +\item \href{#method-ParamSet-qunif}{\code{ParamSet$qunif()}} +\item \href{#method-ParamSet-get_domain}{\code{ParamSet$get_domain()}} +\item \href{#method-ParamSet-subset}{\code{ParamSet$subset()}} +\item \href{#method-ParamSet-subspaces}{\code{ParamSet$subspaces()}} +\item \href{#method-ParamSet-flatten}{\code{ParamSet$flatten()}} +\item \href{#method-ParamSet-search_space}{\code{ParamSet$search_space()}} \item \href{#method-ParamSet-add_dep}{\code{ParamSet$add_dep()}} \item \href{#method-ParamSet-format}{\code{ParamSet$format()}} \item \href{#method-ParamSet-print}{\code{ParamSet$print()}} @@ -191,32 +199,20 @@ Has the set parameter dependencies?} \subsection{Method \code{new()}}{ Creates a new instance of this \link[R6:R6Class]{R6} class. \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamSet$new(params = named_list())}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{ParamSet$new(params = named_list(), allow_dangling_dependencies = FALSE)}\if{html}{\out{
}} } \subsection{Arguments}{ \if{html}{\out{
}} \describe{ -\item{\code{params}}{(\code{list()})\cr -List of \link{Param}, named with their respective ID. -Parameters are cloned.} -} -\if{html}{\out{
}} -} -} -\if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-ParamSet-add}{}}} -\subsection{Method \code{add()}}{ -Adds a single param or another set to this set, all params are cloned. -\subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamSet$add(p)}\if{html}{\out{
}} -} +\item{\code{params}}{(named \code{list()})\cr +List of \code{\link{Domain}}, named with their respective ID.} -\subsection{Arguments}{ -\if{html}{\out{
}} -\describe{ -\item{\code{p}}{(\link{Param} | \link{ParamSet}).} +\item{\code{allow_dangling_dependencies}}{(\code{character(1)})\cr +Whether dependencies depending on parameters that are not present should be allowed. A parameter \code{x} having +\code{depends = y == 0} if \code{y} is not present would usually throw an error, but if dangling +dependencies are allowed, the dependency is added regardless. This is mainly for internal +use.} } \if{html}{\out{
}} } @@ -229,17 +225,22 @@ Retrieves IDs of contained parameters based on some filter criteria selections, \code{NULL} means no restriction. Only returns IDs of parameters that satisfy all conditions. \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamSet$ids(class = NULL, is_bounded = NULL, tags = NULL)}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{ParamSet$ids(class = NULL, tags = NULL, any_tags = NULL)}\if{html}{\out{
}} } \subsection{Arguments}{ \if{html}{\out{
}} \describe{ -\item{\code{class}}{(\code{character()}).} +\item{\code{class}}{(\code{character()})\cr +Typically a subset of \code{"ParamDbl"}, \code{"ParamInt"}, \code{"ParamFct"}, \code{"ParamLgl"}, \code{"ParamUty"}. +Other classes are possible if implemented by 3rd party packages. +Return only IDs of dimensions with the given class.} -\item{\code{is_bounded}}{(\code{logical(1)}).} +\item{\code{tags}}{(\code{character()}). +Return only IDs of dimensions that have \emph{all} tags given in this argument.} -\item{\code{tags}}{(\code{character()}).} +\item{\code{any_tags}}{(\code{character()}). +Return only IDs of dimensions that have at least one of the tags given in this argument.} } \if{html}{\out{
}} } @@ -257,27 +258,31 @@ Only returns values of parameters that satisfy all conditions. \subsection{Usage}{ \if{html}{\out{
}}\preformatted{ParamSet$get_values( class = NULL, - is_bounded = NULL, tags = NULL, + any_tags = NULL, type = "with_token", - check_required = TRUE + check_required = TRUE, + remove_dependencies = TRUE )}\if{html}{\out{
}} } \subsection{Arguments}{ \if{html}{\out{
}} \describe{ -\item{\code{class}}{(\code{character()}).} +\item{\code{class}}{(\code{character()}). See \verb{$ids()}.} -\item{\code{is_bounded}}{(\code{logical(1)}).} +\item{\code{tags}}{(\code{character()}). See \verb{$ids()}.} -\item{\code{tags}}{(\code{character()}).} +\item{\code{any_tags}}{(\code{character()}). See \verb{$ids()}.} \item{\code{type}}{(\code{character(1)})\cr -Return values \code{with_token}, \code{without_token} or \code{only_token}?} +Return values \code{"with_token"} (i.e. all values),} \item{\code{check_required}}{(\code{logical(1)})\cr Check if all required parameters are set?} + +\item{\code{remove_dependencies}}{(\code{logical(1)})\cr +If \code{TRUE}, set values with dependencies that are not fulfilled to \code{NULL}.} } \if{html}{\out{
}} } @@ -312,38 +317,83 @@ replace all values. Default is TRUE.} } } \if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-ParamSet-subset}{}}} -\subsection{Method \code{subset()}}{ -Changes the current set to the set of passed IDs. +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-ParamSet-trafo}{}}} +\subsection{Method \code{trafo()}}{ +Perform transformation specified by the \code{trafo} of \code{\link{Domain}} objects, as well as the \verb{$extra_trafo} field. \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamSet$subset(ids)}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{ParamSet$trafo(x, param_set = self)}\if{html}{\out{
}} } \subsection{Arguments}{ \if{html}{\out{
}} \describe{ -\item{\code{ids}}{(\code{character()}).} +\item{\code{x}}{(named \code{list()} | \code{data.frame})\cr +The value(s) to be transformed.} + +\item{\code{param_set}}{(\code{ParamSet})\cr +Passed to \code{extra_trafo()}. Note that the \code{extra_trafo} of \code{self} is used, not the \code{extra_trafo} of the +\code{ParamSet} given in the \code{param_set} argument. +In almost all cases, the default \code{param_set = self} should be used.} } \if{html}{\out{
}} } } \if{html}{\out{
}} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-ParamSet-search_space}{}}} -\subsection{Method \code{search_space()}}{ -Construct a \code{\link{ParamSet}} to tune over. Constructed from \code{\link{TuneToken}} in \verb{$values}, see \code{\link[=to_tune]{to_tune()}}. +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-ParamSet-test_constraint}{}}} +\subsection{Method \code{test_constraint()}}{ +\pkg{checkmate}-like test-function. Takes a named list. +Return \code{FALSE} if the given \verb{$constraint} is not satisfied, \code{TRUE} otherwise. +Note this is different from satisfying the bounds or types given by the \code{ParamSet} itself: +If \code{x} does not satisfy these, an error will be thrown, given that \code{assert_value} is \code{TRUE}. \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamSet$search_space(values = self$values)}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{ParamSet$test_constraint(x, assert_value = TRUE)}\if{html}{\out{
}} } \subsection{Arguments}{ \if{html}{\out{
}} \describe{ -\item{\code{values}}{(\verb{named list}): optional named list of \code{\link{TuneToken}} objects to convert, in place of \verb{$values}.} +\item{\code{x}}{(named \code{list()})\cr +The value to test.} + +\item{\code{assert_value}}{(\code{logical(1)})\cr +Whether to verify that \code{x} satisfies the bounds and types given by this \code{ParamSet}. +Should be \code{TRUE} unless this was already checked before.} +} +\if{html}{\out{
}} +} +\subsection{Returns}{ +\code{logical(1)}: Whether \code{x} satisfies the \verb{$constraint}. +} +} +\if{html}{\out{
}} +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-ParamSet-test_constraint_dt}{}}} +\subsection{Method \code{test_constraint_dt()}}{ +\pkg{checkmate}-like test-function. Takes a \code{\link{data.table}}. +For each row, return \code{FALSE} if the given \verb{$constraint} is not satisfied, \code{TRUE} otherwise. +Note this is different from satisfying the bounds or types given by the \code{ParamSet} itself: +If \code{x} does not satisfy these, an error will be thrown, given that \code{assert_value} is \code{TRUE}. +\subsection{Usage}{ +\if{html}{\out{
}}\preformatted{ParamSet$test_constraint_dt(x, assert_value = TRUE)}\if{html}{\out{
}} +} + +\subsection{Arguments}{ +\if{html}{\out{
}} +\describe{ +\item{\code{x}}{(\code{data.table})\cr +The values to test.} + +\item{\code{assert_value}}{(\code{logical(1)})\cr +Whether to verify that \code{x} satisfies the bounds and types given by this \code{ParamSet}. +Should be \code{TRUE} unless this was already checked before.} } \if{html}{\out{
}} } +\subsection{Returns}{ +\code{logical}: For each row in \code{x}, whether it satisfies the \verb{$constraint}. +} } \if{html}{\out{
}} \if{html}{\out{}} @@ -353,19 +403,44 @@ Construct a \code{\link{ParamSet}} to tune over. Constructed from \code{\link{Tu A point x is feasible, if it configures a subset of params, all individual param constraints are satisfied and all dependencies are satisfied. Params for which dependencies are not satisfied should not be part of \code{x}. +Constraints and dependencies are not checked when \code{check_strict} is \code{FALSE}. \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamSet$check(xs)}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{ParamSet$check(xs, check_strict = TRUE)}\if{html}{\out{
}} } \subsection{Arguments}{ \if{html}{\out{
}} \describe{ \item{\code{xs}}{(named \code{list()}).} + +\item{\code{check_strict}}{(\code{logical(1)})\cr +Whether to check that constraints and dependencies are satisfied.} } \if{html}{\out{
}} } \subsection{Returns}{ -If successful \code{TRUE}, if not a string with the error message. +If successful \code{TRUE}, if not a string with an error message. +} +} +\if{html}{\out{
}} +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-ParamSet-check_dependencies}{}}} +\subsection{Method \code{check_dependencies()}}{ +\pkg{checkmate}-like check-function. Takes a named list. +Checks that all individual param dependencies are satisfied. +\subsection{Usage}{ +\if{html}{\out{
}}\preformatted{ParamSet$check_dependencies(xs)}\if{html}{\out{
}} +} + +\subsection{Arguments}{ +\if{html}{\out{
}} +\describe{ +\item{\code{xs}}{(named \code{list()}).} +} +\if{html}{\out{
}} +} +\subsection{Returns}{ +If successful \code{TRUE}, if not a string with an error message. } } \if{html}{\out{
}} @@ -376,14 +451,18 @@ If successful \code{TRUE}, if not a string with the error message. A point x is feasible, if it configures a subset of params, all individual param constraints are satisfied and all dependencies are satisfied. Params for which dependencies are not satisfied should not be part of \code{x}. +Constraints and dependencies are not checked when \code{check_strict} is \code{FALSE}. \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamSet$test(xs)}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{ParamSet$test(xs, check_strict = TRUE)}\if{html}{\out{
}} } \subsection{Arguments}{ \if{html}{\out{
}} \describe{ \item{\code{xs}}{(named \code{list()}).} + +\item{\code{check_strict}}{(\code{logical(1)})\cr +Whether to check that constraints and dependencies are satisfied.} } \if{html}{\out{
}} } @@ -399,8 +478,9 @@ If successful \code{TRUE}, if not \code{FALSE}. A point x is feasible, if it configures a subset of params, all individual param constraints are satisfied and all dependencies are satisfied. Params for which dependencies are not satisfied should not be part of \code{x}. +Constraints and dependencies are not checked when \code{check_strict} is \code{FALSE}. \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamSet$assert(xs, .var.name = vname(xs))}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{ParamSet$assert(xs, check_strict = TRUE, .var.name = vname(xs))}\if{html}{\out{
}} } \subsection{Arguments}{ @@ -408,6 +488,9 @@ Params for which dependencies are not satisfied should not be part of \code{x}. \describe{ \item{\code{xs}}{(named \code{list()}).} +\item{\code{check_strict}}{(\code{logical(1)})\cr +Whether to check that constraints and dependencies are satisfied.} + \item{\code{.var.name}}{(\code{character(1)})\cr Name of the checked object to print in error messages.\cr Defaults to the heuristic implemented in \link[checkmate:vname]{vname}.} @@ -423,18 +506,22 @@ If successful \code{xs} invisibly, if not an error message. \if{latex}{\out{\hypertarget{method-ParamSet-check_dt}{}}} \subsection{Method \code{check_dt()}}{ \pkg{checkmate}-like check-function. Takes a \link[data.table:data.table]{data.table::data.table} -where rows are points and columns are parameters. A point x is feasible, -if it configures a subset of params, all individual param constraints are -satisfied and all dependencies are satisfied. Params for which -dependencies are not satisfied should be set to \code{NA} in \code{xdt}. +where rows are points and columns are parameters. +A point x is feasible, if it configures a subset of params, +all individual param constraints are satisfied and all dependencies are satisfied. +Params for which dependencies are not satisfied should not be part of \code{x}. +Constraints and dependencies are not checked when \code{check_strict} is \code{FALSE}. \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamSet$check_dt(xdt)}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{ParamSet$check_dt(xdt, check_strict = TRUE)}\if{html}{\out{
}} } \subsection{Arguments}{ \if{html}{\out{
}} \describe{ \item{\code{xdt}}{(\link[data.table:data.table]{data.table::data.table} | \code{data.frame()}).} + +\item{\code{check_strict}}{(\code{logical(1)})\cr +Whether to check that constraints and dependencies are satisfied.} } \if{html}{\out{
}} } @@ -448,13 +535,16 @@ If successful \code{TRUE}, if not a string with the error message. \subsection{Method \code{test_dt()}}{ \pkg{checkmate}-like test-function (s. \verb{$check_dt()}). \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamSet$test_dt(xdt)}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{ParamSet$test_dt(xdt, check_strict = TRUE)}\if{html}{\out{
}} } \subsection{Arguments}{ \if{html}{\out{
}} \describe{ \item{\code{xdt}}{(\link[data.table:data.table]{data.table::data.table}).} + +\item{\code{check_strict}}{(\code{logical(1)})\cr +Whether to check that constraints and dependencies are satisfied.} } \if{html}{\out{
}} } @@ -468,7 +558,7 @@ If successful \code{TRUE}, if not \code{FALSE}. \subsection{Method \code{assert_dt()}}{ \pkg{checkmate}-like assert-function (s. \verb{$check_dt()}). \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamSet$assert_dt(xdt, .var.name = vname(xdt))}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{ParamSet$assert_dt(xdt, check_strict = TRUE, .var.name = vname(xdt))}\if{html}{\out{
}} } \subsection{Arguments}{ @@ -476,6 +566,9 @@ If successful \code{TRUE}, if not \code{FALSE}. \describe{ \item{\code{xdt}}{(\link[data.table:data.table]{data.table::data.table}).} +\item{\code{check_strict}}{(\code{logical(1)})\cr +Whether to check that constraints and dependencies are satisfied.} + \item{\code{.var.name}}{(\code{character(1)})\cr Name of the checked object to print in error messages.\cr Defaults to the heuristic implemented in \link[checkmate:vname]{vname}.} @@ -483,7 +576,128 @@ Defaults to the heuristic implemented in \link[checkmate:vname]{vname}.} \if{html}{\out{
}} } \subsection{Returns}{ -If successful \code{xs} invisibly, if not an error message. +If successful \code{xs} invisibly, if not, an error is generated. +} +} +\if{html}{\out{
}} +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-ParamSet-qunif}{}}} +\subsection{Method \code{qunif()}}{ +Map a \code{matrix} or \code{data.frame} of values between 0 and 1 to proportional values inside the feasible intervals of individual parameters. +\subsection{Usage}{ +\if{html}{\out{
}}\preformatted{ParamSet$qunif(x)}\if{html}{\out{
}} +} + +\subsection{Arguments}{ +\if{html}{\out{
}} +\describe{ +\item{\code{x}}{(\code{matrix} | \code{data.frame})\cr +Values to map. Column names must be a subset of the names of parameters.} +} +\if{html}{\out{
}} +} +\subsection{Returns}{ +\code{data.table}. +} +} +\if{html}{\out{
}} +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-ParamSet-get_domain}{}}} +\subsection{Method \code{get_domain()}}{ +get the \code{\link{Domain}} object that could be used to create a given parameter. +\subsection{Usage}{ +\if{html}{\out{
}}\preformatted{ParamSet$get_domain(id)}\if{html}{\out{
}} +} + +\subsection{Arguments}{ +\if{html}{\out{
}} +\describe{ +\item{\code{id}}{(\code{character(1)}).} +} +\if{html}{\out{
}} +} +\subsection{Returns}{ +\code{\link{Domain}}. +} +} +\if{html}{\out{
}} +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-ParamSet-subset}{}}} +\subsection{Method \code{subset()}}{ +Create a new \code{ParamSet} restricted to the passed IDs. +\subsection{Usage}{ +\if{html}{\out{
}}\preformatted{ParamSet$subset( + ids, + allow_dangling_dependencies = FALSE, + keep_constraint = TRUE +)}\if{html}{\out{
}} +} + +\subsection{Arguments}{ +\if{html}{\out{
}} +\describe{ +\item{\code{ids}}{(\code{character()}).} + +\item{\code{allow_dangling_dependencies}}{(\code{logical(1)})\cr +Whether to allow subsets that cut across parameter dependencies. +Dependencies that point to dropped parameters are kept (but will be "dangling", i.e. their \code{"on"} will not be present).} + +\item{\code{keep_constraint}}{(\code{logical(1)})\cr +Whether to keep the \verb{$constraint} function.} +} +\if{html}{\out{
}} +} +\subsection{Returns}{ +\code{ParamSet}. +} +} +\if{html}{\out{
}} +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-ParamSet-subspaces}{}}} +\subsection{Method \code{subspaces()}}{ +Create new one-dimensional \code{ParamSet}s for each dimension. +\subsection{Usage}{ +\if{html}{\out{
}}\preformatted{ParamSet$subspaces(ids = private$.params$id)}\if{html}{\out{
}} +} + +\subsection{Arguments}{ +\if{html}{\out{
}} +\describe{ +\item{\code{ids}}{(\code{character()})\cr +IDs for which to create \code{ParamSet}s. Defaults to all IDs.} +} +\if{html}{\out{
}} +} +\subsection{Returns}{ +named \code{list()} of \code{ParamSet}. +} +} +\if{html}{\out{
}} +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-ParamSet-flatten}{}}} +\subsection{Method \code{flatten()}}{ +Create a \code{ParamSet} from this object, even if this object itself is not +a \code{ParamSet} but e.g. a \code{\link{ParamSetCollection}}. +\subsection{Usage}{ +\if{html}{\out{
}}\preformatted{ParamSet$flatten()}\if{html}{\out{
}} +} + +} +\if{html}{\out{
}} +\if{html}{\out{}} +\if{latex}{\out{\hypertarget{method-ParamSet-search_space}{}}} +\subsection{Method \code{search_space()}}{ +Construct a \code{\link{ParamSet}} to tune over. Constructed from \code{\link{TuneToken}} in \verb{$values}, see \code{\link[=to_tune]{to_tune()}}. +\subsection{Usage}{ +\if{html}{\out{
}}\preformatted{ParamSet$search_space(values = self$values)}\if{html}{\out{
}} +} + +\subsection{Arguments}{ +\if{html}{\out{
}} +\describe{ +\item{\code{values}}{(\verb{named list}): optional named list of \code{\link{TuneToken}} objects to convert, in place of \verb{$values}.} +} +\if{html}{\out{
}} } } \if{html}{\out{
}} @@ -492,7 +706,7 @@ If successful \code{xs} invisibly, if not an error message. \subsection{Method \code{add_dep()}}{ Adds a dependency to this set, so that param \code{id} now depends on param \code{on}. \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamSet$add_dep(id, on, cond)}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{ParamSet$add_dep(id, on, cond, allow_dangling_dependencies = FALSE)}\if{html}{\out{
}} } \subsection{Arguments}{ @@ -503,6 +717,8 @@ Adds a dependency to this set, so that param \code{id} now depends on param \cod \item{\code{on}}{(\code{character(1)}).} \item{\code{cond}}{(\link{Condition}).} + +\item{\code{allow_dangling_dependencies}}{(\code{logical(1)}): Whether to allow dependencies on parameters that are not present.} } \if{html}{\out{}} } @@ -513,7 +729,7 @@ Adds a dependency to this set, so that param \code{id} now depends on param \cod \subsection{Method \code{format()}}{ Helper for print outputs. \subsection{Usage}{ -\if{html}{\out{
}}\preformatted{ParamSet$format(...)}\if{html}{\out{
}} +\if{html}{\out{
}}\preformatted{ParamSet$format()}\if{html}{\out{
}} } \subsection{Arguments}{ diff --git a/man/ParamSetCollection.Rd b/man/ParamSetCollection.Rd index 3cd31a8a..93e4c93e 100644 --- a/man/ParamSetCollection.Rd +++ b/man/ParamSetCollection.Rd @@ -4,17 +4,16 @@ \alias{ParamSetCollection} \title{ParamSetCollection} \description{ -A collection of multiple \link{ParamSet} objects. +A collection of multiple \code{\link{ParamSet}} objects. \itemize{ \item The collection is basically a light-weight wrapper / container around references to multiple sets. \item In order to ensure unique param names, every param in the collection is referred to with -".". Parameters from ParamSets with empty (i.e. \code{""}) \verb{$set_id} are referenced -directly. Multiple ParamSets with \verb{$set_id} \code{""} can be combined, but their parameter names -must be unique. -\item Operation \code{subset} is currently not allowed. -\item Operation \code{add} currently only works when adding complete sets not single params. +".", where \verb{} is the name of the entry a given \code{\link{ParamSet}} in the named list given during construction. +Parameters from \code{\link{ParamSet}} with empty (i.e. \code{""}) \code{set_id} are referenced +directly. Multiple \code{\link{ParamSet}}s with \code{set_id} \code{""} can be combined, but their parameter names +may not overlap to avoid name clashes. \item When you either ask for 'values' or set them, the operation is delegated to the individual, -contained param set references. The collection itself does not maintain a \code{values} state. +contained \code{\link{ParamSet}} references. The collection itself does not maintain a \code{values} state. This also implies that if you directly change \code{values} in one of the referenced sets, this change is reflected in the collection. \item Dependencies: It is possible to currently handle dependencies @@ -34,15 +33,6 @@ If you call \code{deps} on the collection, you are returned a complete table of \section{Active bindings}{ \if{html}{\out{
}} \describe{ -\item{\code{params}}{(named \code{list()})\cr -List of \link{Param}, named with their respective ID.} - -\item{\code{params_unid}}{(named \code{list()})\cr -List of \link{Param}, named with their true ID. However, -this field has the \link{Param}'s \verb{$id} value set to a -potentially invalid value. This active binding should -only be used internally.} - \item{\code{deps}}{(\code{\link[data.table:data.table]{data.table::data.table()}})\cr Table has cols \code{id} (\code{character(1)}) and \code{on} (\code{character(1)}) and \code{cond} (\link{Condition}). Lists all (direct) dependency parents of a param, through parameter IDs. @@ -54,6 +44,26 @@ Currently set / fixed parameter values. Settable, and feasibility of values will be checked when you set them. You do not have to set values for all parameters, but only for a subset. When you set values, all previously set values will be unset / removed.} + +\item{\code{extra_trafo}}{(\verb{function(x, param_set)})\cr +Transformation function. Settable. +User has to pass a \verb{function(x)}, of the form\cr +(named \code{list()}, \link{ParamSet}) -> named \code{list()}.\cr +The function is responsible to transform a feasible configuration into another encoding, +before potentially evaluating the configuration with the target algorithm. +For the output, not many things have to hold. +It needs to have unique names, and the target algorithm has to accept the configuration. +For convenience, the self-paramset is also passed in, if you need some info from it (e.g. tags). +Is NULL by default, and you can set it to NULL to switch the transformation off.} + +\item{\code{constraint}}{(\verb{function(x)})\cr +Constraint function. Settable. +This function must evaluate a named \code{list()} of values and determine whether it satisfies +constraints, returning a scalar \code{logical(1)} value.} + +\item{\code{sets}}{(named \code{list()})\cr +Read-only \code{list} of of \code{\link{ParamSet}}s contained in this \code{ParamSetCollection}. +This field provides direct references to the \code{\link{ParamSet}} objects.} } \if{html}{\out{
}} } @@ -62,8 +72,6 @@ When you set values, all previously set values will be unset / removed.} \itemize{ \item \href{#method-ParamSetCollection-new}{\code{ParamSetCollection$new()}} \item \href{#method-ParamSetCollection-add}{\code{ParamSetCollection$add()}} -\item \href{#method-ParamSetCollection-remove_sets}{\code{ParamSetCollection$remove_sets()}} -\item \href{#method-ParamSetCollection-subset}{\code{ParamSetCollection$subset()}} \item \href{#method-ParamSetCollection-clone}{\code{ParamSetCollection$clone()}} } } @@ -74,15 +82,24 @@ When you set values, all previously set values will be unset / removed.}
  • paradox::ParamSet$assert()
  • paradox::ParamSet$assert_dt()
  • paradox::ParamSet$check()
  • +
  • paradox::ParamSet$check_dependencies()
  • paradox::ParamSet$check_dt()
  • +
  • paradox::ParamSet$flatten()
  • paradox::ParamSet$format()
  • +
  • paradox::ParamSet$get_domain()
  • paradox::ParamSet$get_values()
  • paradox::ParamSet$ids()
  • paradox::ParamSet$print()
  • +
  • paradox::ParamSet$qunif()
  • paradox::ParamSet$search_space()
  • paradox::ParamSet$set_values()
  • +
  • paradox::ParamSet$subset()
  • +
  • paradox::ParamSet$subspaces()
  • paradox::ParamSet$test()
  • +
  • paradox::ParamSet$test_constraint()
  • +
  • paradox::ParamSet$test_constraint_dt()
  • paradox::ParamSet$test_dt()
  • +
  • paradox::ParamSet$trafo()
  • }} @@ -92,14 +109,21 @@ When you set values, all previously set values will be unset / removed.} \subsection{Method \code{new()}}{ Creates a new instance of this \link[R6:R6Class]{R6} class. \subsection{Usage}{ -\if{html}{\out{
    }}\preformatted{ParamSetCollection$new(sets)}\if{html}{\out{
    }} +\if{html}{\out{
    }}\preformatted{ParamSetCollection$new(sets, tag_sets = FALSE, tag_params = FALSE)}\if{html}{\out{
    }} } \subsection{Arguments}{ \if{html}{\out{
    }} \describe{ -\item{\code{sets}}{(\code{list()} of \link{ParamSet})\cr -Parameter objects are cloned.} +\item{\code{sets}}{(named \code{list()} of \link{ParamSet})\cr +ParamSet objects are not cloned. +Names are used as "set_id" for the naming scheme of delegated parameters.} + +\item{\code{tag_sets}}{(\code{logical(1)})\cr +Whether to add tags of the form \code{"set_"} to each parameter originating from a given \code{ParamSet} given with name \verb{}.} + +\item{\code{tag_params}}{(\code{logical(1)})\cr +Whether to add tags of the form \code{"param_"} to each parameter with original ID \verb{}.} } \if{html}{\out{
    }} } @@ -108,49 +132,24 @@ Parameter objects are cloned.} \if{html}{\out{}} \if{latex}{\out{\hypertarget{method-ParamSetCollection-add}{}}} \subsection{Method \code{add()}}{ -Adds a set to this collection. +Adds a \code{\link{ParamSet}} to this collection. \subsection{Usage}{ -\if{html}{\out{
    }}\preformatted{ParamSetCollection$add(p)}\if{html}{\out{
    }} +\if{html}{\out{
    }}\preformatted{ParamSetCollection$add(p, n = "", tag_sets = FALSE, tag_params = FALSE)}\if{html}{\out{
    }} } \subsection{Arguments}{ \if{html}{\out{
    }} \describe{ \item{\code{p}}{(\link{ParamSet}).} -} -\if{html}{\out{
    }} -} -} -\if{html}{\out{
    }} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-ParamSetCollection-remove_sets}{}}} -\subsection{Method \code{remove_sets()}}{ -Removes sets of given ids from collection. -\subsection{Usage}{ -\if{html}{\out{
    }}\preformatted{ParamSetCollection$remove_sets(ids)}\if{html}{\out{
    }} -} -\subsection{Arguments}{ -\if{html}{\out{
    }} -\describe{ -\item{\code{ids}}{(\code{character()}).} -} -\if{html}{\out{
    }} -} -} -\if{html}{\out{
    }} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-ParamSetCollection-subset}{}}} -\subsection{Method \code{subset()}}{ -Only included for consistency. Not allowed to perform on \link{ParamSetCollection}s. -\subsection{Usage}{ -\if{html}{\out{
    }}\preformatted{ParamSetCollection$subset(ids)}\if{html}{\out{
    }} -} +\item{\code{n}}{(\code{character(1)})\cr +Name to use. Default \code{""}.} -\subsection{Arguments}{ -\if{html}{\out{
    }} -\describe{ -\item{\code{ids}}{(\code{character()}).} +\item{\code{tag_sets}}{(\code{logical(1)})\cr +Whether to add tags of the form \code{"set_"} to the newly added parameters.} + +\item{\code{tag_params}}{(\code{logical(1)})\cr +Whether to add tags of the form \code{"param_"} to each parameter with original ID \verb{}.} } \if{html}{\out{
    }} } diff --git a/man/ParamUty.Rd b/man/ParamUty.Rd deleted file mode 100644 index de1adfe0..00000000 --- a/man/ParamUty.Rd +++ /dev/null @@ -1,160 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/ParamUty.R -\name{ParamUty} -\alias{ParamUty} -\title{Untyped Parameter} -\description{ -A \link{Param} to describe untyped parameters. -} -\examples{ -ParamUty$new("untyped", default = Inf) -} -\seealso{ -Other Params: -\code{\link{ParamDbl}}, -\code{\link{ParamFct}}, -\code{\link{ParamInt}}, -\code{\link{ParamLgl}}, -\code{\link{Param}} -} -\concept{Params} -\section{Super class}{ -\code{\link[paradox:Param]{paradox::Param}} -> \code{ParamUty} -} -\section{Public fields}{ -\if{html}{\out{
    }} -\describe{ -\item{\code{custom_check}}{(\verb{function()})\cr -Custom function to check the feasibility.} - -\item{\code{repr}}{(\code{character(1)})\cr -Custom field for printing the parameter table.} -} -\if{html}{\out{
    }} -} -\section{Active bindings}{ -\if{html}{\out{
    }} -\describe{ -\item{\code{lower}}{(\code{numeric(1)})\cr -Lower bound. -Always \code{NA} for \link{ParamFct}, \link{ParamLgl} and \link{ParamUty}.} - -\item{\code{upper}}{(\code{numeric(1)})\cr -Upper bound. -Always \code{NA} for \link{ParamFct}, \link{ParamLgl} and \link{ParamUty}.} - -\item{\code{levels}}{(\code{character()} | \code{NULL})\cr -Set of allowed levels. -Always \code{NULL} for \link{ParamDbl}, \link{ParamInt} and \link{ParamUty}. -Always \code{c(TRUE, FALSE)} for \link{ParamLgl}.} - -\item{\code{nlevels}}{(\code{integer(1)} | \code{Inf})\cr -Number of categorical levels. -Always \code{Inf} for \link{ParamDbl} and \link{ParamUty}. -The number of integers in the range \verb{[lower, upper]}, or \code{Inf} if unbounded for \link{ParamInt}. -Always \code{2} for \link{ParamLgl}.} - -\item{\code{is_bounded}}{(\code{logical(1)})\cr -Are the bounds finite? -Always \code{TRUE} for \link{ParamFct} and \link{ParamLgl}. -Always \code{FALSE} for \link{ParamUty}.} - -\item{\code{storage_type}}{(\code{character(1)})\cr -Data type when values of this parameter are stored in a data table or sampled. -Always \code{"numeric"} for \link{ParamDbl}. -Always \code{"character"} for \link{ParamFct}. -Always \code{"integer"} for \link{ParamInt}. -Always \code{"logical"} for \link{ParamLgl}. -Always \code{"list"} for \link{ParamUty}.} -} -\if{html}{\out{
    }} -} -\section{Methods}{ -\subsection{Public methods}{ -\itemize{ -\item \href{#method-ParamUty-new}{\code{ParamUty$new()}} -\item \href{#method-ParamUty-clone}{\code{ParamUty$clone()}} -} -} -\if{html}{\out{ -
    Inherited methods - -
    -}} -\if{html}{\out{
    }} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-ParamUty-new}{}}} -\subsection{Method \code{new()}}{ -Creates a new instance of this \link[R6:R6Class]{R6} class. -\subsection{Usage}{ -\if{html}{\out{
    }}\preformatted{ParamUty$new( - id, - default = NO_DEF, - tags = character(), - custom_check = NULL, - repr = substitute(default) -)}\if{html}{\out{
    }} -} - -\subsection{Arguments}{ -\if{html}{\out{
    }} -\describe{ -\item{\code{id}}{(\code{character(1)})\cr -Identifier of the object.} - -\item{\code{default}}{(\code{any})\cr -Default value. Can be from the domain of the parameter or an element of -\code{special_vals}. Has value \link{NO_DEF} if no default exists. \code{NULL} can be a -valid default. -The value has no effect on \code{ParamSet$values} or the behavior of -\code{ParamSet$check()}, \verb{$test()} or \verb{$assert()}. -The \code{default} is intended to be used for documentation purposes. -`} - -\item{\code{tags}}{(\code{character()})\cr -Arbitrary tags to group and subset parameters. Some tags serve a special -purpose:\cr -\itemize{ -\item \code{"required"} implies that the parameters has to be given when setting -\code{values} in \link{ParamSet}. -}} - -\item{\code{custom_check}}{(\verb{function()})\cr -Custom function to check the feasibility. -Function which checks the input. -Must return 'TRUE' if the input is valid and a string with the error message otherwise. -Defaults to \code{NULL}, which means that no check is performed.} - -\item{\code{repr}}{(\code{character(1)})\cr -Custom representation string. Used for parameter table in help pages.} -} -\if{html}{\out{
    }} -} -} -\if{html}{\out{
    }} -\if{html}{\out{}} -\if{latex}{\out{\hypertarget{method-ParamUty-clone}{}}} -\subsection{Method \code{clone()}}{ -The objects of this class are cloneable with this method. -\subsection{Usage}{ -\if{html}{\out{
    }}\preformatted{ParamUty$clone(deep = FALSE)}\if{html}{\out{
    }} -} - -\subsection{Arguments}{ -\if{html}{\out{
    }} -\describe{ -\item{\code{deep}}{Whether to make a deep clone.} -} -\if{html}{\out{
    }} -} -} -} diff --git a/man/Sampler.Rd b/man/Sampler.Rd index 5bf0185b..f66fc8d4 100644 --- a/man/Sampler.Rd +++ b/man/Sampler.Rd @@ -21,7 +21,7 @@ Other Sampler: \section{Public fields}{ \if{html}{\out{
    }} \describe{ -\item{\code{param_set}}{(\link{ParamSet})\cr +\item{\code{param_set}}{(\code{\link{ParamSet}})\cr Domain / support of the distribution we want to sample from.} } \if{html}{\out{
    }} @@ -51,9 +51,8 @@ e.g., \link{Sampler1D}. \subsection{Arguments}{ \if{html}{\out{
    }} \describe{ -\item{\code{param_set}}{(\link{ParamSet})\cr -Domain / support of the distribution we want to sample from. -ParamSet is cloned on construction.} +\item{\code{param_set}}{(\code{\link{ParamSet}})\cr +The \code{\link{ParamSet}} to associated with this \code{Sampler}.} } \if{html}{\out{
    }} } @@ -75,7 +74,7 @@ Sample \code{n} values from the distribution. \if{html}{\out{}} } \subsection{Returns}{ -\link{Design}. +\code{\link{Design}}. } } \if{html}{\out{
    }} diff --git a/man/Sampler1D.Rd b/man/Sampler1D.Rd index 12cf81b3..b2e6a4d2 100644 --- a/man/Sampler1D.Rd +++ b/man/Sampler1D.Rd @@ -25,8 +25,8 @@ Other Sampler: \section{Active bindings}{ \if{html}{\out{
    }} \describe{ -\item{\code{param}}{(\link{Param})\cr -Returns the one Parameter that is sampled from.} +\item{\code{param}}{(\code{\link{ParamSet}})\cr +Returns the one-dimensional \code{\link{ParamSet}} that is sampled from.} } \if{html}{\out{
    }} } @@ -53,7 +53,7 @@ Returns the one Parameter that is sampled from.} Creates a new instance of this \link[R6:R6Class]{R6} class. Note that this object is typically constructed via derived classes, -e.g., \link{Sampler1DUnif}. +e.g., \code{\link{Sampler1DUnif}}. \subsection{Usage}{ \if{html}{\out{
    }}\preformatted{Sampler1D$new(param)}\if{html}{\out{
    }} } @@ -61,8 +61,9 @@ e.g., \link{Sampler1DUnif}. \subsection{Arguments}{ \if{html}{\out{
    }} \describe{ -\item{\code{param}}{(\link{Param})\cr -Domain / support of the distribution we want to sample from.} +\item{\code{param}}{(\code{\link{ParamSet}})\cr +Domain / support of the distribution we want to sample from. +Must be one-dimensional.} } \if{html}{\out{
    }} } diff --git a/man/Sampler1DCateg.Rd b/man/Sampler1DCateg.Rd index e8f1b966..8ebbf668 100644 --- a/man/Sampler1DCateg.Rd +++ b/man/Sampler1DCateg.Rd @@ -4,7 +4,7 @@ \alias{Sampler1DCateg} \title{Sampler1DCateg Class} \description{ -Sampling from a discrete distribution, for a \link{ParamFct} or \link{ParamLgl}. +Sampling from a discrete distribution, for a \code{\link{ParamSet}} containing a single \code{\link[=p_fct]{p_fct()}} or \code{\link[=p_lgl]{p_lgl()}}. } \seealso{ Other Sampler: @@ -57,8 +57,9 @@ Creates a new instance of this \link[R6:R6Class]{R6} class. \subsection{Arguments}{ \if{html}{\out{
    }} \describe{ -\item{\code{param}}{(\link{Param})\cr -Domain / support of the distribution we want to sample from.} +\item{\code{param}}{(\code{\link{ParamSet}})\cr +Domain / support of the distribution we want to sample from. +Must be one-dimensional.} \item{\code{prob}}{(\code{numeric()} | NULL)\cr Numeric vector of \code{param$nlevels} probabilities, which is uniform by default.} diff --git a/man/Sampler1DNormal.Rd b/man/Sampler1DNormal.Rd index e4e7cfa6..c043e228 100644 --- a/man/Sampler1DNormal.Rd +++ b/man/Sampler1DNormal.Rd @@ -4,7 +4,7 @@ \alias{Sampler1DNormal} \title{Sampler1DNormal Class} \description{ -Normal sampling (potentially truncated) for \link{ParamDbl}. +Normal sampling (potentially truncated) for \code{\link[=p_dbl]{p_dbl()}}. } \seealso{ Other Sampler: @@ -60,8 +60,9 @@ Creates a new instance of this \link[R6:R6Class]{R6} class. \subsection{Arguments}{ \if{html}{\out{
    }} \describe{ -\item{\code{param}}{(\link{Param})\cr -Domain / support of the distribution we want to sample from.} +\item{\code{param}}{(\code{\link{ParamSet}})\cr +Domain / support of the distribution we want to sample from. +Must be one-dimensional.} \item{\code{mean}}{(\code{numeric(1)})\cr Mean parameter of the normal distribution. diff --git a/man/Sampler1DRfun.Rd b/man/Sampler1DRfun.Rd index 22f6a87f..dd479245 100644 --- a/man/Sampler1DRfun.Rd +++ b/man/Sampler1DRfun.Rd @@ -60,8 +60,9 @@ Creates a new instance of this \link[R6:R6Class]{R6} class. \subsection{Arguments}{ \if{html}{\out{
    }} \describe{ -\item{\code{param}}{(\link{Param})\cr -Domain / support of the distribution we want to sample from.} +\item{\code{param}}{(\code{\link{ParamSet}})\cr +Domain / support of the distribution we want to sample from. +Must be one-dimensional.} \item{\code{rfun}}{(\verb{function()})\cr Random number generator function, e.g. \code{rexp} to sample from exponential distribution.} diff --git a/man/Sampler1DUnif.Rd b/man/Sampler1DUnif.Rd index 09cf10f0..0254bf28 100644 --- a/man/Sampler1DUnif.Rd +++ b/man/Sampler1DUnif.Rd @@ -49,8 +49,9 @@ Creates a new instance of this \link[R6:R6Class]{R6} class. \subsection{Arguments}{ \if{html}{\out{
    }} \describe{ -\item{\code{param}}{(\link{Param})\cr -Domain / support of the distribution we want to sample from.} +\item{\code{param}}{(\code{\link{ParamSet}})\cr +Domain / support of the distribution we want to sample from. +Must be one-dimensional.} } \if{html}{\out{
    }} } diff --git a/man/SamplerHierarchical.Rd b/man/SamplerHierarchical.Rd index 6f221be7..e0b6f9fd 100644 --- a/man/SamplerHierarchical.Rd +++ b/man/SamplerHierarchical.Rd @@ -27,7 +27,7 @@ Other Sampler: \if{html}{\out{
    }} \describe{ \item{\code{samplers}}{(\code{list()})\cr -List of \link{Sampler1D} objects that gives a Sampler for each \link{Param} in the \code{param_set}.} +List of \code{\link{Sampler1D}} objects that gives a Sampler for each dimension in the \code{param_set}.} } \if{html}{\out{
    }} } @@ -59,12 +59,11 @@ Creates a new instance of this \link[R6:R6Class]{R6} class. \subsection{Arguments}{ \if{html}{\out{
    }} \describe{ -\item{\code{param_set}}{(\link{ParamSet})\cr -Domain / support of the distribution we want to sample from. -ParamSet is cloned on construction.} +\item{\code{param_set}}{(\code{\link{ParamSet}})\cr +The \code{\link{ParamSet}} to associated with this \code{SamplerHierarchical}.} \item{\code{samplers}}{(\code{list()})\cr -List of \link{Sampler1D} objects that gives a Sampler for each \link{Param} in the \code{param_set}.} +List of \code{\link{Sampler1D}} objects that gives a Sampler for each dimension in the \code{param_set}.} } \if{html}{\out{
    }} } diff --git a/man/SamplerJointIndep.Rd b/man/SamplerJointIndep.Rd index 25477667..ee4a3349 100644 --- a/man/SamplerJointIndep.Rd +++ b/man/SamplerJointIndep.Rd @@ -25,7 +25,7 @@ Other Sampler: \if{html}{\out{
    }} \describe{ \item{\code{samplers}}{(\code{list()})\cr -List of \link{Sampler} objects.} +List of \code{\link{Sampler}} objects.} } \if{html}{\out{
    }} } @@ -58,7 +58,7 @@ Creates a new instance of this \link[R6:R6Class]{R6} class. \if{html}{\out{
    }} \describe{ \item{\code{samplers}}{(\code{list()})\cr -List of \link{Sampler} objects.} +List of \code{\link{Sampler}} objects.} } \if{html}{\out{
    }} } diff --git a/man/SamplerUnif.Rd b/man/SamplerUnif.Rd index a405c822..77a038b3 100644 --- a/man/SamplerUnif.Rd +++ b/man/SamplerUnif.Rd @@ -5,7 +5,7 @@ \title{SamplerUnif Class} \description{ Uniform random sampling for an arbitrary (bounded) \link{ParamSet}. -Constructs 1 uniform sampler per \link{Param}, then passes them to \link{SamplerHierarchical}. +Constructs 1 uniform sampler per parameter, then passes them to \link{SamplerHierarchical}. Hence, also works for \link{ParamSet}s sets with dependencies. } \seealso{ @@ -51,9 +51,8 @@ Creates a new instance of this \link[R6:R6Class]{R6} class. \subsection{Arguments}{ \if{html}{\out{
    }} \describe{ -\item{\code{param_set}}{(\link{ParamSet})\cr -Domain / support of the distribution we want to sample from. -ParamSet is cloned on construction.} +\item{\code{param_set}}{(\code{\link{ParamSet}})\cr +The \code{\link{ParamSet}} to associated with this \code{SamplerUnif}.} } \if{html}{\out{
    }} } diff --git a/man/assert_param.Rd b/man/assert_param_set.Rd similarity index 67% rename from man/assert_param.Rd rename to man/assert_param_set.Rd index 27a28566..ce12917d 100644 --- a/man/assert_param.Rd +++ b/man/assert_param_set.Rd @@ -1,33 +1,28 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/asserts.R -\name{assert_param} -\alias{assert_param} +\name{assert_param_set} \alias{assert_param_set} \title{Assertions for Params and ParamSets} \usage{ -assert_param(param, cl = "Param", no_untyped = FALSE, must_bounded = FALSE) - assert_param_set( param_set, - cl = "Param", + cl = NULL, no_untyped = FALSE, must_bounded = FALSE, no_deps = FALSE ) } \arguments{ -\item{param}{(\link{Param}).} +\item{param_set}{(\code{\link{ParamSet}}).} \item{cl}{(\code{character()})\cr Allowed subclasses.} \item{no_untyped}{(\code{logical(1)})\cr -Are untyped \link{Param}s allowed?} +Are untyped \code{\link{Domain}}s allowed?} \item{must_bounded}{(\code{logical(1)})\cr -Only bounded \link{Param}s allowed?} - -\item{param_set}{(\link{ParamSet}).} +Only bounded \code{\link{Domain}}s allowed?} \item{no_deps}{(\code{logical(1)})\cr Are dependencies allowed?} diff --git a/man/domain_check.Rd b/man/domain_check.Rd new file mode 100644 index 00000000..56b797b6 --- /dev/null +++ b/man/domain_check.Rd @@ -0,0 +1,33 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/Domain_methods.R +\name{domain_check} +\alias{domain_check} +\alias{domain_assert} +\alias{domain_test} +\title{Check Value Validity} +\usage{ +domain_check(param, values) + +domain_assert(param, values, .var.name = checkmate::vname(param), add = NULL) + +domain_test(param, values) +} +\arguments{ +\item{x}{(\code{any}).} +} +\value{ +If successful \code{TRUE}, if not a string with the error message. +} +\description{ +\pkg{checkmate}-like check-function. Check whether a list of values is feasible in the domain. +A value is feasible if it is of the same \code{storage_type}, inside of the bounds or element of +\code{special_vals}. \code{TuneToken}s are generally \emph{not} accepted, so they should be filtered out +before the call, if present. + +\code{domain_check} will return \code{TRUE} for accepted values, a \code{character(1)} error message otherwise. + +\code{domain_test} will return \code{TRUE} for accepted values, \code{FALSE} otherwise. + +\code{domain_assert} will return the \code{param} argument silently for accepted values, and throw an error message otherwise. +} +\keyword{internal} diff --git a/man/domain_is_bounded.Rd b/man/domain_is_bounded.Rd new file mode 100644 index 00000000..5be27f82 --- /dev/null +++ b/man/domain_is_bounded.Rd @@ -0,0 +1,18 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/Domain_methods.R +\name{domain_is_bounded} +\alias{domain_is_bounded} +\title{Whether a Given Domain is Bounded} +\usage{ +domain_is_bounded(param) +} +\arguments{ +\item{x}{(\code{Domain}).} +} +\value{ +\code{logical}. +} +\description{ +This should generally be \code{TRUE} when \code{lower} and \code{upper} are given and finite, or when the \code{nlevels} is finite, and \code{FALSE} otherwise. +} +\keyword{internal} diff --git a/man/domain_is_categ.Rd b/man/domain_is_categ.Rd new file mode 100644 index 00000000..ca99e8b3 --- /dev/null +++ b/man/domain_is_categ.Rd @@ -0,0 +1,18 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/Domain_methods.R +\name{domain_is_categ} +\alias{domain_is_categ} +\title{Whether a Given Domain is Categorical} +\usage{ +domain_is_categ(param) +} +\arguments{ +\item{x}{(\code{Domain}).} +} +\value{ +\code{logical}. +} +\description{ +This should generally be \code{TRUE} for categorical \code{\link{Domain}}s, such as \code{\link[=p_fct]{p_fct()}} or \code{\link[=p_lgl]{p_lgl()}}, and \code{FALSE} otherwise. +} +\keyword{internal} diff --git a/man/domain_is_number.Rd b/man/domain_is_number.Rd new file mode 100644 index 00000000..62e757c3 --- /dev/null +++ b/man/domain_is_number.Rd @@ -0,0 +1,18 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/Domain_methods.R +\name{domain_is_number} +\alias{domain_is_number} +\title{Whether a Given Domain is Numeric} +\usage{ +domain_is_number(param) +} +\arguments{ +\item{x}{(\code{Domain}).} +} +\value{ +\code{logical}. +} +\description{ +This should generally be \code{TRUE} for discrete or continuous numeric \code{\link{Domain}}s, and \code{FALSE} otherwise. +} +\keyword{internal} diff --git a/man/domain_nlevels.Rd b/man/domain_nlevels.Rd new file mode 100644 index 00000000..a74c2cf6 --- /dev/null +++ b/man/domain_nlevels.Rd @@ -0,0 +1,19 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/Domain_methods.R +\name{domain_nlevels} +\alias{domain_nlevels} +\title{The Number of Levels of a Given Domain} +\usage{ +domain_nlevels(param) +} +\arguments{ +\item{x}{(\code{Domain}).} +} +\value{ +\code{numeric}. +} +\description{ +This should be the number of discrete possible levels for discrete type \code{\link{Domain}}s such as \code{\link[=p_int]{p_int()}} or \code{\link[=p_fct]{p_fct()}}, and +\code{Inf} for continuous or untyped parameters. +} +\keyword{internal} diff --git a/man/domain_qunif.Rd b/man/domain_qunif.Rd new file mode 100644 index 00000000..f8c046df --- /dev/null +++ b/man/domain_qunif.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/Domain_methods.R +\name{domain_qunif} +\alias{domain_qunif} +\title{Transform a Numeric Value to a Sample} +\usage{ +domain_qunif(param, x) +} +\arguments{ +\item{param}{(\code{Domain}).} + +\item{x}{\code{numeric} between 0 and 1.} +} +\value{ +\code{any} -- format depending on the \code{Domain}. +} +\description{ +Return a valid sample from the given \code{\link{Domain}}, given a value from the interval \verb{[0, 1]}. +} +\keyword{internal} diff --git a/man/domain_sanitize.Rd b/man/domain_sanitize.Rd new file mode 100644 index 00000000..7af1174e --- /dev/null +++ b/man/domain_sanitize.Rd @@ -0,0 +1,23 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/Domain_methods.R +\name{domain_sanitize} +\alias{domain_sanitize} +\title{Map to Acceptable Value} +\usage{ +domain_sanitize(param, values) +} +\arguments{ +\item{param}{(\code{Domain}).} + +\item{values}{(\code{any}) -- format depending on the \code{Domain}.} +} +\value{ +\code{any} -- format depending on the \code{Domain}. +} +\description{ +Map values that are close enough to the given \code{\link{Domain}} to values that are truly acceptable. + +This is used to map \code{numeric()} values that are close to but outside the acceptable interval to the interval bounds. +It is also used to convert integer-valued \code{numeric} values to \code{integer} values for \code{\link[=p_int]{p_int()}}. +} +\keyword{internal} diff --git a/man/generate_design_grid.Rd b/man/generate_design_grid.Rd index 41f25513..1dffab7d 100644 --- a/man/generate_design_grid.Rd +++ b/man/generate_design_grid.Rd @@ -7,16 +7,16 @@ generate_design_grid(param_set, resolution = NULL, param_resolutions = NULL) } \arguments{ -\item{param_set}{(\link{ParamSet}).} +\item{param_set}{(\code{\link{ParamSet}}).} \item{resolution}{(\code{integer(1)})\cr -Global resolution for all \link{Param}s.} +Global resolution for all parameters.} \item{param_resolutions}{(named \code{integer()})\cr -Resolution per \link{Param}, named by parameter ID.} +Resolution per \code{\link{Domain}}, named by parameter ID.} } \value{ -\link{Design}. +\code{\link{Design}}. } \description{ Generate a grid with a specified resolution in the parameter space. @@ -25,11 +25,11 @@ always produce a grid over all their valid levels. For number params the endpoints of the params are always included in the grid. } \examples{ -ps = ParamSet$new(list( - ParamDbl$new("ratio", lower = 0, upper = 1), - ParamFct$new("letters", levels = letters[1:3]) -)) -generate_design_grid(ps, 10) +pset = ps( + ratio = p_dbl(lower = 0, upper = 1), + letters = p_fct(levels = letters[1:3]) +) +generate_design_grid(pset, 10) } \seealso{ Other generate_design: diff --git a/man/generate_design_lhs.Rd b/man/generate_design_lhs.Rd index 836fa03d..cdefe012 100644 --- a/man/generate_design_lhs.Rd +++ b/man/generate_design_lhs.Rd @@ -7,7 +7,7 @@ generate_design_lhs(param_set, n, lhs_fun = NULL) } \arguments{ -\item{param_set}{(\link{ParamSet}).} +\item{param_set}{(\code{\link{ParamSet}}).} \item{n}{(\code{integer(1)}) \cr Number of points to sample.} @@ -17,7 +17,7 @@ Function to use to generate a LHS sample, with n samples and k values per param. LHS functions are implemented in package \pkg{lhs}, default is to use \code{\link[lhs:maximinLHS]{lhs::maximinLHS()}}.} } \value{ -\link{Design}. +\code{\link{Design}}. } \description{ Generate a space-filling design using Latin hypercube sampling. Dependent @@ -25,13 +25,13 @@ parameters whose constraints are unsatisfied generate \code{NA} entries in their respective columns. } \examples{ -ps = ParamSet$new(list( - ParamDbl$new("ratio", lower = 0, upper = 1), - ParamFct$new("letters", levels = letters[1:3]) -)) +pset = ps( + ratio = p_dbl(lower = 0, upper = 1), + letters = p_fct(levels = letters[1:3]) +) if (requireNamespace("lhs", quietly = TRUE)) { - generate_design_lhs(ps, 10) + generate_design_lhs(pset, 10) } } \seealso{ diff --git a/man/generate_design_random.Rd b/man/generate_design_random.Rd index 9c3fc7b6..cb492567 100644 --- a/man/generate_design_random.Rd +++ b/man/generate_design_random.Rd @@ -7,25 +7,25 @@ generate_design_random(param_set, n) } \arguments{ -\item{param_set}{(\link{ParamSet}).} +\item{param_set}{(\code{\link{ParamSet}}).} \item{n}{(\code{integer(1)})\cr Number of points to draw randomly.} } \value{ -\link{Design}. +\code{\link{Design}}. } \description{ Generates a design with randomly drawn points. -Internally uses \link{SamplerUnif}, hence, also works for \link{ParamSet}s with dependencies. +Internally uses \code{\link{SamplerUnif}}, hence, also works for \link{ParamSet}s with dependencies. If dependencies do not hold, values are set to \code{NA} in the resulting data.table. } \examples{ -ps = ParamSet$new(list( - ParamDbl$new("ratio", lower = 0, upper = 1), - ParamFct$new("letters", levels = letters[1:3]) -)) -generate_design_random(ps, 10) +pset = ps( + ratio = p_dbl(lower = 0, upper = 1), + letters = p_fct(levels = letters[1:3]) +) +generate_design_random(pset, 10) } \seealso{ Other generate_design: diff --git a/man/generate_design_sobol.Rd b/man/generate_design_sobol.Rd index ce3e6bc8..9b440222 100644 --- a/man/generate_design_sobol.Rd +++ b/man/generate_design_sobol.Rd @@ -7,13 +7,13 @@ generate_design_sobol(param_set, n) } \arguments{ -\item{param_set}{(\link{ParamSet}).} +\item{param_set}{(\code{\link{ParamSet}}).} \item{n}{(\code{integer(1)}) \cr Number of points to sample.} } \value{ -\link{Design}. +\code{\link{Design}}. } \description{ Generate a space-filling design using a Sobol sequence. Dependent @@ -26,13 +26,13 @@ Note that non determinism is achieved by sampling the seed argument via \code{sample(.Machine$integer.max, size = 1L)}. } \examples{ -ps = ParamSet$new(list( - ParamDbl$new("ratio", lower = 0, upper = 1), - ParamFct$new("letters", levels = letters[1:3]) -)) +pset = ps( + ratio = p_dbl(lower = 0, upper = 1), + letters = p_fct(levels = letters[1:3]) +) if (requireNamespace("spacefillr", quietly = TRUE)) { - generate_design_sobol(ps, 10) + generate_design_sobol(pset, 10) } } \seealso{ diff --git a/man/paradox-package.Rd b/man/paradox-package.Rd index 7e7ef662..5168d963 100644 --- a/man/paradox-package.Rd +++ b/man/paradox-package.Rd @@ -18,14 +18,14 @@ Useful links: } \author{ -\strong{Maintainer}: Michel Lang \email{michellang@gmail.com} (\href{https://orcid.org/0000-0001-9754-0393}{ORCID}) +\strong{Maintainer}: Martin Binder \email{mlr.developer@mb706.com} Authors: \itemize{ + \item Michel Lang \email{michellang@gmail.com} (\href{https://orcid.org/0000-0001-9754-0393}{ORCID}) \item Bernd Bischl \email{bernd_bischl@gmx.net} (\href{https://orcid.org/0000-0001-6002-6980}{ORCID}) \item Jakob Richter \email{jakob1richter@gmail.com} (\href{https://orcid.org/0000-0003-4481-5554}{ORCID}) \item Xudong Sun \email{smilesun.east@gmail.com} (\href{https://orcid.org/0000-0003-3269-2307}{ORCID}) - \item Martin Binder \email{mlr.developer@mb706.com} } Other contributors: diff --git a/man/ps.Rd b/man/ps.Rd index 17b7b167..c8ab62b2 100644 --- a/man/ps.Rd +++ b/man/ps.Rd @@ -4,18 +4,27 @@ \alias{ps} \title{Construct a ParamSet using Short Forms} \usage{ -ps(..., .extra_trafo = NULL, .allow_dangling_dependencies = FALSE) +ps( + ..., + .extra_trafo = NULL, + .constraint = NULL, + .allow_dangling_dependencies = FALSE +) } \arguments{ -\item{...}{(\code{\link{Domain}} | \code{\link{Param}})\cr -Named arguments of \code{\link{Domain}} or \code{\link{Param}} objects. The \code{\link{ParamSet}} will be constructed of the given \code{\link{Param}}s, -or of \code{\link{Param}}s constructed from the given domains. The names of the arguments will be used as \verb{$id} -(the \verb{$id} of \code{\link{Param}} arguments are ignored).} +\item{...}{(\code{\link{Domain}})\cr +Named arguments of \code{\link{Domain}} objects. The \code{\link{ParamSet}} will be constructed of the given \code{\link{Domain}}s, +The names of the arguments will be used as \verb{$id()} in the resulting \code{\link{ParamSet}}.} \item{.extra_trafo}{(\verb{function(x, param_set)})\cr Transformation to set the resulting \code{\link{ParamSet}}'s \verb{$trafo} value to. This is in addition to any \code{trafo} of \code{\link{Domain}} objects given in \code{...}, and will be run \emph{after} transformations of individual parameters were performed.} +\item{.constraint}{(\verb{function(x)})\cr +Constraint function. +When given, this function must evaluate a named \code{list()} of values and determine whether it satisfies +constraints, returning a scalar \code{logical(1)} value.} + \item{.allow_dangling_dependencies}{(\code{logical})\cr Whether dependencies depending on parameters that are not present should be allowed. A parameter \code{x} having \code{depends = y == 0} if \code{y} is not present in the \code{ps()} call would usually throw an error, but if dangling @@ -69,7 +78,7 @@ pars$search_space() } \seealso{ Other ParamSet construction helpers: -\code{\link{Domain}}, +\code{\link{Domain}()}, \code{\link{to_tune}()} } \concept{ParamSet construction helpers} diff --git a/man/ps_replicate.Rd b/man/ps_replicate.Rd new file mode 100644 index 00000000..ef5aeb92 --- /dev/null +++ b/man/ps_replicate.Rd @@ -0,0 +1,71 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/ps_replicate.R +\name{ps_replicate} +\alias{ps_replicate} +\title{Create a ParamSet by Repeating a Given ParamSet} +\usage{ +ps_replicate( + set, + times = length(prefixes), + prefixes = sprintf("rep\%s", seq_len(times)), + tag_sets = FALSE, + tag_params = FALSE +) +} +\arguments{ +\item{set}{(\code{\link{ParamSet}})\cr +\code{\link{ParamSet}} to use as template.} + +\item{times}{(\code{integer(1)})\cr +Number of times to repeat \code{set}. +Should not be given if \code{prefixes} is provided.} + +\item{prefixes}{(\code{character})\cr +A \code{character} vector indicating the prefixes to use for each repetition of \code{set}. +If this is given, \code{times} is inferred from \code{length(prefixes)} and should not be given separately. +If \code{times} is given, this defaults to \code{"repX"}, with \code{X} counting up from 1.} + +\item{tag_sets}{(\code{logical(1)})\cr +Whether to add a tag of the form \code{"set_"} to each parameter in the result, indicating the repetition each parameter belongs to.} + +\item{tag_params}{(\code{logical(1)})\cr +Whether to add a tag of the form \code{"param_"} to each parameter in the result, indicating the original parameter ID inside \code{set}.} +} +\description{ +Repeat a \code{\link{ParamSet}} a given number of times and thus create a larger \code{\link{ParamSet}}. +By default, the resulting parameters are prefixed with the string \verb{"repX.", where }X\verb{counts up from 1. It is also possible to tag parameters by their original name and by their prefix, making grouped retrieval e.g. using}$get_values()` easier. +} +\examples{ +pset = ps( + i = p_int(), + z = p_lgl() +) + +ps_replicate(pset, 3) + +ps_replicate(pset, prefixes = c("first", "last")) + +pset$values = list(i = 1, z = FALSE) + +psr = ps_replicate(pset, 2, tag_sets = TRUE, tag_params = TRUE) + +# observe the effect of tag_sets, tag_params: +psr$tags + +# note that values are repeated as well +psr$values + +psr$set_values(rep1.i = 10, rep2.z = TRUE) +psr$values + +# use `any_tags` to get subset of values. +# `any_tags = ` is preferable to `tags = `, since parameters +# could also have other tags. `tags = ` would require the +# selected params to have the given tags exclusively. + +# get all values associated with the original parameter `i` +psr$get_values(any_tags = "param_i") + +# get all values associated with the first repetition "rep1" +psr$get_values(any_tags = "set_rep1") +} diff --git a/man/ps_union.Rd b/man/ps_union.Rd new file mode 100644 index 00000000..732603e5 --- /dev/null +++ b/man/ps_union.Rd @@ -0,0 +1,57 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/ps_union.R +\name{ps_union} +\alias{ps_union} +\title{Create a ParamSet from a list of ParamSets} +\usage{ +ps_union(sets, tag_sets = FALSE, tag_params = FALSE) +} +\arguments{ +\item{sets}{(\code{list} of \code{\link{ParamSet}})\cr +This may be a named list, in which case non-empty names are prefixed to parameters in the corresponding \code{\link{ParamSet}}.} + +\item{tag_sets}{(\code{logical(1)})\cr +Whether to add tags of the form \code{"set_"} to each parameter originating from a given \code{ParamSet} given with name \verb{}.} + +\item{tag_params}{(\code{logical(1)})\cr +Whether to add tags of the form \code{"param_"} to each parameter with original ID \verb{}.} +} +\description{ +This emulates \code{ParamSetCollection$new(sets)}, except that the result is a flat \code{\link{ParamSet}}, not a \code{\link{ParamSetCollection}}. +The resulting object is decoupled from the input \code{\link{ParamSet}} objects: Unlike \code{\link{ParamSetCollection}}, changing \verb{$values} of +the resulting object will not change the input \code{\link{ParamSet}} \verb{$values} by reference. + +This emulates \code{ParamSetCollection$new(sets)}, which in particular means that the resulting \code{\link{ParamSet}} has all the \code{\link{Domain}}s +from the input \code{sets}, but some \verb{$id}s are changed: If the \code{\link{ParamSet}} is given in \code{sets} with a name, then the \code{\link{Domain}}s will +have their \verb{} changed to \verb{.}. This is also reflected in deps. + +The \code{c()} operator, applied to \code{\link{ParamSet}}s, is a synony for \code{ps_union()}. +} +\examples{ +ps1 = ps(x = p_dbl()) +ps1$values = list(x = 1) + +ps2 = ps(y = p_lgl()) + +pu = ps_union(list(ps1, ps2)) +# same as: +pu = c(ps1, ps2) + +pu + +pu$values + +pu$values$x = 2 +pu$values + +# p1 is unchanged: +ps1$values + +# Prefixes automatically created for named elements. +# This allows repeating components. +pu2 = c(one = ps1, two = ps1, ps2) +pu2 + +pu2$values + +} diff --git a/man/to_tune.Rd b/man/to_tune.Rd index e5764143..0b74e7d0 100644 --- a/man/to_tune.Rd +++ b/man/to_tune.Rd @@ -32,42 +32,41 @@ can be constructed via the \code{to_tune()} function in one of several ways: \item \strong{\code{to_tune(lower, upper, logscale)}}: Indicates a numeric parameter should be tuned in the inclusive interval spanning \code{lower} to \code{upper}, possibly on a log scale if \code{logscale} is se to \code{TRUE}. All parameters are optional, and the parameter's own lower / upper bounds are used without log scale, by default. Depending on the parameter, -integer (if it is a \code{\link{ParamInt}}) or real values (if it is a \code{\link{ParamDbl}}) are used.\cr +integer (if it is a \code{\link[=p_int]{p_int()}}) or real values (if it is a \code{\link[=p_dbl]{p_dbl()}}) are used.\cr \code{lower}, \code{upper}, and \code{logscale} can be given by position, except when only one of them is given, in which case it must be named to disambiguate from the following cases.\cr When \code{logscale} is \code{TRUE}, then a \code{trafo} is generated automatically that transforms to the given bounds. The bounds are log()'d pre-trafo (see examples). See the \code{logscale} argument of \code{\link{Domain}} functions for more info.\cr -Note that "logscale" is \emph{not} inherited from the \code{\link{Param}} that the \code{TuneToken} belongs to! Defining a parameter +Note that "logscale" is \emph{not} inherited from the \code{\link{Domain}} that the \code{TuneToken} belongs to! Defining a parameter with \verb{p_dbl(... logscale = TRUE)} will \emph{not} automatically give the \code{to_tune()} assigned to it log-scale. \item \strong{\code{to_tune(levels)}}: Indicates a parameter should be tuned through the given discrete values. \code{levels} can be any named or unnamed atomic vector or list (although in the unnamed case it must be possible to construct a corresponding \code{character} vector with distinct values using \code{as.character}). \item \strong{\verb{to_tune()}}: The given \code{\link{Domain}} object (constructed e.g. with \code{\link[=p_int]{p_int()}} or \code{\link[=p_fct]{p_fct()}}) indicates the range which should be tuned over. The supplied \code{trafo} function is used for parameter transformation. -\item \strong{\verb{to_tune()}}: The given \code{\link{Param}} object indicates the range which should be tuned over. -\item \strong{\verb{to_tune()}}: The given \code{\link{ParamSet}} is used to tune over a single \code{Param}. This is useful for cases -where a single evaluation-time parameter value (e.g. \code{\link{ParamUty}}) is constructed from multiple tuner-visible -parameters (which may not be \code{ParamUty}). The supplied \code{\link{ParamSet}} should always contain a \verb{$trafo} function, -which must always return a \code{list} with a single entry. +\item \strong{\verb{to_tune()}}: The given \code{\link{ParamSet}} is used to tune over a single dimension. This is useful for cases +where a single evaluation-time parameter value (e.g. \code{\link[=p_uty]{p_uty()}}) is constructed from multiple tuner-visible +parameters (which may not be \code{\link[=p_uty]{p_uty()}}). If not one-dimensional, the supplied \code{\link{ParamSet}} should always contain a \verb{$extra_trafo} function, +which must then always return a \code{list} with a single entry. } The \code{TuneToken} object's internals are subject to change and should not be relied upon. \code{TuneToken} objects should only be constructed via \code{to_tune()}, and should only be used by giving them to \verb{$values} of a \code{\link{ParamSet}}. } \examples{ -params = ParamSet$new(list( - ParamInt$new("int", 0, 10), - ParamInt$new("int_unbounded"), - ParamDbl$new("dbl", 0, 10), - ParamDbl$new("dbl_unbounded"), - ParamDbl$new("dbl_bounded_below", lower = 1), - ParamFct$new("fct", c("a", "b", "c")), - ParamUty$new("uty1"), - ParamUty$new("uty2"), - ParamUty$new("uty3"), - ParamUty$new("uty4"), - ParamUty$new("uty5") -)) +params = ps( + int = p_int(0, 10), + int_unbounded = p_int(), + dbl = p_dbl(0, 10), + dbl_unbounded = p_dbl(), + dbl_bounded_below = p_dbl(lower = 1), + fct = p_fct(c("a", "b", "c")), + uty1 = p_uty(), + uty2 = p_uty(), + uty3 = p_uty(), + uty4 = p_uty(), + uty5 = p_uty() +) params$values = list( @@ -127,7 +126,7 @@ params$values$uty2 = to_tune(c(2, 4, 8)) print(params$search_space()) # Notice how `logscale` applies `log()` to lower and upper bound pre-trafo: -params = ParamSet$new(list(ParamDbl$new("x"))) +params = ps(x = p_dbl()) params$values$x = to_tune(1, 100, logscale = TRUE) @@ -144,7 +143,7 @@ print(grid$transpose()) } \seealso{ Other ParamSet construction helpers: -\code{\link{Domain}}, +\code{\link{Domain}()}, \code{\link{ps}()} } \concept{ParamSet construction helpers} diff --git a/tests/testthat/helper_02_ParamSet.R b/tests/testthat/helper_02_ParamSet.R index 1df2ee13..1bddec3a 100644 --- a/tests/testthat/helper_02_ParamSet.R +++ b/tests/testthat/helper_02_ParamSet.R @@ -1,58 +1,45 @@ th_paramset_dbl1 = function() { - ParamSet$new( - params = list( - th_param_dbl() - ) - ) + th_param_dbl() } th_paramset_full = function() { - ParamSet$new( - params = list( - th_param_int(), - th_param_dbl(), - th_param_fct(), - th_param_lgl() - ) + c( + th_param_int(), + th_param_dbl(), + th_param_fct(), + th_param_lgl() ) } th_paramset_untyped = function() { - ParamSet$new( - params = list(th_param_uty()) - ) + th_param_uty() } th_paramset_numeric = function() { - ParamSet$new( - params = list( - th_param_int(), - th_param_dbl() - ) + c( + th_param_int(), + th_param_dbl() ) } th_paramset_categorical = function() { - ParamSet$new( - params = list( - th_param_fct(), - th_param_lgl() - ) + c( + th_param_fct(), + th_param_lgl() ) } th_paramset_repeated = function() { - ps = ParamSet$new( - params = c( - list(th_param_nat(), th_param_fct()) - ) + c( + th_param_nat(), + th_param_fct(), + ps_replicate(th_param_dbl_na(), 4) ) - ps$add(th_param_dbl_na()$rep(4L)) } th_paramset_deps = function() { ps = th_paramset_full() - ps$add_dep("th_param_fct", on = "th_param_lgl", CondEqual$new(TRUE)) - ps$add_dep("th_param_dbl", on = "th_param_fct", CondAnyOf$new(c("a", "b"))) - return(ps) + ps$add_dep("th_param_fct", on = "th_param_lgl", CondEqual(TRUE)) + ps$add_dep("th_param_dbl", on = "th_param_fct", CondAnyOf(c("a", "b"))) + ps } diff --git a/tests/testthat/helper_03_domain.R b/tests/testthat/helper_03_domain.R new file mode 100644 index 00000000..964a32ad --- /dev/null +++ b/tests/testthat/helper_03_domain.R @@ -0,0 +1,33 @@ + +# compare ParamSets, but ignore Param ID + +expect_equal_ps = function(a, b) { + assert_class(a, "ParamSet") + assert_class(b, "ParamSet") + + normalize_ids = function(original) { + acl = original$clone(deep = TRUE) + acp = acl$.__enclos_env__$private + acp$.params$id = sprintf("x%s", seq_len(original$length)) + names(acp$.values) = sprintf("x%s", match(names(original$values), original$ids())) + acp$.tags = setkeyv(copy(acp$.tags)[, id := sprintf("x%s", match(id, original$ids()))], key(acp$.tags)) + acp$.trafos = setkeyv(copy(acp$.trafos)[, id := sprintf("x%s", match(id, original$ids()))], key(acp$.trafos)) + acp$.deps[, id := sprintf("x%s", match(id, original$ids()))] + setindexv(acp$.params, NULL) + setindexv(acp$.trafos, NULL) + setindexv(acp$.tags, NULL) + setindexv(acp$.deps, NULL) + acl + } + + expect_equal(normalize_ids(a), normalize_ids(b)) +} + +reset_indices = function(p) { + + setindexv(p$.__enclos_env__$private$.tags, NULL) + setindexv(p$.__enclos_env__$private$.trafos, NULL) + setindexv(p$.__enclos_env__$private$.params, NULL) + setindexv(p$.__enclos_env__$private$.deps, NULL) + p +} diff --git a/tests/testthat/helper_compat.R b/tests/testthat/helper_compat.R index 826edc6c..3a9149da 100644 --- a/tests/testthat/helper_compat.R +++ b/tests/testthat/helper_compat.R @@ -9,3 +9,45 @@ context = function(...) suppressWarnings(testthat::context(...)) expect_is = function(...) suppressWarnings(testthat::expect_is(...)) expect_equivalent = function(...) suppressWarnings(testthat::expect_equivalent(...)) library("checkmate") + + +ParamInt = list( + new = function(id, ...) { + ParamSet$new(set_names(list(p_int(...)), id)) + }, + classname = "ParamInt" +) + +ParamDbl = list( + new = function(id, ...) { + ParamSet$new(set_names(list(p_dbl(...)), id)) + }, + classname = "ParamDbl" +) + +ParamFct = list( + new = function(id, ...) { + ParamSet$new(set_names(list(p_fct(...)), id)) + }, + classname = "ParamFct" +) + +ParamLgl = list( + new = function(id, ...) { + ParamSet$new(set_names(list(p_lgl(...)), id)) + }, + classname = "ParamLgl" +) + +ParamUty = list( + new = function(id, ...) { + ParamSet$new(set_names(list(p_uty(...)), id)) + }, + classname = "ParamUty" +) + +ParamSet_legacy = list( + new = function(params = list()) { + ps_union(params) + } +) diff --git a/tests/testthat/test_Condition.R b/tests/testthat/test_Condition.R index 952f61fe..ec011afe 100644 --- a/tests/testthat/test_Condition.R +++ b/tests/testthat/test_Condition.R @@ -1,20 +1,20 @@ context("Condition") test_that("Condition", { - cond = CondEqual$new("a") - y = cond$test(c("a", "b", "c", NA_character_)) + cond = CondEqual("a") + y = condition_test(cond, c("a", "b", "c", NA_character_)) expect_equal(y, c(TRUE, FALSE, FALSE, FALSE)) expect_output(print(cond), fixed = "CondEqual") - expect_error(CondEqual$new(c("a","b")), "Assertion on 'rhs' failed") - expect_error(CondEqual$new(NA), "Assertion on 'rhs' failed") + expect_error(CondEqual(c("a","b")), "Assertion on 'rhs' failed") + expect_error(CondEqual(NA), "Assertion on 'rhs' failed") - cond = CondAnyOf$new(c("a", "b")) - y = cond$test(c("a", "b", "c", NA_character_)) + cond = CondAnyOf(c("a", "b")) + y = condition_test(cond, c("a", "b", "c", NA_character_)) expect_equal(y, c(TRUE, TRUE, FALSE, FALSE)) expect_output(print(cond), fixed = "CondAnyOf") - expect_error(CondAnyOf$new(list("a","b")), "Assertion on 'rhs' failed") - expect_error(CondAnyOf$new(c("a", "b", NA_character_)), "Assertion on 'rhs' failed") - expect_error(CondAnyOf$new(character()), "Assertion on 'rhs' failed") + expect_error(CondAnyOf(list("a","b")), "Assertion on 'rhs' failed") + expect_error(CondAnyOf(c("a", "b", NA_character_)), "Assertion on 'rhs' failed") + expect_error(CondAnyOf(character()), "Assertion on 'rhs' failed") }) diff --git a/tests/testthat/test_Design.R b/tests/testthat/test_Design.R index d23e32e5..b359fe5e 100644 --- a/tests/testthat/test_Design.R +++ b/tests/testthat/test_Design.R @@ -1,11 +1,11 @@ context("Design") test_that("transpose works", { - ps = ParamSet$new(list( + ps = ParamSet_legacy$new(list( ParamFct$new("f", levels = c("a", "b")), ParamInt$new("i", lower = 1, upper = 5) )) - ps$add_dep("i", on = "f", CondEqual$new("a")) + ps$add_dep("i", on = "f", CondEqual("a")) data = data.table(f = c("a", "b"), i = c(1L, NA)) d = Design$new(ps, data, remove_dupl = FALSE) xs = d$transpose(filter_na = FALSE) @@ -16,7 +16,7 @@ test_that("transpose works", { expect_equal(xs, xs2) # now a trafo, with a dep - ps$trafo = function(x, param_set) { + ps$extra_trafo = function(x, param_set) { if (!is.null(x$i)) { x$i = x$i + 10 } diff --git a/tests/testthat/test_Param.R b/tests/testthat/test_Param.R index a687cca8..68bcf90d 100644 --- a/tests/testthat/test_Param.R +++ b/tests/testthat/test_Param.R @@ -4,24 +4,24 @@ context("Param") test_that("basic properties", { p1 = ParamDbl$new("x", default = 4) p2 = ParamFct$new("y", levels = c("a", "b")) - expect_true(p1$has_default) - expect_false(p2$has_default) - expect_true(p1$is_number) - expect_false(p2$is_number) - expect_false(p1$is_categ) - expect_true(p2$is_categ) + expect_equal(p1$default, list(x = 4)) + expect_equal(p2$default, named_list()) + expect_true(p1$is_number[["x"]]) + expect_false(p2$is_number[["y"]]) + expect_false(p1$is_categ[["x"]]) + expect_true(p2$is_categ[["y"]]) }) test_that("check and assert work", { # test-funcion should be tested in individual test_Param files # here we briefly check all 3 to see if they work in principle p = ParamDbl$new("x", lower = 1, upper = 2) - p$assert(1) - expect_error(p$assert(3)) - expect_true(p$check(1)) - expect_string(p$check(3), fixed = "<= 2") - expect_true(p$test(1)) - expect_false(p$test(3)) + p$assert(list(x = 1)) + expect_error(p$assert(list(x = 3)), "Assertion .* failed") + expect_true(p$check(list(x = 1))) + expect_string(p$check(list(x = 3)), fixed = "<= 2") + expect_true(p$test(list(x = 1))) + expect_false(p$test(list(x = 3))) }) @@ -42,24 +42,15 @@ test_that("special_vals work for all Param subclasses", { p = cl$new(id = paste0("test.", cl$classname), special_vals = special_vals) } for (special_val in special_vals) { - expect_true(p$test(special_val)) - expect_false(p$test("never valid")) - expect_false(p$test(NA)) - expect_false(p$test(NULL)) + expect_true(p$test(set_names(list(special_val), paste0("test.", cl$classname)))) + expect_false(p$test(set_names(list("never valid"), paste0("test.", cl$classname)))) + expect_false(p$test(set_names(list(NA), paste0("test.", cl$classname)))) + expect_false(p$test(set_names(list(NULL), paste0("test.", cl$classname)))) } } } }) test_that("we cannot create Params with non-strict R names", { - expect_error(ParamInt$new(id = "$foo"), "comply") -}) - -test_that("printer works", { - for (p in th_paramset_full()$params) { - info = p$id - s = capture_output(print(p)) - expect_true(grepl(p$id, s, fixed = TRUE), info = info) - expect_true(grepl(class(p)[1L], s, fixed = TRUE), info = info) - } + expect_error(ParamInt$new(id = "$foo"), "does not comply") }) diff --git a/tests/testthat/test_ParamDbl.R b/tests/testthat/test_ParamDbl.R index d88e672b..d9c3a005 100644 --- a/tests/testthat/test_ParamDbl.R +++ b/tests/testthat/test_ParamDbl.R @@ -2,14 +2,14 @@ context("ParamDbl") test_that("constructor works", { p = ParamDbl$new(id = "test", lower = 1, upper = 10) - expect_equal(p$id, "test") - expect_equal(p$lower, 1) - expect_equal(p$upper, 10) + expect_equal(p$ids(), "test") + expect_equal(p$lower, c(test = 1)) + expect_equal(p$upper, c(test = 10)) # check that we can create param with Inf bounds p = ParamDbl$new(id = "test", lower = 1) - expect_equal(p$lower, 1) - expect_equal(p$upper, Inf) + expect_equal(p$lower, c(test = 1)) + expect_equal(p$upper, c(test = Inf)) # check some invalid arg settings expect_error(ParamDbl$new(id = "x", lower = NULL), "not 'NULL'") @@ -19,12 +19,12 @@ test_that("constructor works", { test_that("allowing inf as feasible value works", { p = ParamDbl$new(id = "x", lower = 1, upper = 10) - expect_true(p$test(1)) - expect_false(p$test(Inf)) + expect_true(p$test(list(x = 1))) + expect_false(p$test(list(x = Inf))) p = ParamDbl$new(id = "x", lower = 1, special_vals = list(Inf)) - expect_true(p$test(1)) - expect_true(p$test(Inf)) + expect_true(p$test(list(x = 1))) + expect_true(p$test(list(x = Inf))) }) @@ -43,10 +43,12 @@ test_that("qunif", { # then check that the estimated ecdfs from both distribs are nearly the same (L1 dist) p = ParamDbl$new("x", lower = a, upper = b) u = runif(n) - v1 = p$qunif(u) - expect_double(v1, any.missing = FALSE, len = n) + v1 = p$qunif(data.table(x = u)) + expect_data_table(v1, ncols = 1, nrows = n) + expect_equal(colnames(v1), "x") + expect_double(v1$x, any.missing = FALSE, len = n) v2 = runif(n, min = a, max = b) - e1 = ecdf(v1) + e1 = ecdf(v1$x) e2 = ecdf(v2) s = seq(a, b, by = 0.0001) d = abs(e1(s) - e2(s)) @@ -58,12 +60,13 @@ test_that("qunif", { test_that("tolerance in check allows values at the upper bound", { p = ParamDbl$new("x", lower = log(.01), upper = log(100)) - ub = p$qunif(1) - expect_true(p$check(ub)) + ub = p$qunif(data.table(x = 1)) + expect_true(p$check_dt(ub)) + expect_true(p$check(as.list(ub))) }) test_that("tolerance for setting values", { - p = ParamSet$new(list(ParamDbl$new("x", lower = 0, upper = 1))) + p = ParamSet_legacy$new(list(ParamDbl$new("x", lower = 0, upper = 1))) p$values$x = -1e-8 expect_equal(p$values$x, 0) expect_error({p$values$x = -1e-6}, "Element 1 is not >=") diff --git a/tests/testthat/test_ParamFct.R b/tests/testthat/test_ParamFct.R index d75d2f6c..d855f3eb 100644 --- a/tests/testthat/test_ParamFct.R +++ b/tests/testthat/test_ParamFct.R @@ -2,8 +2,8 @@ context("ParamFct") test_that("test if ParamFct constructor works", { p = ParamFct$new(id = "test", levels = c("a", "b")) - expect_equal(p$levels, c("a", "b")) - expect_equal(p$nlevels, 2L) + expect_equal(p$levels$test, c("a", "b")) + expect_equal(p$nlevels[["test"]], 2L) # we dont allow NAs as levels expect_error(ParamFct$new(id = "test", levels = c("a", NA))) @@ -15,9 +15,9 @@ test_that("qunif", { p = ParamFct$new("x", levels = vals) k = p$nlevels u = runif(n) - v1 = p$qunif(u) + v1 = p$qunif(data.frame(x = u))$x expect_character(v1, any.missing = FALSE, len = n) - expect_setequal(unique(v1), p$levels) # check we see all levels + expect_setequal(unique(v1), p$levels$x) # check we see all levels # check that empirical frequencies are pretty much uniform freqs = prop.table(table(v1)) p = rep(1 / k, k) diff --git a/tests/testthat/test_ParamInt.R b/tests/testthat/test_ParamInt.R index 35f81775..ec375d42 100644 --- a/tests/testthat/test_ParamInt.R +++ b/tests/testthat/test_ParamInt.R @@ -2,15 +2,15 @@ context("ParamInt") test_that("constructor works", { p = ParamInt$new(id = "test", lower = 1L, upper = 10L) - expect_equal(p$id, "test") - expect_equal(p$lower, 1L) - expect_equal(p$upper, 10L) - expect_equal(p$nlevels, 10L) + expect_equal(p$ids(), "test") + expect_equal(p$lower[["test"]], 1L) + expect_equal(p$upper[["test"]], 10L) + expect_equal(p$nlevels[["test"]], 10L) # check that we can create param with Inf bounds p = ParamInt$new(id = "test", lower = 1L) - expect_equal(p$lower, 1L) - expect_equal(p$upper, Inf) + expect_equal(p$lower[["test"]], 1L) + expect_equal(p$upper[["test"]], Inf) # check some invalid arg settings expect_error(ParamInt$new(id = "x", lower = NULL), "not 'NULL'") @@ -32,10 +32,10 @@ test_that("qunif", { testit = function(a, b) { p = ParamInt$new("x", lower = a, upper = b) - k = p$nlevels + k = p$nlevels[["x"]] expect_equal(k, b - a + 1) u = runif(n) - v1 = p$qunif(u) + v1 = p$qunif(data.frame(x = u))$x expect_integer(v1, any.missing = FALSE, len = n) expect_setequal(unique(v1), a:b) # check we see all levels # check that empirical frequencies are pretty much uniform @@ -49,9 +49,9 @@ test_that("qunif", { test_that("assigning integer value results in int", { - p = ParamSet$new(list(ParamInt$new("x"))) + p = ParamSet_legacy$new(list(ParamInt$new("x"))) p$values$x = 0 expect_equal(typeof(p$values$x), "integer") - expect_error({p$values$x = 1e-10}, "be of type.*integerish") + expect_error({p$values$x = 1e-2}, "be of type.*integerish") }) diff --git a/tests/testthat/test_ParamLgl.R b/tests/testthat/test_ParamLgl.R index 78106d5c..0bcd225c 100644 --- a/tests/testthat/test_ParamLgl.R +++ b/tests/testthat/test_ParamLgl.R @@ -2,9 +2,9 @@ context("ParamLgl") test_that("constructor works", { p = ParamLgl$new(id = "test") - expect_equal(p$id, "test") - expect_equal(p$nlevels, 2L) - expect_equal(p$levels, c(TRUE, FALSE)) + expect_equal(p$ids(), "test") + expect_equal(p$nlevels[["test"]], 2L) + expect_equal(p$levels[["test"]], c(TRUE, FALSE)) }) test_that("qunif", { @@ -12,9 +12,9 @@ test_that("qunif", { testit = function() { p = ParamLgl$new("x") u = runif(n) - v1 = p$qunif(u) + v1 = p$qunif(data.frame(x = u))$x expect_logical(v1, any.missing = FALSE, len = n) - expect_setequal(unique(v1), p$levels) # check we see all levels + expect_setequal(unique(v1), p$levels[["x"]]) # check we see all levels # check that empirical frequencies are pretty much uniform freqs = prop.table(table(v1)) p = c(1 / 2, 1 / 2) diff --git a/tests/testthat/test_ParamSet.R b/tests/testthat/test_ParamSet.R index ef04e608..260e5538 100644 --- a/tests/testthat/test_ParamSet.R +++ b/tests/testthat/test_ParamSet.R @@ -9,7 +9,7 @@ test_that("simple active bindings work", { th_paramset_numeric() ) for (ps in ps_list) { - info = ps$set_id + info = str_collapse(ps$class) expect_class(ps, "ParamSet", info = info) expect_int(ps$length, lower = 0L, info = info) expect_character(ps$ids(), info = info) @@ -23,7 +23,9 @@ test_that("simple active bindings work", { expect_names(names(ps$upper), identical.to = ps$ids(), info = info) expect_list(ps$levels, info = info) expect_names(names(ps$levels), identical.to = ps$ids(), info = info) - expect_flag(ps$is_bounded, info = info) + expect_logical(ps$is_bounded, any.missing = FALSE, info = info) + expect_names(names(ps$is_bounded), identical.to = ps$ids(), info = info) + expect_flag(ps$all_bounded, info = info) expect_numeric(ps$nlevels, any.missing = FALSE, lower = 1, info = info) expect_list(ps$tags, types = "character", info = info) expect_names(names(ps$tags), identical.to = ps$ids(), info = info) @@ -31,7 +33,7 @@ test_that("simple active bindings work", { expect_names(names(ps$default), subset.of = ps$ids(), info = info) } ps = th_paramset_full() - expect_output(print(ps), "") + expect_output(print(ps), fixed = "") expect_equal(ps$ids(), c("th_param_int", "th_param_dbl", "th_param_fct", "th_param_lgl")) expect_equal(ps$lower, c(th_param_int = -10, th_param_dbl = -10, th_param_fct = NA_real_, th_param_lgl = NA_real_)) expect_equal(ps$upper, c(th_param_int = 10, th_param_dbl = 10, th_param_fct = NA_real_, th_param_lgl = NA_real_)) @@ -42,20 +44,20 @@ test_that("ParamSet$subset", { getps = function() th_paramset_full()$clone(deep = TRUE) # give us a fresh clone of the fullset # we can subset to an empty set ps = getps() - ps$subset(character(0L)) + ps = ps$subset(character(0L)) expect_true(ps$is_empty) ps = getps() # subsetting to 2 params make the set smaller - ps$subset(ids[2:3]) + ps = ps$subset(ids[2:3]) expect_equal(ps$ids(), ids[2:3]) expect_equal(ps$length, 2) # subsetting to all ids does not change anything ps = getps() - ps$subset(ids) + ps = ps$subset(ids) expect_equal(as.data.table(ps), as.data.table(getps())) # subset full set to 2 numeric params ps = getps() - ps$subset(c("th_param_int", "th_param_dbl")) + ps = ps$subset(c("th_param_int", "th_param_dbl")) expect_equal(as.data.table(ps), as.data.table(th_paramset_numeric())) }) @@ -64,20 +66,20 @@ test_that("ParamSet$add_param_set", { ps1 = ParamSet$new() n1 = ps1$length ps2 = ParamSet$new() - ps1$add(ps2) + ps1 = ps_union(list(ps1, ps2)) expect_equal(ps1$length, n1) - ps2$add(ps1) + ps2 = ps_union(list(ps2, ps1)) expect_equal(ps2$length, n1) # adding 2 sets, numeric and untyped, makes them larger ps1 = th_paramset_numeric()$clone(deep = TRUE) ps2 = th_paramset_untyped()$clone(deep = TRUE) - ps1$add(ps2) + ps1 = ps_union(list(ps1, ps2)) expect_equal(ps2$length, 1L) expect_equal(ps1$ids(), c("th_param_int", "th_param_dbl", "th_param_uty")) ps1 = th_paramset_numeric()$clone(deep = TRUE) ps2 = th_paramset_untyped()$clone(deep = TRUE) - ps2$add(ps1) + ps2 = ps_union(list(ps2, ps1)) expect_equal(ps2$ids(), c("th_param_uty", "th_param_int", "th_param_dbl")) expect_equal(ps1$length, 2L) }) @@ -102,32 +104,30 @@ test_that("ParamSet$check", { expect_true(ps$check(list(th_param_dbl = 5))) expect_true(ps$check(list(th_param_int = 5))) - ps = ParamLgl$new("x")$rep(2) - ps$add_dep("x_rep_1", "x_rep_2", CondEqual$new(TRUE)) - expect_string(ps$check(list(x_rep_1 = FALSE, x_rep_2 = FALSE)), fixed = "x_rep_2 = TRUE") + ps = ps_replicate(ParamLgl$new("x"), 2) + ps$add_dep("rep1.x", "rep2.x", CondEqual(TRUE)) + expect_string(ps$check(list(rep1.x = FALSE, rep2.x = FALSE), check_strict = TRUE), fixed = "rep2.x == TRUE") }) test_that("we cannot create ParamSet with non-strict R names", { - ps = ParamSet$new() - expect_error(ps$set_id <- "$foo", "comply") + expect_error(ParamDbl$new("$foo"), "does not comply") }) test_that("ParamSets cannot have duplicated ids", { p1 = ParamDbl$new("x1") p2 = ParamDbl$new("x1") - expect_error(ParamSet$new(list(p1, p2)), "duplicated") - ps = ParamSet$new(list(p1)) - expect_error(ps$add(p2), "duplicated") - expect_error(ps$add(ParamSet$new(list(p2))), "duplicated") + expect_error(ParamSet_legacy$new(list(p1, p2)), "duplicated") + ps = ParamSet_legacy$new(list(p1)) + expect_error(ps_union(list(ps, p2)), "duplicated") + expect_error(ps_union(list(ps, ParamSet_legacy$new(list(p2)))), "duplicated") }) test_that("ParamSet$print", { - ps = ParamSet$new() - ps$set_id = "foo" - expect_output(print(ps), "") + ps = ParamSet_legacy$new() + expect_output(print(ps), fixed = "") expect_output(print(ps), "Empty") ps = th_paramset_numeric() - expect_output(print(ps), "") + expect_output(print(ps), fixed = sprintf("", ps$length)) s = capture_output(print(ps)) expect_true(grepl("ParamInt", s, fixed = TRUE)) expect_true(grepl("ParamDbl", s, fixed = TRUE)) @@ -141,80 +141,83 @@ test_that("ParamSet$print", { th_paramset_untyped() ) for (ps in ps_list) { - expect_output(print(ps), "") + expect_output(print(ps), fixed = sprintf("", ps$length)) } }) test_that("ParamSet does a deep copy of params on construction", { p = ParamDbl$new("x", lower = 1, upper = 3) - ps = ParamSet$new(list(p)) - p$lower = 2 - expect_equal(p$lower, 2) - expect_equal(ps$lower, c(x = 1)) - expect_equal(ps$params[["x"]]$lower, 1) + ps = ParamSet_legacy$new(list(y = p)) + p$values = list(x = 1) + ps$values = list(y.x = 2) + expect_equal(p$values, list(x = 1)) + expect_equal(ps$values, list(y.x = 2)) }) test_that("ParamSet does a deep copy of param on add", { p = ParamDbl$new("x", lower = 1, upper = 3) - ps = ParamSet$new(list())$add(p) - p$lower = 2 - expect_equal(p$lower, 2) - expect_equal(ps$lower, c(x = 1)) - expect_equal(ps$params[["x"]]$lower, 1) + ps = ps_union(list(ParamSet_legacy$new(list()), ParamSet_legacy$new(list(y = p)))) + p$values = list(x = 1) + ps$values = list(y.x = 2) + expect_equal(p$values, list(x = 1)) + expect_equal(ps$values, list(y.x = 2)) }) test_that("ParamSet$clone can be deep", { - p1 = ParamDbl$new("x", lower = 1, upper = 3) + + p1 = c(ParamDbl$new("x", lower = 1, upper = 3), ParamDbl$new("foo", lower = -10, upper = 10)) p2 = ParamFct$new("y", levels = c("a", "b")) - ps1 = ParamSet$new(list(p1, p2)) + ps1 = ParamSet_legacy$new(list(p1, p2)) ps2 = ps1$clone(deep = TRUE) - pp = ps2$params[["x"]] - pp$lower = 9 - expect_equal(ps2$lower, c(x = 9, y = NA)) - expect_equal(ps1$lower, c(x = 1, y = NA)) + + p3 = ParamFct$new("z", levels = c("a", "b")) + ps2 = ps_union(list(ps2, p3)) + + expect_equal(ps2$params, ps_union(list(p1, p2, p3))$params) + expect_equal(ps1$params, ps_union(list(p1, p2))$params) # now lets add a dep, see if that gets clones properly - ps1$add_dep("x", on = "y", CondEqual$new("a")) + ps1$add_dep("x", on = "y", CondEqual("a")) ps2 = ps1$clone(deep = TRUE) d = ps2$deps$id[1] = "foo" expect_equal(ps2$deps$id[1], "foo") expect_equal(ps1$deps$id[1], "x") - ps = ParamSet$new() + ps = ParamSet_legacy$new() expect_equal(ps, ps$clone(deep = TRUE)) }) test_that("ParamSet$is_bounded", { - ps = ParamSet$new(list( + ps = ParamSet_legacy$new(list( ParamDbl$new("x", lower = 1, upper = 3) )) - expect_true(ps$is_bounded) - ps = ParamSet$new(list( + expect_true(ps$all_bounded) + ps = ParamSet_legacy$new(list( ParamDbl$new("x", lower = 1, upper = 3), ParamLgl$new("y") )) - expect_true(ps$is_bounded) - ps = ParamSet$new(list( + expect_true(ps$all_bounded) + ps = ParamSet_legacy$new(list( ParamDbl$new("x", lower = 1), ParamLgl$new("y") )) - expect_false(ps$is_bounded) + expect_false(ps$all_bounded) }) test_that("ParamSet$add_param", { - ps = ParamSet$new(list()) - ps$add(ParamDbl$new("x", lower = 1)) + ps = ParamSet_legacy$new(list()) + ps = ps_union(list(ps, ParamDbl$new("x", lower = 1))) expect_equal(ps$length, 1L) expect_equal(ps$ids(), "x") expect_equal(ps$lower, c(x = 1)) - ps$add(ParamFct$new("y", levels = c("a"))) + ps = ps_union(list(ps, ParamFct$new("y", levels = c("a")))) expect_equal(ps$length, 2L) expect_equal(ps$ids(), c("x", "y")) expect_equal(ps$lower, c(x = 1, y = NA)) }) test_that("as.data.table", { - d = as.data.table(ParamSet$new()) + d = as.data.table(ParamSet_legacy$new()) expect_data_table(d, nrows = 0) ps = th_paramset_full() d = as.data.table(ps) @@ -225,14 +228,14 @@ test_that("as.data.table", { }) test_that("ParamSet$default", { - ps = ParamSet$new(list( + ps = ParamSet_legacy$new(list( ParamDbl$new("x", lower = 1, upper = 3, default = 2), ParamInt$new("y", lower = 1, upper = 3) )) expect_equal(ps$default, list(x = 2)) expect_error(ParamDbl$new("x", lower = 1, upper = 3, default = 4)) expect_error(ParamDbl$new("x", lower = 1, upper = 3, default = NULL)) - ps = ParamSet$new(list( + ps = ParamSet_legacy$new(list( ParamDbl$new("x", lower = 1, upper = 3, special_vals = list(NULL), default = NULL), ParamInt$new("y", lower = 1, upper = 3) )) @@ -251,7 +254,7 @@ test_that("is_number / is_categ / all_numeric / all_categoric", { }) test_that("ParamSet$ids", { - ps = ParamSet$new(list( + ps = ParamSet_legacy$new(list( ParamDbl$new(id = "x", lower = 1, tags = c("t1")), ParamInt$new(id = "y", lower = 1, upper = 2), ParamFct$new(id = "z", levels = letters[1:3], tags = c("t1")) @@ -259,11 +262,12 @@ test_that("ParamSet$ids", { expect_equal(ps$ids(), c("x", "y", "z")) expect_equal(ps$ids(class = c("ParamInt", "ParamFct")), c("y", "z")) expect_equal(ps$ids(class = c("ParamInt", "ParamFct"), tags = "t1"), c("z")) - expect_equal(ps$ids(is_bounded = TRUE), c("y", "z")) + expect_equal(ps$ids(class = c("ParamInt", "ParamFct"), any_tags = c("t1", "t2")), c("z")) + expect_equal(ps$ids(class = c("ParamInt", "ParamFct"), tags = c("t1", "t2")), character(0)) }) test_that("ParamSet$get_values", { - ps = ParamSet$new(list( + ps = ParamSet_legacy$new(list( ParamDbl$new(id = "x", lower = 1, tags = c("t1")), ParamInt$new(id = "y", lower = 1, upper = 2), ParamFct$new(id = "z", levels = letters[1:3], tags = c("t1")) @@ -272,15 +276,13 @@ test_that("ParamSet$get_values", { expect_equal(ps$get_values(class = c("ParamInt", "ParamFct")), named_list()) ps$values$x = 1 expect_equal(ps$get_values(class = c("ParamInt", "ParamFct")), named_list()) - expect_equal(ps$get_values(is_bounded = TRUE), named_list()) ps$values$y = 2 expect_equal(ps$get_values(), list(x = 1, y = 2)) expect_equal(ps$get_values(class = c("ParamInt", "ParamFct")), list(y = 2)) - expect_equal(ps$get_values(is_bounded = TRUE), list(y = 2)) }) test_that("required tag", { - ps = ParamSet$new(list( + ps = ParamSet_legacy$new(list( ParamDbl$new(id = "x", tags = c("required")), ParamInt$new(id = "y") )) @@ -298,16 +300,16 @@ test_that("required tag", { }) test_that("required tag, empty param set (#219)", { - ps = ParamSet$new() + ps = ParamSet_legacy$new() ps$ids() expect_identical(ps$ids(tags = "required"), character(0)) }) test_that("paramset clones properly", { - ps = ParamSet$new() - ps$add(ParamFct$new("a", levels = letters[1:3])) - ps$add(ParamFct$new("b", levels = letters[1:3])) - ps$add_dep("a", "b", CondAnyOf$new(letters[1:2])) + ps = ParamSet_legacy$new() + ps = ps_union(list(ps, ParamFct$new("a", levels = letters[1:3]))) + ps = ps_union(list(ps, ParamFct$new("b", levels = letters[1:3]))) + ps$add_dep("a", "b", CondAnyOf(letters[1:2])) ps2 = ps$clone(deep = TRUE) expect_equal(ps, ps2) @@ -332,46 +334,46 @@ test_that("ParamSet$check_dt", { expect_character(ps$check_dt(xdt), fixed = "th_param_int: Element 1 is not <= 10") xdt = data.table(th_param_dbl = c(1, 1), new_param = c(1, 20)) expect_character(ps$check_dt(xdt), fixed = "not available") - ps = ParamLgl$new("x")$rep(2) - ps$add_dep("x_rep_2", "x_rep_1", CondEqual$new(TRUE)) - xdt = data.table(x_rep_1 = c(TRUE, TRUE), x_rep_2 = c(FALSE, TRUE)) - expect_true(ps$check_dt(xdt)) - xdt = data.table(x_rep_1 = c(TRUE, TRUE, FALSE), x_rep_2 = c(FALSE, TRUE, FALSE)) - expect_character(ps$check_dt(xdt), fixed = "x_rep_1 = TRUE") - xdt = data.table(x_rep_1 = c(TRUE, TRUE, FALSE), x_rep_2 = c(FALSE, TRUE, NA)) - expect_true(ps$check_dt(xdt)) + ps = ps_replicate(ParamLgl$new("x"), 2) + ps$add_dep("rep2.x", "rep1.x", CondEqual(TRUE)) + xdt = data.table(rep1.x = c(TRUE, TRUE), rep2.x = c(FALSE, TRUE)) + expect_true(ps$check_dt(xdt, check_strict = TRUE)) + xdt = data.table(rep1.x = c(TRUE, TRUE, FALSE), rep2.x = c(FALSE, TRUE, FALSE)) + expect_character(ps$check_dt(xdt, check_strict = TRUE), fixed = "rep1.x == TRUE") + xdt = data.table(rep1.x = c(TRUE, TRUE, FALSE), rep2.x = c(FALSE, TRUE, NA)) + expect_true(ps$check_dt(xdt, check_strict = TRUE)) }) test_that("rd_info.ParamSet", { - ps = ParamSet$new() + ps = ParamSet_legacy$new() expect_character(rd_info(ps), pattern = "empty", ignore.case = TRUE) - ps$add(ParamFct$new("a", levels = letters[1:3])) + ps = ps_union(list(ps, ParamFct$new("a", levels = letters[1:3]))) expect_character(rd_info(ps), len = 1L) }) test_that("ParamSet$values convert nums to ints for ParamInt", { pp = ParamInt$new("x") - ps = ParamSet$new(list(pp)) + ps = ParamSet_legacy$new(list(pp)) ps$values$x = 2 expect_class(ps$values$x, "integer") }) test_that("Empty ParamSets are named (#351)", { - ps = ps()$add(ps(x = p_lgl())) + ps = ps_union(list(ps(), ps(x = p_lgl()))) expect_names(names(ps$values), type = "strict") expect_is(ps$search_space(), "ParamSet") }) test_that("set_values checks inputs correctly", { - param_set = ps(a = paradox::p_dbl(), b = paradox::p_dbl()) + param_set = ps(a = p_dbl(), b = p_dbl()) expect_error(param_set$set_values(a = 2, .values = list(a = 1))) expect_error(param_set$set_values(2)) expect_error(param_set$set_values(.values = list(1))) }) test_that("set_values works for ... with correct inputs", { - param_set = ps(a = paradox::p_dbl(), b = paradox::p_dbl()) + param_set = ps(a = p_dbl(), b = p_dbl()) param_set$values$a = 1 param_set$set_values(b = 2, .insert = FALSE) expect_true(is.null(param_set$values$a)) @@ -383,7 +385,7 @@ test_that("set_values works for ... with correct inputs", { }) test_that("set_values works for .values with correct inputs", { - param_set = ps(a = paradox::p_dbl(), b = paradox::p_dbl()) + param_set = ps(a = p_dbl(), b = p_dbl()) param_set$values$a = 1 param_set$set_values(.values = list(b = 2), .insert = FALSE) expect_true(is.null(param_set$values$a)) @@ -395,7 +397,7 @@ test_that("set_values works for .values with correct inputs", { }) test_that("set_values works for .values and ... with correct inputs", { - param_set = ps(a = paradox::p_dbl(), b = paradox::p_dbl(), c = paradox::p_dbl()) + param_set = ps(a = p_dbl(), b = p_dbl(), c = p_dbl()) param_set$values$a = 1 param_set$set_values(b = 2, .values = list(c = 3), .insert = TRUE) expect_true(param_set$values$a == 1) @@ -422,6 +424,10 @@ test_that("set_values allows to unset parameters by setting them to NULL", { param_set = ps(a = p_int()) param_set$set_values(a = 1) + # .insert = FALSE can also set values to NULL + expect_error(param_set$set_values(.values = list(a = NULL), .insert = FALSE), "not 'NULL'") + param_set = ps(a = p_int(special_vals = list(NULL))) + param_set$set_values(a = 1) param_set$set_values(.values = list(a = NULL), .insert = FALSE) - expect_true(length(param_set$values) == 0) + expect_identical(param_set$values, list(a = NULL)) }) diff --git a/tests/testthat/test_ParamSetCollection.R b/tests/testthat/test_ParamSetCollection.R index 541707d4..91325115 100644 --- a/tests/testthat/test_ParamSetCollection.R +++ b/tests/testthat/test_ParamSetCollection.R @@ -2,12 +2,9 @@ context("ParamSetCollection") test_that("ParamSet basic stuff works", { ps1 = th_paramset_dbl1() - ps1$set_id = "s1" ps2 = th_paramset_full() - ps2$set_id = "s2" ps3 = th_paramset_dbl1() - ps3$set_id = "" - psc = ParamSetCollection$new(list(ps1, ps2, ps3)) + psc = ParamSetCollection$new(list(s1 = ps1, s2 = ps2, ps3)) ps1clone = ps1$clone(deep = TRUE) ps2clone = ps2$clone(deep = TRUE) @@ -21,10 +18,10 @@ test_that("ParamSet basic stuff works", { expect_class(psc, "ParamSetCollection") expect_equal(psc$length, ps1$length + ps2$length + ps3$length) # check that param internally in collection is constructed correctly - p = psc$params[[2L]] - p = p$clone() + p = psc$params[2L] p$id = "th_param_int" - expect_equal(p, ps2$params[[1L]]) + + expect_equal(p, ps2$params[1L]) expect_equal(psc$ids(), c(paste0("s1.", ps1$ids()), paste0("s2.", ps2$ids()), ps3$ids())) expect_equal(psc$lower, my_c(ps1$lower, ps2$lower, ps3$lower)) d = as.data.table(psc) @@ -42,12 +39,13 @@ test_that("ParamSet basic stuff works", { d = generate_design_random(psc, n = 10L) expect_data_table(d$data, nrows = 10, ncols = 6L) - psc$trafo = function(x, param_set) { + psflat = psc$flatten() + psflat$extra_trafo = function(x, param_set) { x$s2.th_param_int = 99 # nolint return(x) } - expect_true(psc$has_trafo) - d = generate_design_random(psc, n = 10L) + expect_true(psflat$has_trafo) + d = generate_design_random(psflat, n = 10L) expect_data_table(d$data, nrows = 10, ncols = 6L) xs = d$transpose(trafo = TRUE) for (i in 1:10) { @@ -68,54 +66,45 @@ test_that("ParamSet basic stuff works", { expect_equal(ps2, ps2clone) # adding a set - ps4 = ParamSet$new(list(ParamDbl$new("x"))) - ps4$set_id = "s4" - psc$add(ps4) + ps4 = ParamSet_legacy$new(list(ParamDbl$new("x"))) + psc = psc$add(ps4, n = "s4") expect_equal(psc$length, ps1$length + ps2$length + ps3$length + ps4$length) expect_equal(psc$ids(), c(paste0("s1.", ps1$ids()), paste0("s2.", ps2$ids()), ps3$ids(), paste0("s4.", ps4$ids()))) - psc$remove_sets("s1") - expect_equal(psc$length, ps2$length + ps3$length + ps4$length) - expect_equal(psc$ids(), c(paste0("s2.", ps2$ids()), ps3$ids(), paste0("s4.", ps4$ids()))) }) test_that("some operations are not allowed", { ps1 = th_paramset_dbl1() - ps1$set_id = "s1" ps2 = th_paramset_full() - ps2$set_id = "s2" - psc = ParamSetCollection$new(list(ps1, ps2)) + psc = ParamSetCollection$new(list(s1 = ps1, s2 = ps2)) - expect_error(psc$subset("foo"), "not allowed") - expect_error(psc$add(th_param_dbl()), "ParamSet") + expect_error(psc$subset("foo"), "Must be a subset of") }) test_that("deps", { - ps1 = ParamSet$new(list( + ps1 = ParamSet_legacy$new(list( ParamFct$new("f", levels = c("a", "b")), ParamDbl$new("d") )) - ps1$set_id = "ps1" - ps1$add_dep("d", on = "f", CondEqual$new("a")) + ps1$add_dep("d", on = "f", CondEqual("a")) - ps2 = ParamSet$new(list( + ps2 = ParamSet_legacy$new(list( ParamFct$new("f", levels = c("a", "b")), ParamDbl$new("d") )) - ps2$set_id = "ps2" ps1clone = ps1$clone(deep = TRUE) ps2clone = ps2$clone(deep = TRUE) - psc = ParamSetCollection$new(list(ps1, ps2)) + psc = ParamSetCollection$new(list(ps1 = ps1, ps2 = ps2)) d = psc$deps expect_data_table(d, nrows = 1, ncols = 3) expect_equal(d$id, c("ps1.d")) # check deps across sets - psc$add_dep("ps2.d", on = "ps1.f", CondEqual$new("a")) + psc$add_dep("ps2.d", on = "ps1.f", CondEqual("a")) expect_data_table(psc$deps, nrows = 2, ncols = 3) expect_true(psc$check(list(ps1.f = "a", ps1.d = 0, ps2.d = 0))) - expect_string(psc$check(list(ps2.d = 0))) + expect_string(psc$check(list(ps2.d = 0), check_strict = TRUE)) # ps1 and ps2 should not be changed expect_equal(ps1clone, ps1) @@ -123,27 +112,25 @@ test_that("deps", { }) test_that("values", { - ps1 = ParamSet$new(list( + ps1 = ParamSet_legacy$new(list( ParamFct$new("f", levels = c("a", "b")), ParamDbl$new("d", lower = 1, upper = 8) )) - ps1$set_id = "foo" - ps2 = ParamSet$new(list( + ps2 = ParamSet_legacy$new(list( ParamFct$new("f", levels = c("a", "b")), ParamDbl$new("d", lower = 1, upper = 8) )) - ps2$set_id = "bar" - ps3 = ParamSet$new(list( + ps3 = ParamSet_legacy$new(list( ParamDbl$new("x", lower = 1, upper = 8) )) - ps4 = ParamSet$new(list( + ps4 = ParamSet_legacy$new(list( ParamDbl$new("y", lower = 1, upper = 8) )) ps1clone = ps1$clone(deep = TRUE) ps2clone = ps2$clone(deep = TRUE) - pcs = ParamSetCollection$new(list(ps1, ps2, ps3, ps4)) + pcs = ParamSetCollection$new(list(foo = ps1, bar = ps2, ps3, ps4)) expect_equal(pcs$values, named_list()) ps2$values = list(d = 3) expect_equal(pcs$values, list(bar.d = 3)) @@ -167,66 +154,49 @@ test_that("values", { expect_equal(ps1clone, ps1) expect_equal(ps2clone, ps2) + + # resetting pcs values + pcs$values = list() + expect_list(pcs$values, len = 0) }) test_that("empty collections", { # no paramsets psc = ParamSetCollection$new(list()) expect_equal(psc$length, 0L) - expect_equal(psc$params, named_list()) + expect_equal(psc$subspaces(), named_list()) expect_equal(psc$ids(), character(0L)) expect_data_table(as.data.table(psc), nrows = 0L) # 1 empty paramset - psc = ParamSetCollection$new(list(ParamSet$new())) + psc = ParamSetCollection$new(list(ParamSet_legacy$new())) expect_equal(psc$length, 0L) - expect_equal(psc$params, named_list()) + expect_equal(psc$subspaces(), named_list()) expect_equal(psc$ids(), character(0L)) expect_data_table(as.data.table(psc), nrows = 0L) }) test_that("no problems if we name the list of sets", { - ps = ParamSet$new(list(ParamDbl$new("test1"))) - ps$set_id = "paramset" - psc = ParamSetCollection$new(list(prefix = ps)) - expect_equal(names(psc$params), "paramset.test1") + ps = ParamSet_legacy$new(list(ParamDbl$new("test1"))) + psc = ParamSetCollection$new(list(paramset = ps)) + expect_equal(names(psc$subspaces()), "paramset.test1") }) test_that("no warning in printer, see issue 208", { - ps = ParamSet$new(list(ParamDbl$new("test1"))) - ps$set_id = "paramset" - psc = ParamSetCollection$new(list(ps)) + ps = ParamSet_legacy$new(list(ParamDbl$new("test1"))) + + psc = ParamSetCollection$new(list(paramset = ps)) psc$values = list(paramset.test1 = 1) expect_warning(capture_output(print(ps)), NA) }) - -test_that("collection reflects direct paramset$set_id change", { - ps = ParamSet$new(list(ParamDbl$new("d"))) - ps$set_id = "paramset" - psc = ParamSetCollection$new(list(ps)) - ps$values = list(d = 1) - expect_equal(psc$values, list(paramset.d = 1)) - ps$set_id = "foo" - expect_equal(psc$values, list(foo.d = 1)) - expect_equal(psc$params, list(foo.d = ParamDbl$new("foo.d"))) - - ps$set_id = "" - expect_equal(psc$values, list(d = 1)) - expect_equal(psc$params, list(d = ParamDbl$new("d"))) -}) - - test_that("collection allows state-change setting of paramvals, see issue 205", { - ps1 = ParamSet$new(list(ParamDbl$new("d1"))) - ps1$set_id = "s1" - ps2 = ParamSet$new(list(ParamDbl$new("d2"))) - ps2$set_id = "s2" - ps3 = ParamSet$new(list(ParamDbl$new("d3"))) - ps3$set_id = "" - - psc = ParamSetCollection$new(list(ps1, ps2, ps3)) + ps1 = ParamSet_legacy$new(list(ParamDbl$new("d1"))) + ps2 = ParamSet_legacy$new(list(ParamDbl$new("d2"))) + ps3 = ParamSet_legacy$new(list(ParamDbl$new("d3"))) + + psc = ParamSetCollection$new(list(s1 = ps1, s2 = ps2, ps3)) expect_equal(psc$values, named_list()) psc$values$s1.d1 = 1 # nolint expect_equal(psc$values, list(s1.d1 = 1)) @@ -237,28 +207,23 @@ test_that("collection allows state-change setting of paramvals, see issue 205", }) test_that("set_id inference in values assignment works now", { - psa = ParamSet$new(list(ParamDbl$new("parama"))) - psa$set_id = "a.b" + psa = ParamSet_legacy$new(list(ParamDbl$new("parama"))) + + psb = ParamSet_legacy$new(list(ParamDbl$new("paramb"))) - psb = ParamSet$new(list(ParamDbl$new("paramb"))) - psb$set_id = "b" + psc = ParamSet_legacy$new(list(ParamDbl$new("paramc"))) - psc = ParamSet$new(list(ParamDbl$new("paramc"))) - psc$set_id = "c" + pscol1 = ParamSetCollection$new(list(b = psb, c = psc)) - pscol1 = ParamSetCollection$new(list(psb, psc)) - pscol1$set_id = "a" + pscol2 = ParamSetCollection$new(list(a.b = psa, a = pscol1)) - pscol2 = ParamSetCollection$new(list(psa, pscol1)) + pstest = ParamSet_legacy$new(list(ParamDbl$new("paramc"))) - pstest = ParamSet$new(list(ParamDbl$new("paramc"))) - pstest$set_id = "a.c" + expect_error(pscol2$add(pstest, n = "a.c"), "would lead to nameclashes.*a\\.c\\.paramc") - expect_error(pscol2$add(pstest), "nameclashes.* a\\.c\\.paramc") + pstest = ParamSet_legacy$new(list(ParamDbl$new("a.c.paramc"))) - pstest = ParamSet$new(list(ParamDbl$new("a.c.paramc"))) - pstest$set_id = "" - expect_error(pscol2$add(pstest), "nameclashes.* a\\.c\\.paramc") + expect_error(pscol2$add(pstest), "would lead to nameclashes.*a\\.c\\.paramc") pscol2$values = list(a.c.paramc = 3, a.b.parama = 1, a.b.paramb = 2) @@ -268,6 +233,6 @@ test_that("set_id inference in values assignment works now", { expect_equal(pscol1$values, list(b.paramb = 2, c.paramc = 3)) expect_equal(pscol2$values, list(a.b.parama = 1, a.b.paramb = 2, a.c.paramc = 3)) - expect_error(ParamSetCollection$new(list(pscol1, pstest)), + expect_error(ParamSetCollection$new(list(a = pscol1, pstest)), "duplicated parameter.* a\\.c\\.paramc") }) diff --git a/tests/testthat/test_ParamUty.R b/tests/testthat/test_ParamUty.R index 77a9af3f..589b3060 100644 --- a/tests/testthat/test_ParamUty.R +++ b/tests/testthat/test_ParamUty.R @@ -2,21 +2,21 @@ context("ParamUty") test_that("ParamUty", { p = ParamUty$new(id = "x") - expect_true(p$check(FALSE)) - expect_true(p$check(NULL)) - expect_true(p$check(NA)) + expect_true(p$check(list(x = FALSE))) + expect_true(p$check(list(x = NULL))) + expect_true(p$check(list(x = NA))) p = ParamUty$new(id = "x", custom_check = function(x) if (is.null(x)) "foo" else TRUE) - expect_true(p$check(FALSE)) - expect_string(p$check(NULL), fixed = "foo") - expect_true(p$check(NA)) + expect_true(p$check(list(x = FALSE))) + expect_string(p$check(list(x = NULL)), fixed = "foo") + expect_true(p$check(list(x = NA))) p = ParamUty$new(id = "x", default = Inf) }) test_that("R6 values of ParamUty are cloned", { - ps = ParamSet$new(list(ParamUty$new("x"))) + ps = ParamSet_legacy$new(list(ParamUty$new("x"))) ps$values$x = R6Class("testclass", public = list(x = NULL))$new() psclone = ps$clone(deep = TRUE) @@ -28,3 +28,7 @@ test_that("R6 values of ParamUty are cloned", { expect_true(psunclone$values$x$x) # reference check: value was not cloned expect_null(psclone$values$x$x) # was cloned before change --> should still be null }) + +test_that("default NULL works", { + expect_equal(p_uty(default = NULL)$cargo[[1]]$repr, "NULL") +}) diff --git a/tests/testthat/test_Param_rep.R b/tests/testthat/test_Param_rep.R index 1ba731b0..91e76a73 100644 --- a/tests/testthat/test_Param_rep.R +++ b/tests/testthat/test_Param_rep.R @@ -2,31 +2,22 @@ context("Repeated params") test_that("rep params work", { p = ParamDbl$new(id = "x", lower = 1, upper = 3) - ps = p$rep(2L) + ps = ps_replicate(p, 2) expect_r6(ps, "ParamSet") expect_equal(ps$length, 2L) expect_subset(ps$class, "ParamDbl") - expect_equal(ps$ids(), c("x_rep_1", "x_rep_2")) + expect_equal(ps$ids(), c("rep1.x", "rep2.x")) expect_subset(ps$lower, 1) expect_subset(ps$upper, 3) p = ParamFct$new(id = "kk", levels = c("a", "b")) - ps = p$rep(3L) + ps = ps_replicate(p, 3) expect_r6(ps, "ParamSet") expect_equal(ps$length, 3L) expect_subset(ps$class, "ParamFct") - expect_equal(ps$ids(), c("kk_rep_1", "kk_rep_2", "kk_rep_3")) + expect_equal(ps$ids(), c("rep1.kk", "rep2.kk", "rep3.kk")) for (id in ps$ids()) { - expect_equal(ps$params[[id]]$levels, c("a", "b")) + expect_equal(ps$levels[[id]], c("a", "b")) } }) - -test_that("rep params deep copies", { - p = ParamDbl$new(id = "x", lower = 1, upper = 3) - ps = p$rep(1L) - # lets change the first param - p$lower = 99 - expect_equal(p$lower, 99) - expect_equal(ps$params[["x_rep_1"]]$lower, 1) -}) diff --git a/tests/testthat/test_deps.R b/tests/testthat/test_deps.R index 0d3ab275..0762ca04 100644 --- a/tests/testthat/test_deps.R +++ b/tests/testthat/test_deps.R @@ -3,27 +3,27 @@ context("Dependencies") test_that("basic example works", { ps = th_paramset_full() expect_false(ps$has_deps) - ps$add_dep("th_param_int", on = "th_param_fct", CondEqual$new("a")) + ps$add_dep("th_param_int", on = "th_param_fct", CondEqual("a")) expect_true(ps$has_deps) x = list(th_param_int = 1) - expect_string(ps$check(x), fixed = "The parameter 'th_param_int' can only be set") + expect_string(ps$check(x, check_strict = TRUE), fixed = "th_param_int: can only be set") x = list(th_param_int = 1, th_param_fct = "a") - expect_true(ps$check(x)) + expect_true(ps$check(x, check_strict = TRUE)) x = list(th_param_int = 1, th_param_fct = "b") - expect_string(ps$check(x), fixed = "The parameter 'th_param_int' can only be set") + expect_string(ps$check(x, check_strict = TRUE), fixed = "th_param_int: can only be set") x = list(th_param_int = NA, th_param_fct = "b") - expect_string(ps$check(x), fixed = "May not be NA") + expect_string(ps$check(x, check_strict = TRUE), fixed = "May not be NA") x = list(th_param_fct = "a") - expect_true(ps$check(x)) + expect_true(ps$check(x, check_strict = TRUE)) x = list(th_param_fct = "b") - expect_true(ps$check(x)) + expect_true(ps$check(x, check_strict = TRUE)) x = list(th_param_dbl = 1.3) - expect_true(ps$check(x)) + expect_true(ps$check(x, check_strict = TRUE)) # test printer, with 2 deps ps = th_paramset_full() - ps$add_dep("th_param_int", on = "th_param_fct", CondEqual$new("a")) - ps$add_dep("th_param_int", on = "th_param_lgl", CondEqual$new(TRUE)) + ps$add_dep("th_param_int", on = "th_param_fct", CondEqual("a")) + ps$add_dep("th_param_int", on = "th_param_lgl", CondEqual(TRUE)) expect_output(print(ps), "th_param_fct,th_param_lgl") # test that we can remove deps @@ -35,60 +35,60 @@ test_that("basic example works", { test_that("nested deps work", { ps = th_paramset_full() - ps$add_dep("th_param_int", on = "th_param_fct", CondAnyOf$new(c("a", "b"))) - ps$add_dep("th_param_dbl", on = "th_param_lgl", CondEqual$new(TRUE)) - ps$add_dep("th_param_lgl", on = "th_param_fct", CondEqual$new("c")) + ps$add_dep("th_param_int", on = "th_param_fct", CondAnyOf(c("a", "b"))) + ps$add_dep("th_param_dbl", on = "th_param_lgl", CondEqual(TRUE)) + ps$add_dep("th_param_lgl", on = "th_param_fct", CondEqual("c")) x1 = list(th_param_int = 1) - expect_string(ps$check(x1), fixed = "The parameter 'th_param_int' can only be set") + expect_string(ps$check(x1, check_strict = TRUE), fixed = "th_param_int: can only be set") x2 = list(th_param_int = 1, th_param_fct = "b") - expect_true(ps$check(x2)) + expect_true(ps$check(x2, check_strict = TRUE)) x3 = list(th_param_int = 1, th_param_fct = "c") - expect_string(ps$check(x3), fixed = "The parameter 'th_param_int' can only be set") + expect_string(ps$check(x3, check_strict = TRUE), fixed = "th_param_int: can only be set") x4 = list(th_param_fct = "a") - expect_true(ps$check(x4)) + expect_true(ps$check(x4, check_strict = TRUE)) x5 = list(th_param_dbl = 1.3) - expect_string(ps$check(x5), fixed = "The parameter 'th_param_dbl' can only be set") + expect_string(ps$check(x5, check_strict = TRUE), fixed = "th_param_dbl: can only be set") x6 = list(th_param_fct = "c", th_param_lgl = TRUE, th_param_dbl = 3) - expect_true(ps$check(x6)) + expect_true(ps$check(x6, check_strict = TRUE)) }) test_that("adding 2 sets with deps works", { - ps1 = ParamSet$new(list( + ps1 = ParamSet_legacy$new(list( ParamFct$new("x1", levels = c("a", "b")), ParamDbl$new("y1") )) - ps1$add_dep("y1", on = "x1", CondEqual$new("a")) + ps1$add_dep("y1", on = "x1", CondEqual("a")) - ps2 = ParamSet$new(list( + ps2 = ParamSet_legacy$new(list( ParamFct$new("x2", levels = c("a", "b")), ParamDbl$new("y2") )) - ps2$add_dep("y2", on = "x2", CondEqual$new("a")) + ps2$add_dep("y2", on = "x2", CondEqual("a")) - ps1$add(ps2) + ps1 = ps_union(list(ps1, ps2)) expect_equal(ps1$length, 4L) expect_true(ps1$has_deps) expect_data_table(ps1$deps, nrows = 2) # do a few feasibility checks on larger set - expect_true(ps1$test(list(x1 = "a", y1 = 1, x2 = "a", y2 = 1))) - expect_true(ps1$test(list(x1 = "a", y1 = 1))) - expect_false(ps1$test(list(x1 = "b", y1 = 1))) - expect_true(ps1$test(list(x2 = "a", y2 = 1))) - expect_false(ps1$test(list(x2 = "b", y2 = 1))) + expect_true(ps1$test(list(x1 = "a", y1 = 1, x2 = "a", y2 = 1), check_strict = TRUE)) + expect_true(ps1$test(list(x1 = "a", y1 = 1), check_strict = TRUE)) + expect_false(ps1$test(list(x1 = "b", y1 = 1), check_strict = TRUE)) + expect_true(ps1$test(list(x2 = "a", y2 = 1), check_strict = TRUE)) + expect_false(ps1$test(list(x2 = "b", y2 = 1), check_strict = TRUE)) }) test_that("subsetting with deps works", { - ps = ParamSet$new(list( + ps = ParamSet_legacy$new(list( ParamFct$new("a", levels = c("a", "b")), ParamFct$new("b", levels = c("a", "b")), ParamFct$new("c", levels = c("a", "b")), ParamFct$new("d", levels = c("a", "b")) )) - ps$add_dep("a", on = "b", CondEqual$new("a")) - ps$add_dep("a", on = "c", CondEqual$new("a")) - ps$add_dep("b", on = "c", CondEqual$new("a")) + ps$add_dep("a", on = "b", CondEqual("a")) + ps$add_dep("a", on = "c", CondEqual("a")) + ps$add_dep("b", on = "c", CondEqual("a")) ps$clone(deep = TRUE)$subset("d") ps$clone(deep = TRUE)$subset(c("a", "b", "c")) @@ -97,26 +97,26 @@ test_that("subsetting with deps works", { }) test_that("cannot add a dep on yourself", { - ps = ParamSet$new(list(ParamFct$new("x", levels = c("a")))) - expect_error(ps$add_dep("x", on = "x", CondEqual$new("a")), "depend on itself") + ps = ParamSet_legacy$new(list(ParamFct$new("x", levels = c("a")))) + expect_error(ps$add_dep("x", on = "x", CondEqual("a")), "depend on itself") }) test_that("we can also dep on integer", { - ps = ParamSet$new(list( + ps = ParamSet_legacy$new(list( ParamInt$new("i", lower = 0, upper = 9), ParamDbl$new("d", lower = 0, upper = 9) )) - ps$add_dep("d", on = "i", CondAnyOf$new(1:3)) + ps$add_dep("d", on = "i", CondAnyOf(1:3)) - expect_true(ps$check(list(i = 2, d = 5))) - expect_string(ps$check(list(i = 5, d = 5))) + expect_true(ps$check(list(i = 2, d = 5), check_strict = TRUE)) + expect_string(ps$check(list(i = 5, d = 5), check_strict = TRUE)) }) test_that("deps make sense", { ps = th_paramset_full() - expect_error(ps$add_dep("th_param_lgl", "th_param_fct", CondEqual$new("d")), + expect_error(ps$add_dep("th_param_lgl", "th_param_fct", CondEqual("d")), "Condition has infeasible values for th_param_fct") - expect_error(ps$add_dep("th_param_lgl", "th_param_int", CondAnyOf$new(5:15)), + expect_error(ps$add_dep("th_param_lgl", "th_param_int", CondAnyOf(5:15)), "Condition has infeasible values for th_param_int") }) diff --git a/tests/testthat/test_domain.R b/tests/testthat/test_domain.R index 500720b8..1a29fe1d 100644 --- a/tests/testthat/test_domain.R +++ b/tests/testthat/test_domain.R @@ -13,44 +13,41 @@ test_that("p_xxx printers", { expect_output(print(p_uty()), "p_uty\\(\\)") expect_output(print(p_fct("a")), "p_fct\\(levels = \"a\"\\)") - expect_output(print(p_fct(1)), "p_fct\\(levels = \"1\"\\)") - expect_output(print(p_fct(list(x = 1))), "p_fct\\(levels = \"x\"\\)") + expect_output(print(p_fct("1")), "p_fct\\(levels = \"1\"\\)") + expect_output(print(p_fct(list(x = 1))), "p_fct\\(levels = list\\(x = 1\\)\\)") - expect_output(print(p_fct(list(x = 1), depends = x == 1)), "p_fct\\(levels = \"x\"\\, depends = x == 1)") + expect_output(print(p_fct(list(x = 1), depends = x == 1)), "p_fct\\(levels = list\\(x = 1\\)\\, depends = x == 1)") reqquote = quote(x == 1) - expect_output(print(p_fct(list(x = 1), depends = reqquote)), "p_fct\\(levels = \"x\"\\, depends = x == 1)") + expect_output(print(p_fct(list(x = 1), depends = reqquote)), "p_fct\\(levels = list\\(x = 1\\)\\, depends = x == 1)") }) test_that("ps(p_xxx(...)) creates ParamSets", { - expect_equal(ps(x = p_int()), ParamSet$new(list(ParamInt$new("x")))) - expect_equal(ps(x = p_dbl()), ParamSet$new(list(ParamDbl$new("x")))) - expect_equal(ps(x = p_uty()), ParamSet$new(list(ParamUty$new("x")))) - expect_equal(ps(x = p_lgl()), ParamSet$new(list(ParamLgl$new("x")))) - expect_equal(ps(x = p_fct(letters)), ParamSet$new(list(ParamFct$new("x", letters)))) + expect_equal_ps(ps(x = p_int()), ParamSet_legacy$new(list(ParamInt$new("x")))) + expect_equal_ps(ps(x = p_dbl()), ParamSet_legacy$new(list(ParamDbl$new("x")))) + expect_equal_ps(ps(x = p_uty()), ParamSet_legacy$new(list(ParamUty$new("x")))) + expect_equal_ps(ps(x = p_lgl()), ParamSet_legacy$new(list(ParamLgl$new("x")))) + expect_equal_ps(ps(x = p_fct(letters)), ParamSet_legacy$new(list(ParamFct$new("x", letters)))) - expect_equal(ps(x = p_int(upper = 1, lower = 0)), ParamSet$new(list(ParamInt$new("x", 0, 1)))) - expect_equal(ps(x = p_dbl(upper = 1, lower = 0)), ParamSet$new(list(ParamDbl$new("x", 0, 1)))) + expect_equal_ps(ps(x = p_int(upper = 1, lower = 0)), ParamSet_legacy$new(list(ParamInt$new("x", 0, 1)))) + expect_equal_ps(ps(x = p_dbl(upper = 1, lower = 0)), ParamSet_legacy$new(list(ParamDbl$new("x", 0, 1)))) - expect_equal(ps(x = p_int(special_vals = list("x"), default = 0, tags = "required")), - ParamSet$new(list(ParamInt$new("x", special_vals = list("x"), default = 0, tags = "required")))) - expect_equal(ps(x = p_dbl(special_vals = list("x"), default = 0, tags = "required")), - ParamSet$new(list(ParamDbl$new("x", special_vals = list("x"), default = 0, tags = "required")))) + expect_equal_ps(ps(x = p_int(special_vals = list("x"), default = 0, tags = "xx")), + ParamSet_legacy$new(list(ParamInt$new("x", special_vals = list("x"), default = 0, tags = "xx")))) + expect_equal_ps(ps(x = p_dbl(special_vals = list("x"), default = 0, tags = "xx")), + ParamSet_legacy$new(list(ParamDbl$new("x", special_vals = list("x"), default = 0, tags = "xx")))) - expect_equal(ps(x = p_lgl(special_vals = list("x"), default = TRUE, tags = "required")), - ParamSet$new(list(ParamLgl$new("x", special_vals = list("x"), default = TRUE, tags = "required")))) + expect_equal_ps(ps(x = p_lgl(special_vals = list("x"), default = TRUE, tags = "xx")), + ParamSet_legacy$new(list(ParamLgl$new("x", special_vals = list("x"), default = TRUE, tags = "xx")))) - expect_equal(ps(x = p_fct(letters, special_vals = list(0), default = 0, tags = "required")), - ParamSet$new(list(ParamFct$new("x", letters, special_vals = list(0), default = 0, tags = "required")))) + expect_equal_ps(ps(x = p_fct(letters, special_vals = list(0), default = 0, tags = "xx")), + ParamSet_legacy$new(list(ParamFct$new("x", letters, special_vals = list(0), default = 0, tags = "xx")))) - expect_equal(ps(x = p_uty(default = 1, tags = "required", custom_check = check_int)), - ParamSet$new(list(ParamUty$new("x", default = 1, tags = "required", custom_check = check_int)))) + expect_equal_ps(ps(x = p_uty(default = 1, tags = "xx", custom_check = check_int)), + ParamSet_legacy$new(list(ParamUty$new("x", default = 1, tags = "xx", custom_check = check_int)))) expect_error(ps(x = p_int(), x = p_int()), "unique names") - expect_equal(ps(x = p_uty(default = 1, tags = "required", custom_check = check_int)), - ps(x = ParamUty$new("y", default = 1, tags = "required", custom_check = check_int))) - expect_error(p_int(id = 1), "unused argument.*id") }) @@ -90,17 +87,17 @@ test_that("p_fct autotrafo", { test_that("requirements in domains", { - simpleps = ParamSet$new(list(ParamInt$new("x"), ParamDbl$new("y")))$add_dep("y", "x", CondEqual$new(1)) + simpleps = ParamSet_legacy$new(list(ParamInt$new("x"), ParamDbl$new("y")))$add_dep("y", "x", CondEqual(1)) # basic equality expression - expect_equal( + expect_equal_ps( ps( x = p_int(), y = p_dbl(depends = x == 1) ), simpleps) # quote() is accepted - expect_equal( + expect_equal_ps( ps( x = p_int(), y = p_dbl(depends = quote(x == 1)) @@ -108,72 +105,72 @@ test_that("requirements in domains", { # using a expression variable reqquote = quote(x == 1) - expect_equal( + expect_equal_ps( ps( x = p_int(), y = p_dbl(depends = reqquote) ), simpleps) # the same for `p_fct`, which behaves slightly differently from the rest - simpleps = ParamSet$new(list(ParamInt$new("x"), ParamFct$new("y", letters)))$add_dep("y", "x", CondEqual$new(1)) - expect_equal( + simpleps = ParamSet_legacy$new(list(ParamInt$new("x"), ParamFct$new("y", letters)))$add_dep("y", "x", CondEqual(1)) + expect_equal_ps( ps( x = p_int(), y = p_fct(letters, depends = x == 1) ), simpleps) reqquote = quote(x == 1) - expect_equal( + expect_equal_ps( ps( x = p_int(), y = p_fct(letters, depends = reqquote) ), simpleps) # the same for `p_fct` involving autotrafo, which behaves slightly differently from the rest - simpleps = ps(x = p_int(), y = p_fct(list(a = 1, b = 2)))$add_dep("y", "x", CondEqual$new(1)) - expect_equal( + simpleps = ps(x = p_int(), y = p_fct(list(a = 1, b = 2)))$add_dep("y", "x", CondEqual(1)) + expect_equal_ps( ps( x = p_int(), y = p_fct(list(a = 1, b = 2), depends = x == 1) ), simpleps) reqquote = quote(x == 1) - expect_equal( + expect_equal_ps( ps( x = p_int(), y = p_fct(list(a = 1, b = 2), depends = reqquote) ), simpleps) # `&&` - expect_equal( + expect_equal_ps( ps( x = p_int(), y = p_dbl(depends = x == 1 && x == 3) ), - ParamSet$new(list(ParamInt$new("x"), ParamDbl$new("y")))$add_dep("y", "x", CondEqual$new(1))$add_dep("y", "x", CondEqual$new(3))) + ParamSet_legacy$new(list(ParamInt$new("x"), ParamDbl$new("y")))$add_dep("y", "x", CondEqual(1))$add_dep("y", "x", CondEqual(3))) # `&&`, `%in%` - expect_equal( + expect_equal_ps( ps( x = p_int(), z = p_fct(letters[1:3]), y = p_dbl(depends = x == 1 && z %in% c("a", "b")) ), - ParamSet$new(list(ParamInt$new("x"), ParamFct$new("z", letters[1:3]), ParamDbl$new("y")))$ - add_dep("y", "x", CondEqual$new(1))$add_dep("y", "z", CondAnyOf$new(c("a", "b")))) + ParamSet_legacy$new(list(ParamInt$new("x"), ParamFct$new("z", letters[1:3]), ParamDbl$new("y")))$ + add_dep("y", "x", CondEqual(1))$add_dep("y", "z", CondAnyOf(c("a", "b")))) # recursive dependencies - expect_equal( + expect_equal_ps( ps( x = p_int(), z = p_fct(letters[1:3], depends = x == 2), y = p_dbl(depends = x == 1 && z %in% c("a", "b")) ), - ParamSet$new(list(ParamInt$new("x"), ParamFct$new("z", letters[1:3]), ParamDbl$new("y")))$ - add_dep("z", "x", CondEqual$new(2))$add_dep("y", "x", CondEqual$new(1))$add_dep("y", "z", CondAnyOf$new(c("a", "b")))) + ParamSet_legacy$new(list(ParamInt$new("x"), ParamFct$new("z", letters[1:3]), ParamDbl$new("y")))$ + add_dep("z", "x", CondEqual(2))$add_dep("y", "x", CondEqual(1))$add_dep("y", "z", CondAnyOf(c("a", "b")))) # `fct` with complex requirements - complexps = ParamSet$new(list(ParamInt$new("x"), ParamFct$new("z", letters[1:3]), ParamFct$new("y", letters[1:3])))$ - add_dep("y", "x", CondEqual$new(1))$add_dep("y", "z", CondAnyOf$new(c("a", "b"))) - expect_equal( + complexps = ParamSet_legacy$new(list(ParamInt$new("x"), ParamFct$new("z", letters[1:3]), ParamFct$new("y", letters[1:3])))$ + add_dep("y", "x", CondEqual(1))$add_dep("y", "z", CondAnyOf(c("a", "b"))) + expect_equal_ps( ps( x = p_int(), z = p_fct(letters[1:3]), @@ -181,7 +178,7 @@ test_that("requirements in domains", { ), complexps) # parentheses are ignored - expect_equal( + expect_equal_ps( ps( x = p_int(), z = p_fct(letters[1:3]), @@ -189,15 +186,15 @@ test_that("requirements in domains", { ), complexps) # multiple dependencies on the same value - expect_equal( + expect_equal_ps( ps( x = p_int(), z = p_fct(letters[1:3]), y = p_fct(letters[1:3], depends = ((((x == 1)) && (z %in% c("a", "b") && z == "a")))) ), - ParamSet$new(list(ParamInt$new("x"), ParamFct$new("z", letters[1:3]), ParamFct$new("y", letters[1:3])))$ - add_dep("y", "x", CondEqual$new(1))$add_dep("y", "z", CondAnyOf$new(c("a", "b")))$ - add_dep("y", "z", CondEqual$new("a"))) + ParamSet_legacy$new(list(ParamInt$new("x"), ParamFct$new("z", letters[1:3]), ParamFct$new("y", letters[1:3])))$ + add_dep("y", "x", CondEqual(1))$add_dep("y", "z", CondAnyOf(c("a", "b")))$ + add_dep("y", "z", CondEqual("a"))) expect_error(p_int(depends = 1 == x), "must be a parameter name") expect_error(p_int(depends = 1), "must be an expression") @@ -299,54 +296,54 @@ test_that("logscale in domains", { }) -test_that("$.has_logscale flag works", { +test_that("$is_logscale flags work", { pps = ps(x = p_int(1, 2, logscale = TRUE)) - expect_true(get_private(pps$params[["x"]])$.has_logscale) + expect_equal(pps$is_logscale, c(x = TRUE)) pps = ps(x = p_int(1, 2, logscale = TRUE), y = p_int(10, 20)) - expect_equal(map_lgl(pps$params, function(param) get_private(param)$.has_logscale), c(x = TRUE, y = FALSE)) + expect_equal(pps$is_logscale, c(x = TRUE, y = FALSE)) pps = ps(x = p_int(1, 2, logscale = TRUE), y = p_int(10, 20), z = p_int(1, 2, trafo = function(x) 2^x)) - expect_equal(map_lgl(pps$params, function(param) get_private(param)$.has_logscale), c(x = TRUE, y = FALSE, z = FALSE)) + expect_equal(pps$is_logscale, c(x = TRUE, y = FALSE, z = FALSE)) }) -test_that("$.has_trafo flag works", { +test_that("$has_trafo_param flags work", { pps = ps(x = p_int(1, 2, trafo = function(x) 2^x)) - expect_true(get_private(pps$params[["x"]])$.has_trafo) + expect_equal(pps$has_trafo_param, c(x = TRUE)) pps = ps(x = p_int(1, 2, trafo = function(x) 2^x), y = p_int(10, 20)) - expect_equal(map_lgl(pps$params, function(param) get_private(param)$.has_trafo), c(x = TRUE, y = FALSE)) + expect_equal(pps$has_trafo_param, c(x = TRUE, y = FALSE)) pps = ps(x = p_int(1, 2, trafo = function(x) 2^x), y = p_int(10, 20), z = p_int(1, 2, logscale = TRUE)) - expect_equal(map_lgl(pps$params, function(param) get_private(param)$.has_trafo), c(x = TRUE, y = FALSE, z = FALSE)) + expect_equal(pps$has_trafo_param, c(x = TRUE, y = FALSE, z = TRUE)) }) -test_that("$.extra_trafo flag works", { +test_that("$extra_trafo flag works", { pps = ps(x = p_int(1, 2), .extra_trafo = function(x, param_set) { x = 1 x }) - expect_true(get_private(pps)$.has_extra_trafo) + expect_true(pps$has_extra_trafo) pps = ps(x = p_int(1, 2, logscale = TRUE)) - expect_false(get_private(pps)$.has_extra_trafo) + expect_false(pps$has_extra_trafo) - pps$trafo = function(x, param_set) { + pps$extra_trafo = function(x, param_set) { x = 1 x } - expect_true(get_private(pps)$.has_extra_trafo) + expect_true(pps$has_extra_trafo) - pps$trafo = NULL - expect_false(get_private(pps)$.has_extra_trafo) + pps$extra_trafo = NULL + expect_false(pps$has_extra_trafo) pps = ps(x = p_int(1, 10)) pps$values$x = to_tune() search_space = pps$search_space() - expect_false(get_private(search_space)$.has_extra_trafo) + expect_false(search_space$has_extra_trafo) pps = ps(x = p_int(1, 10)) pps$values$x = to_tune(logscale = TRUE) search_space = pps$search_space() - expect_false(get_private(search_space)$.has_extra_trafo) + expect_false(search_space$has_extra_trafo) }) diff --git a/tests/testthat/test_generate_design.R b/tests/testthat/test_generate_design.R index ca77c3e3..3f7b71ff 100644 --- a/tests/testthat/test_generate_design.R +++ b/tests/testthat/test_generate_design.R @@ -2,14 +2,14 @@ context("generate_design") test_that("generate_design_random", { ps_list = list( - th_paramset_dbl1(), - th_paramset_full(), - th_paramset_repeated(), - th_paramset_numeric() + dbl = th_paramset_dbl1(), + full = th_paramset_full(), + repeated = th_paramset_repeated(), + numeric = th_paramset_numeric() ) - for (ps in ps_list) { - info = ps$set_id + for (info in names(ps_list)) { + ps = ps_list[[info]] d = generate_design_random(ps, n = 5L) dd = d$data expect_data_table(dd, any.missing = FALSE, nrows = 5L, ncols = ps$length, info = info) @@ -19,14 +19,14 @@ test_that("generate_design_random", { test_that("generate_design_grid", { ps_list = list( - th_paramset_dbl1(), - th_paramset_full(), - th_paramset_repeated(), - th_paramset_numeric() + dbl = th_paramset_dbl1(), + full = th_paramset_full(), + repeated = th_paramset_repeated(), + numeric = th_paramset_numeric() ) - for (ps in ps_list) { - info = ps$set_id + for (info in names(ps_list)) { + ps = ps_list[[info]] reso = 3L d = generate_design_grid(ps, resolution = reso) dd = d$data @@ -41,18 +41,18 @@ test_that("generate_design_grid", { }) test_that("generate_design_grid with different resolutions and egde cases", { - ps = ParamSet$new(list(ParamFct$new("f", levels = letters[1:2]))) + ps = ParamSet_legacy$new(list(ParamFct$new("f", levels = letters[1:2]))) d = generate_design_grid(ps) expect_data_table(d$data, any.missing = FALSE, nrows = 2, ncols = 1) - ps = ParamSet$new(list( + ps = ParamSet_legacy$new(list( ParamFct$new("f", levels = letters[1:2]), ParamDbl$new("d", lower = 0, upper = 1) )) d = generate_design_grid(ps, param_resolutions = c(d = 3)) expect_data_table(d$data, any.missing = FALSE, nrows = 6, ncols = 2) - ps = ParamSet$new(list( + ps = ParamSet_legacy$new(list( ParamInt$new("x", lower = 0, upper = 10), ParamInt$new("y", lower = 0, upper = 10) )) @@ -68,7 +68,7 @@ test_that("generate_design_grid with different resolutions and egde cases", { expect_equal(length(unique(dd$x)), 4) expect_equal(length(unique(dd$y)), 3) - ps = ParamSet$new(list( + ps = ParamSet_legacy$new(list( ParamInt$new("x", lower = 0, upper = 10), ParamInt$new("y", lower = 0, upper = 10), ParamLgl$new("z") @@ -82,7 +82,7 @@ test_that("generate_design_grid with different resolutions and egde cases", { }) test_that("check generate_design_grid against concrete expectation", { - ps = ParamSet$new(list( + ps = ParamSet_legacy$new(list( ParamDbl$new("x", lower = 1, upper = 3), ParamFct$new("y", levels = c("a", "b")) )) @@ -95,14 +95,14 @@ test_that("generate_design_lhs", { skip_if_not_installed("lhs") ps_list = list( - th_paramset_dbl1(), - th_paramset_full(), - th_paramset_repeated(), - th_paramset_numeric() + dbl = th_paramset_dbl1(), + full = th_paramset_full(), + repeated = th_paramset_repeated(), + numeric = th_paramset_numeric() ) - for (ps in ps_list) { - info = ps$set_id + for (info in names(ps_list)) { + ps = ps_list[[info]] d = generate_design_lhs(ps, 10) dd = d$data expect_data_table(d$data, nrows = 10, any.missing = FALSE, info = info) @@ -143,7 +143,7 @@ test_that("generate_design_random and grid works with deps", { test_that("generate_design_random with zero rows", { ps = th_paramset_full() d = generate_design_random(ps, n = 0) - expect_data_table(d$data, any.missing = FALSE, nrows = 0, ncols = ps$length, info = ps$set_id) + expect_data_table(d$data, any.missing = FALSE, nrows = 0, ncols = ps$length) }) test_that("generate_design_lhs with zero rows", { @@ -151,27 +151,27 @@ test_that("generate_design_lhs with zero rows", { ps = th_paramset_full() d = generate_design_lhs(ps, n = 0) - expect_data_table(d$data, any.missing = FALSE, nrows = 0, ncols = ps$length, info = ps$set_id) + expect_data_table(d$data, any.missing = FALSE, nrows = 0, ncols = ps$length) }) test_that("generate_design_grid with zero rows", { ps = th_paramset_full() d = generate_design_grid(ps, resolution = 0) - expect_data_table(d$data, any.missing = FALSE, nrows = 0, ncols = ps$length, info = ps$set_id) + expect_data_table(d$data, any.missing = FALSE, nrows = 0, ncols = ps$length) }) test_that("generate_design_sobol", { skip_if_not_installed("spacefillr") ps_list = list( - th_paramset_dbl1(), - th_paramset_full(), - th_paramset_repeated(), - th_paramset_numeric() + dbl = th_paramset_dbl1(), + full = th_paramset_full(), + repeated = th_paramset_repeated(), + numeric = th_paramset_numeric() ) - for (ps in ps_list) { - info = ps$set_id + for (info in names(ps_list)) { + ps = ps_list[[info]] d = generate_design_sobol(ps, 10) dd = d$data expect_data_table(d$data, nrows = 10, any.missing = FALSE, info = info) @@ -195,6 +195,6 @@ test_that("generate_design_sobol with zero rows", { ps = th_paramset_full() d = generate_design_sobol(ps, n = 0) - expect_data_table(d$data, any.missing = FALSE, nrows = 0, ncols = ps$length, info = ps$set_id) + expect_data_table(d$data, any.missing = FALSE, nrows = 0, ncols = ps$length) }) diff --git a/tests/testthat/test_param_vals.R b/tests/testthat/test_param_vals.R index 13ed72dc..7a36b68c 100644 --- a/tests/testthat/test_param_vals.R +++ b/tests/testthat/test_param_vals.R @@ -1,7 +1,7 @@ context("values") test_that("values", { - ps = ParamSet$new(list( + ps = ParamSet_legacy$new(list( ParamDbl$new(id = "d", lower = 0, upper = 1), ParamInt$new(id = "i", lower = 1, upper = 3), ParamFct$new(id = "f", levels = letters[1:3]) @@ -12,24 +12,24 @@ test_that("values", { ps$values = list(d = 1, f = "a") expect_true(ps$check(list(d = 0, f = "a"))) ps2 = ps$clone() - ps2$subset(ids = c("d", "i")) + ps2 = ps2$subset(ids = c("d", "i")) expect_equal(ps2$values, list(d = 1)) ps2$values = list(d = 0.5) expect_true(ps$check(list(d = 1, f = "a"))) expect_equal(ps2$values, list(d = 0.5)) # check printer - expect_output(print(ps2), "d.*.*0.5") + expect_output(print(ps2), "d.*.*0.5") ps2 = ps$clone() - ps2$subset(ids = c("i")) + ps2 = ps2$subset(ids = c("i")) expect_equal(ps2$values, set_names(list(), character(0))) - ps3 = ParamSet$new(list( + ps3 = ParamSet_legacy$new(list( ParamDbl$new(id = "x", lower = 0, upper = 9) )) ps3$values = list(x = 7) ps2 = ps$clone() - ps2$add(ps3) + ps2 = ps_union(list(ps2, ps3)) expect_equal(ps2$values, list(d = 1, f = "a", x = 7)) # designs @@ -62,7 +62,7 @@ test_that("values", { test_that("values calls assert", { # most of the tests should be done for ParamSet$check, so we simply # check here, that paramvals calls assert - ps = ParamSet$new(list( + ps = ParamSet_legacy$new(list( ParamDbl$new(id = "d", lower = 0, upper = 1), ParamInt$new(id = "i", lower = 1, upper = 3), ParamFct$new(id = "f", levels = letters[1:3]) @@ -72,8 +72,8 @@ test_that("values calls assert", { # now check that we can disable assert ps$assert_values = FALSE - ps$values = list(xxx = 1) - expect_equal(ps$values, list(xxx = 1)) ps$values = list(d = 9) expect_equal(ps$values, list(d = 9)) }) + + diff --git a/tests/testthat/test_sampler.R b/tests/testthat/test_sampler.R index 8e42d2ba..ee856759 100644 --- a/tests/testthat/test_sampler.R +++ b/tests/testthat/test_sampler.R @@ -8,14 +8,14 @@ test_that("1d samplers: basic tests", { ParamLgl = list(Sampler1DUnif, Sampler1DCateg) ) ps = th_paramset_full() - for (p in ps$params) { + for (p in ps$subspaces()) { ss = samplers[[p$class]] for (s in ss) { expect_error(s$new(ps()), "exactly 1 Param, but contains 0") - expect_error(s$new(ps(x = p, y = p)), "exactly 1 Param, but contains 2") - expect_class(s$new(ps(x = p)), "Sampler1D") + expect_error(s$new(ps_union(list(x = p, y = p))), "exactly 1 Param, but contains 2") + expect_class(s$new(p), "Sampler1D") s = s$new(p) - info = paste(p$id, "-", class(s)[[1L]]) + info = paste(p$ids(), "-", class(s)[[1L]]) n = 5L x = s$sample(n) d = x$data @@ -26,7 +26,7 @@ test_that("1d samplers: basic tests", { expect_true(all(d1 >= p$lower & d1 <= p$upper), info = info) } if (p$class %in% c("ParamFct")) { - expect_true(all(d1 %in% p$levels), info = info) + expect_true(all(d1 %in% p$levels[[1]]), info = info) } expect_output(print(s), ""z2" dependency is actually kept. This may be useful. # if some parameter depends on y, that dependency is lost. nothing we can do here. @@ -195,33 +194,33 @@ test_that("Dependencies work", { # all dependencies lost expect_equal(nrow(tuneps$deps), 0) - pars = ParamSet$new(list( + pars = ParamSet_legacy$new(list( ParamInt$new("x", lower = 0, upper = 1), ParamInt$new("y", lower = 0, upper = 1), ParamInt$new("z", lower = 0, upper = 1), ParamInt$new("z2", lower = 0, upper = 1) )) - pars$add_dep("y", "x", CondEqual$new(1)) - pars$add_dep("x", "z", CondEqual$new(1)) - pars$add_dep("z2", "x", CondEqual$new(1)) + pars$add_dep("y", "x", CondEqual(1)) + pars$add_dep("x", "z", CondEqual(1)) + pars$add_dep("z2", "x", CondEqual(1)) # only the relevant dependency is kept tuneps = pars$search_space(list(x = to_tune(), y = to_tune())) - expect_equal(setindex(tuneps$deps, NULL), data.table(id = "y", on = "x", cond = list(CondEqual$new(1)))) + expect_equal(setindex(tuneps$deps, NULL), data.table(id = "y", on = "x", cond = list(CondEqual(1)))) #dependencies are kept between params, even if the dependor is trafo'd from other params tuneps = pars$search_space(list(x = to_tune(), y = to_tune(ps(y1 = p_int(0, 1), y2 = p_int(0, 1), .extra_trafo = function(x, param_set) list(abs(x$y1 - x$y2)))))) - expect_equal(setindex(tuneps$deps, NULL), data.table(id = c("y1", "y2"), on = c("x", "x"), cond = list(CondEqual$new(1)))) + expect_equal(setindex(tuneps$deps, NULL), data.table(id = c("y1", "y2"), on = c("x", "x"), cond = list(CondEqual(1)))) tuneps = pars$search_space(list(x = to_tune(), y = to_tune(ps(y1 = p_int(0, 1), y2 = p_int(0, 1, depends = y1 == 1), .extra_trafo = function(x, param_set) list(min(x$y1, x$y2, na.rm = TRUE)))))) # mixing dependencies from inside and outside - expect_equal(setindex(tuneps$deps, NULL), data.table(id = c("y2", "y1", "y2"), on = c("y1", "x", "x"), cond = list(CondEqual$new(1)))) + expect_equal(setindex(tuneps$deps, NULL), data.table(id = c("y2", "y1", "y2"), on = c("y1", "x", "x"), cond = list(CondEqual(1)))) - parsnodep = ParamSet$new(list( + parsnodep = ParamSet_legacy$new(list( ParamInt$new("x", lower = 0, upper = 1), ParamInt$new("y", lower = 0, upper = 1), ParamInt$new("z", lower = 0, upper = 1), @@ -231,14 +230,14 @@ test_that("Dependencies work", { # amazing: dependencies across to_tune tuneps = parsnodep$search_space(list(x = to_tune(p_int(0, 1, depends = y == 0)), y = to_tune())) - expect_equal(setindex(tuneps$deps, NULL), data.table(id = "x", on = "y", cond = list(CondEqual$new(0)))) + expect_equal(setindex(tuneps$deps, NULL), data.table(id = "x", on = "y", cond = list(CondEqual(0)))) tuneps = pars$search_space(list(x = to_tune(), y = to_tune(ps(y1 = p_int(0, 1), y2 = p_int(0, 1, depends = x == 1), .extra_trafo = function(x, param_set) list(min(x$y1, x$y2, na.rm = TRUE)), .allow_dangling_dependencies = TRUE)))) # mixing dependencies from inside and across to_tune. I am the only person in this building capable of coding this. - expect_equal(setindex(tuneps$deps, NULL), data.table(id = c("y2", "y1", "y2"), on = c("x", "x", "x"), cond = list(CondEqual$new(1)))) + expect_equal(setindex(tuneps$deps, NULL), data.table(id = c("y2", "y1", "y2"), on = c("x", "x", "x"), cond = list(CondEqual(1)))) expect_error(pars$search_space(list(x = to_tune(), y = to_tune(ps(y1 = p_int(0, 1), y2 = p_int(0, 1, depends = z == 1), .extra_trafo = function(x, param_set) list(min(x$y1, x$y2, na.rm = TRUE)), .allow_dangling_dependencies = TRUE)))), @@ -261,11 +260,11 @@ test_that("Dependencies work", { # dependency after subsetting factorials works, even if the dependency now # contains infeasible values - largeps = ParamSet$new(list( + largeps = ParamSet_legacy$new(list( ParamFct$new("x", c("a", "b", "c")), ParamLgl$new("y") )) - largeps$add_dep("y", "x", CondAnyOf$new(c("a", "b"))) + largeps$add_dep("y", "x", CondAnyOf(c("a", "b"))) res = largeps$search_space(list(x = to_tune(c("a", "b")), y = to_tune())) expect_equal(res$deps$cond[[1]]$rhs, c("a", "b")) @@ -280,12 +279,10 @@ test_that("Dependencies work", { test_that("ParamSetCollection works", { - ps1 = ParamSet$new(list(ParamInt$new("x"), ParamInt$new("y"))) - ps2 = ParamSet$new(list(ParamInt$new("a"))) - - ps1$set_id = "prefix" + ps1 = ParamSet_legacy$new(list(ParamInt$new("x"), ParamInt$new("y"))) + ps2 = ParamSet_legacy$new(list(ParamInt$new("a"))) - psc = ParamSetCollection$new(list(ps1, ps2)) + psc = ParamSetCollection$new(list(prefix = ps1, ps2)) ps1$values$x = to_tune(0, 10) ps1$values$y = to_tune(ps(y1 = p_int(0, 1), y2 = p_int(0, 1), .extra_trafo = function(x, param_set) list(y = x$y1 * x$y2))) @@ -310,7 +307,7 @@ test_that("ParamSetCollection works", { }) test_that("ParamSet$get_values() works", { - pars = ParamSet$new(list( + pars = ParamSet_legacy$new(list( ParamInt$new("x", lower = 0, upper = 10), ParamDbl$new("y", lower = 0, upper = 10), ParamDbl$new("z", lower = 0, upper = 10) @@ -324,7 +321,7 @@ test_that("ParamSet$get_values() works", { expect_named(pars$get_values(type = "without_token"), c("y", "z")) expect_named(pars$get_values(type = "only_token"), "x") - pars = ParamSet$new(list( + pars = ParamSet_legacy$new(list( ParamInt$new("x", lower = 0, upper = 10), ParamDbl$new("y", lower = 0, upper = 10), ParamDbl$new("z", lower = 0, upper = 10) @@ -339,25 +336,25 @@ test_that("ParamSet$get_values() works", { test_that("partial bounds in tunetoken", { - pars = ParamSet$new(list( + pars = ParamSet_legacy$new(list( ParamInt$new("x", lower = 0, upper = 10), ParamDbl$new("y", lower = 0), ParamDbl$new("z", upper = 10) )) - expect_equal(pars$search_space(list(x = to_tune()))$params[[1]], ParamInt$new("x", lower = 0, upper = 10)) + expect_equal_ps(pars$search_space(list(x = to_tune())), ParamInt$new("x", lower = 0, upper = 10)) - expect_equal(pars$search_space(list(x = to_tune(lower = 1)))$params[[1]], ParamInt$new("x", lower = 1, upper = 10)) - expect_equal(pars$search_space(list(x = to_tune(upper = 1)))$params[[1]], ParamInt$new("x", lower = 0, upper = 1)) - expect_equal(pars$search_space(list(x = to_tune(lower = 1, upper = 2)))$params[[1]], ParamInt$new("x", lower = 1, upper = 2)) + expect_equal_ps(pars$search_space(list(x = to_tune(lower = 1))), ParamInt$new("x", lower = 1, upper = 10)) + expect_equal_ps(pars$search_space(list(x = to_tune(upper = 1))), ParamInt$new("x", lower = 0, upper = 1)) + expect_equal_ps(pars$search_space(list(x = to_tune(lower = 1, upper = 2))), ParamInt$new("x", lower = 1, upper = 2)) expect_error(pars$search_space(list(y = to_tune(lower = 1))), "y range must be bounded, but is \\[1, Inf\\]") - expect_equal(pars$search_space(list(y = to_tune(upper = 1)))$params[[1]], ParamDbl$new("y", lower = 0, upper = 1)) - expect_equal(pars$search_space(list(y = to_tune(lower = 1, upper = 2)))$params[[1]], ParamDbl$new("y", lower = 1, upper = 2)) + expect_equal_ps(pars$search_space(list(y = to_tune(upper = 1))), ParamDbl$new("y", lower = 0, upper = 1)) + expect_equal_ps(pars$search_space(list(y = to_tune(lower = 1, upper = 2))), ParamDbl$new("y", lower = 1, upper = 2)) expect_error(pars$search_space(list(z = to_tune(upper = 1))), "z range must be bounded, but is \\[-Inf, 1\\]") - expect_equal(pars$search_space(list(z = to_tune(lower = 1)))$params[[1]], ParamDbl$new("z", lower = 1, upper = 10)) - expect_equal(pars$search_space(list(z = to_tune(lower = 1, upper = 2)))$params[[1]], ParamDbl$new("z", lower = 1, upper = 2)) + expect_equal_ps(pars$search_space(list(z = to_tune(lower = 1))), ParamDbl$new("z", lower = 1, upper = 10)) + expect_equal_ps(pars$search_space(list(z = to_tune(lower = 1, upper = 2))), ParamDbl$new("z", lower = 1, upper = 2)) expect_output(print(to_tune()), "entire parameter range") expect_output(print(to_tune(lower = 1)), "range \\[1, \\.\\.\\.]") @@ -373,20 +370,15 @@ test_that("partial bounds in tunetoken", { test_that("logscale in tunetoken", { - pars = ParamSet$new(list( + pars = ParamSet_legacy$new(list( ParamInt$new("x", lower = 0, upper = 10), ParamDbl$new("y", lower = 0) )) - p1 = pars$search_space(list(x = to_tune(logscale = TRUE)))$params[[1]] - p2 = ParamDbl$new("x", lower = log(.5), upper = log(11)) - expect_equal(p1$lower, p2$lower) - expect_equal(p1$upper, p2$upper) - - p1 = pars$search_space(list(y = to_tune(lower = 1, upper = 10, logscale = TRUE)))$params[[1]] - p2 = ParamDbl$new("y", lower = log(1), upper = log(10)) - expect_equal(p1$lower, p2$lower) - expect_equal(p1$upper, p2$upper) + expect_equal(reset_indices(pars$search_space(list(x = to_tune(logscale = TRUE))))$.__enclos_env__$private$.params[, cargo := list(list(NULL))], + reset_indices(ParamDbl$new("x", lower = log(.5), upper = log(11)))$.__enclos_env__$private$.params) + expect_equal(reset_indices(pars$search_space(list(y = to_tune(lower = 1, upper = 10, logscale = TRUE))))$.__enclos_env__$private$.params[, cargo := list(list(NULL))], + reset_indices(ParamDbl$new("y", lower = log(1), upper = log(10)))$.__enclos_env__$private$.params) expect_error(pars$search_space(list(y = to_tune(upper = 10, logscale = TRUE))), "When logscale is TRUE then lower bound must be strictly greater than 0") diff --git a/tests/testthat/test_trafo.R b/tests/testthat/test_trafo.R index b9154600..febd6a4d 100644 --- a/tests/testthat/test_trafo.R +++ b/tests/testthat/test_trafo.R @@ -1,14 +1,14 @@ context("trafo") test_that("trafo", { - ps = ParamSet$new(list( + ps = ParamSet_legacy$new(list( ParamDbl$new("x", lower = -3, upper = 3), ParamDbl$new("w1", lower = 7, upper = 9), ParamDbl$new("w2", lower = 7, upper = 9), ParamFct$new("f", levels = c("a", "b")) )) expect_false(ps$has_trafo) - ps$trafo = function(x, param_set) { + ps$extra_trafo = function(x, param_set) { x$x = 2^x$x s = x$w1 + x$w2 x$w1 = x$w1 / s @@ -19,7 +19,7 @@ test_that("trafo", { expect_output(print(ps), "Trafo is set") d1 = generate_design_grid(ps, resolution = 4) dd1 = d1$data - d2 = ps$trafo(dd1) + d2 = map_dtr(seq_len(nrow(dd1)), function(i) ps$trafo(as.list(dd1[i]))) expect_numeric(d2$x, lower = 0) expect_numeric(d2$w1, lower = 0, upper = 1) expect_numeric(d2$w2, lower = 0, upper = 1) diff --git a/vignettes/indepth.Rmd b/vignettes/indepth.Rmd index 9b1d6a16..8b05185a 100644 --- a/vignettes/indepth.Rmd +++ b/vignettes/indepth.Rmd @@ -7,14 +7,8 @@ vignette: > %\VignetteEncoding{UTF-8} --- - - -**Note:** Many of the concepts explained here, are also covered in the [mlr3book](https://github.com/mlr-org/mlr3book/). - ## Parameters (using paradox) - - The `paradox` package offers a language for the description of *parameter spaces*, as well as tools for useful operations on these parameter spaces. A parameter space is often useful when describing: @@ -28,152 +22,141 @@ The tools provided by `paradox` therefore relate to: * **Parameter sampling**: Generating parameter values that lie in the parameter space for systematic exploration of program behavior depending on these parameters `paradox` is, by nature, an auxiliary package that derives its usefulness from other packages that make use of it. -It is heavily utilized in other [mlr-org](https://github.com/mlr-org) packages such as `mlr3`, `mlr3pipelines`, and `mlr3tuning`. +It is heavily utilized in other [mlr-org](https://github.com/mlr-org) packages such as `mlr3`, `mlr3pipelines`, `mlr3tuning` and `miesmuschel`. ### Reference Based Objects -`paradox` is the spiritual successor to the `ParamHelpers` package and was written from scratch using the `R6` class system. -The most important consequence of this is that all objects created in `paradox` are "reference-based", unlike most other objects in R. -When a change is made to a `ParamSet` object, for example by adding a parameter using the `$add()` function, all variables that point to this `ParamSet` will contain the changed object. -To create an independent copy of a `ParamSet`, the `$clone()` method needs to be used: +`paradox` is the spiritual successor to the `ParamHelpers` package and was written from scratch. +The most important consequence of this is that some objects created in `paradox` are "reference-based", unlike most other objects in R. +When a change is made to a `ParamSet` object, for example by changing the `$values` field, all variables that point to this `ParamSet` will contain the changed object. +To create an independent copy of a `ParamSet`, the `$clone(deep = TRUE)` method needs to be used: ```{r} library("paradox") -ps = ParamSet$new() -ps2 = ps -ps3 = ps$clone(deep = TRUE) -print(ps) # the same for ps2 and ps3 +ps1 = ps(a = p_int(init = 1)) +ps2 = ps1 +ps3 = ps1$clone(deep = TRUE) +print(ps1) # the same for ps2 and ps3 ``` ```{r} -ps$add(ParamLgl$new("a")) +ps1$values$a = 2 ``` ```{r} -print(ps) # ps was changed -print(ps2) # contains the same reference as ps -print(ps3) # is a "clone" of the old (empty) ps +print(ps1) # ps1 value of 'a' was changed +print(ps2) # contains the same reference as ps1, so also changed +print(ps3) # is a "clone" of the old ps1 with 'a' == 1 ``` ### Defining a Parameter Space -#### Single Parameters +#### `Domain` Representing Single Parameters -The basic building block for describing parameter spaces is the **`Param`** class. -It represents a single parameter, which usually can take a single atomic value. +Parameter spaces are made up of individual parameters, which usually can take a single atomic value. Consider, for example, trying to configure the `rpart` package's `rpart.control` object. -It has various components (`minsplit`, `cp`, ...) that all take a single value, and that would all be represented by a different instance of a `Param` object. +It has various components (`minsplit`, `cp`, ...) that all take a single value. -The `Param` class has various subclasses that represent different value types: +These components are represented by `Domain` objects, which are constructed by calls of the form `p_xxx()`: -* `ParamInt`: Integer numbers -* `ParamDbl`: Real numbers -* `ParamFct`: String values from a set of possible values, similar to R `factor`s -* `ParamLgl`: Truth values (`TRUE` / `FALSE`), as `logical`s in R -* `ParamUty`: Parameter that can take any value +* `p_int()` for integer numbers +* `p_dbl()` for real numbers +* `p_fct()` for categorical values, similar to R `factor`s +* `p_lgl()` for truth values (`TRUE` / `FALSE`), as `logical`s in R +* `p_uty()` for parameters that can take any value -A particular instance of a parameter is created by calling the attached `$new()` function: +A `ParamSet` that represent a given set of parameters is created by calling `ps()` with named arguments that are `Domain` objects. +While `Domain` themselves are R objects that can in principle be handled and manipulated, they should not be changed after construction. ```{r} library("paradox") -parA = ParamLgl$new(id = "A") -parB = ParamInt$new(id = "B", lower = 0, upper = 10, tags = c("tag1", "tag2")) -parC = ParamDbl$new(id = "C", lower = 0, upper = 4, special_vals = list(NULL)) -parD = ParamFct$new(id = "D", levels = c("x", "y", "z"), default = "y") -parE = ParamUty$new(id = "E", custom_check = function(x) checkmate::checkFunction(x)) +param_set = ps( + parA = p_lgl(init = FALSE), + parB = p_int(lower = 0, upper = 10, tags = c("tag1", "tag2")), + parC = p_dbl(lower = 0, upper = 4, special_vals = list(NULL)), + parD = p_fct(levels = c("x", "y", "z"), default = "y"), + parE = p_uty(custom_check = function(x) checkmate::checkFunction(x)) +) +param_set ``` -Every parameter must have: +Every parameter can have: -* **id** - A name for the parameter within the parameter set -* **default** - A default value +* **default** - A default value, indicating the behaviour of something if the specific value is not given. +* **init** - An initial value, which is set in `$values` when the `ParamSet` is created. + Note that this is not the same as `default`: `default` is used when a parameter is not present in `$values`, while `init` is the value that is set upon creation. * **special_vals** - A list of values that are accepted even if they do not conform to the type * **tags** - Tags that can be used to organize parameters +* **trafo** - A transformation function that is applied to the parameter value after it has been sampled. + It is for example used through the `Design$transpose()` function after a `Design` was created by `generate_design_random()` or similar functions. -The numeric (`Int` and `Dbl`) parameters furthermore allow for specification of a **lower** and **upper** bound. -Meanwhile, the `Fct` parameter must be given a vector of **levels** that define the possible states its parameter can take. -The `Uty` parameter can also have a **`custom_check`** function that must return `TRUE` when a value is acceptable and may return a `character(1)` error description otherwise. +The numeric (`p_int()` and `p_dbl()`) parameters furthermore allow for specification of a **lower** and **upper** bound. +Meanwhile, the `p_fct()` parameter must be given a vector of **levels** that define the possible states its parameter can take. +The `p_uty` parameter can also have a **`custom_check`** function that must return `TRUE` when a value is acceptable and may return a `character(1)` error description otherwise. The example above defines `parE` as a parameter that only accepts functions. -All values which are given to the constructor are then accessible from the object for inspection using `$`. -Although all these values can be changed for a parameter after construction, this can be a bad idea and should be avoided when possible. +All values which are given to the constructor are then accessible from the `ParamSet` for inspection using `$`. +The `ParamSet` should be considered immutable, except for some fields such as `$values`, `$deps`, `$tags`. +Bounds and levels should not be changed after construction. +Instead, a new `ParamSet` should be constructed. -Instead, a new parameter should be constructed. Besides the possible values that can be given to a constructor, there are also the `$class`, `$nlevels`, `$is_bounded`, `$has_default`, `$storage_type`, `$is_number` and `$is_categ` slots that give information about a parameter. A list of all slots can be found in `?Param`. ```{r} -parB$lower -parA$levels -parE$class +param_set$lower +param_set$parD$levels +param_set$class ``` -It is also possible to get all information of a `Param` as `data.table` by calling `as.data.table()`. +It is also possible to get all information of a `ParamSet` as `data.table` by calling `as.data.table()`. ```{r} -as.data.table(parA) +as.data.table(param_set) ``` ##### Type / Range Checking -A `Param` object offers the possibility to check whether a value satisfies its condition, i.e. is of the right type, and also falls within the range of allowed values, using the `$test()`, `$check()`, and `$assert()` functions. +The `ParamSet` object offers the possibility to check whether a value satisfies its condition, i.e. is of the right type, and also falls within the range of allowed values, using the `$test()`, `$check()`, and `$assert()` functions. +Their argument must be a named list with values that are checked against the respective parameters, and it is possible to check only a subset of parameters. `test()` should be used within conditional checks and returns `TRUE` or `FALSE`, while `check()` returns an error description when a value does not conform to the parameter (and thus plays well with the `"checkmate::assert()"` function). `assert()` will throw an error whenever a value does not fit. ```{r} -parA$test(FALSE) -parA$test("FALSE") -parA$check("FALSE") +param_set$test(list(parA = FALSE, parB = 0)) +param_set$test(list(parA = "FALSE")) +param_set$check(list(parA = "FALSE")) ``` -Instead of testing single parameters, it is often more convenient to check a whole set of parameters using a `ParamSet`. - #### Parameter Sets -The ordered collection of parameters is handled in a `ParamSet`^[Although the name is suggestive of a "Set"-valued `Param`, this is unrelated to the other objects that follow the `ParamXxx` naming scheme.]. -It is initialized using the `$new()` function and optionally takes a list of `Param`s as argument. -Parameters can also be added to the constructed `ParamSet` using the `$add()` function. -It is even possible to add whole `ParamSet`s to other `ParamSet`s. - -```{r} -ps = ParamSet$new(list(parA, parB)) -ps$add(parC) -ps$add(ParamSet$new(list(parD, parE))) -print(ps) -``` +The ordered collection of parameters is handled in a `ParamSet`. +It is typically created by calling `ps()`, but can also be initialized using the `ParamSet$new()` function. +The main difference is that `ps()` takes named arguments, whereas `ParamSet$new()` takes a named list. +The latter makes it easier to construct a `ParamSet` programmatically, but is slightly more verbose. -The individual parameters can be accessed through the `$params` slot. -It is also possible to get information about all parameters in a vectorized fashion using mostly the same slots as for individual `Param`s (i.e. `$class`, `$levels` etc.), see `?ParamSet` for details. - -It is possible to reduce `ParamSet`s using the **`$subset`** method. -Be aware that it modifies a ParamSet in-place, so a "clone" must be created first if the original `ParamSet` should not be modified. +`ParamSet`s can be combined using `c()` or `ps_union` (the latter of which takes a list), and they have a `$subset()` method that allows for subsetting. +All of these functions return a new, cloned `ParamSet` object, and do not modify the original `ParamSet`. ```{r} -psSmall = ps$clone() -psSmall$subset(c("A", "B", "C")) -print(psSmall) +ps1 = ParamSet$new(list(x = p_int(), y = p_dbl())) +ps2 = ParamSet$new(list(z = p_fct(levels = c("a", "b", "c")))) +ps_all = c(ps1, ps2) +print(ps_all) +ps_all$subset(c("x", "z")) ``` -Just as for `Param`s, and much more useful, it is possible to get the `ParamSet` as a `data.table` using `as.data.table()`. +`ParamSet`s of each individual parameters can be accessed through the `$subspaces()` function. + +It is possible to get the `ParamSet` as a `data.table` using `as.data.table()`. This makes it easy to subset parameters on certain conditions and aggregate information about them, using the variety of methods provided by `data.table`. ```{r} -as.data.table(ps) +as.data.table(ps_all) ``` -##### Type / Range Checking - -Similar to individual `Param`s, the `ParamSet` provides `$test()`, `$check()` and `$assert()` functions that allow for type and range checking of parameters. -Their argument must be a named list with values that are checked against the respective parameters. -It is possible to check only a subset of parameters. - -```{r} -ps$check(list(A = TRUE, B = 0, E = identity)) -ps$check(list(A = 1)) -ps$check(list(Z = 1)) -``` ##### Values in a `ParamSet` @@ -183,15 +166,15 @@ The `$values` slot contains a named list that is always checked against paramete When trying to set parameter values, e.g. for `mlr3` `Learner`s, it is the `$values` slot of its `$param_set` that needs to be used. ```{r} -ps$values = list(A = TRUE, B = 0) -ps$values$B = 1 -print(ps$values) +ps1$values = list(x = 1, y = 1.5) +ps1$values$y = 2.5 +print(ps1$values) ``` The parameter constraints are automatically checked: ```{r, error = TRUE} -ps$values$B = 100 +ps1$values$x = 1.5 ``` ##### Dependencies @@ -202,29 +185,37 @@ The second parameter would be said to *depend* on the first parameter having the A dependency can be added using the `$add_dep` method, which takes both the ids of the "depender" and "dependee" parameters as well as a `Condition` object. The `Condition` object represents the check to be performed on the "dependee". -Currently it can be created using `CondEqual$new()` and `CondAnyOf$new()`. +Currently it can be created using `CondEqual()` and `CondAnyOf()`. Multiple dependencies can be added, and parameters that depend on others can again be depended on, as long as no cyclic dependencies are introduced. The consequence of dependencies are twofold: -For one, the `$check()`, `$test()` and `$assert()` tests will not accept the presence of a parameter if its dependency is not met. +For one, the `$check()`, `$test()` and `$assert()` tests will not accept the presence of a parameter if its dependency is not met, when the `check_strict` argument is given as `TRUE`. Furthermore, when sampling or creating grid designs from a `ParamSet`, the dependencies will be respected. +The easiest way to set dependencies is to give the `depends` argument to the `Domain` constructor. + The following example makes parameter `D` depend on parameter `A` being `FALSE`, and parameter `B` depend on parameter `D` being one of `"x"` or `"y"`. This introduces an implicit dependency of `B` on `A` being `FALSE` as well, because `D` does not take any value if `A` is `TRUE`. ```{r} -ps$add_dep("D", "A", CondEqual$new(FALSE)) -ps$add_dep("B", "D", CondAnyOf$new(c("x", "y"))) +p = ps( + A = p_lgl(init = FALSE), + B = p_int(lower = 0, upper = 10, depends = D %in% c("x", "y")), + C = p_dbl(lower = 0, upper = 4), + D = p_fct(levels = c("x", "y", "z"), depends = A == FALSE) +) ``` +Note that the `depends` argument is limited to operators `==` and `%in%`, so `D = p_fct(..., depends = !A)` would not work. + ```{r} -ps$check(list(A = FALSE, D = "x", B = 1)) # OK: all dependencies met -ps$check(list(A = FALSE, D = "z", B = 1)) # B's dependency is not met -ps$check(list(A = FALSE, B = 1)) # B's dependency is not met -ps$check(list(A = FALSE, D = "z")) # OK: B is absent -ps$check(list(A = TRUE)) # OK: neither B nor D present -ps$check(list(A = TRUE, D = "x", B = 1)) # D's dependency is not met -ps$check(list(A = TRUE, B = 1)) # B's dependency is not met +p$check(list(A = FALSE, D = "x", B = 1), check_strict = TRUE) # OK: all dependencies met +p$check(list(A = FALSE, D = "z", B = 1), check_strict = TRUE) # B's dependency is not met +p$check(list(A = FALSE, B = 1), check_strict = TRUE) # B's dependency is not met +p$check(list(A = FALSE, D = "z"), check_strict = TRUE) # OK: B is absent +p$check(list(A = TRUE), check_strict = TRUE) # OK: neither B nor D present +p$check(list(A = TRUE, D = "x", B = 1), check_strict = TRUE) # D's dependency is not met +p$check(list(A = TRUE, B = 1), check_strict = TRUE) # B's dependency is not met ``` Internally, the dependencies are represented as a `data.table`, which can be accessed listed in the **`$deps`** slot. @@ -233,33 +224,31 @@ There are no sanity checks done when the `$deps` slot is changed this way. Therefore it is advised to be cautious. ```{r} -ps$deps +p$deps ``` #### Vector Parameters Unlike in the old `ParamHelpers` package, there are no more vectorial parameters in `paradox`. -Instead, it is now possible to create multiple copies of a single parameter using the `$rep` function. +Instead, it is now possible to create multiple copies of a single parameter using the `ps_replicate` function. This creates a `ParamSet` consisting of multiple copies of the parameter, which can then (optionally) be added to another `ParamSet`. ```{r} -ps2d = ParamDbl$new("x", lower = 0, upper = 1)$rep(2) +ps2d = ps_replicate(ps(x = p_dbl(lower = 0, upper = 1)), 2) print(ps2d) ``` -```{r} -ps$add(ps2d) -print(ps) -``` - It is also possible to use a `ParamUty` to accept vectorial parameters, which also works for parameters of variable length. A `ParamSet` containing a `ParamUty` can be used for parameter checking, but not for sampling. -To sample values for a method that needs a vectorial parameter, it is advised to use a parameter transformation function that creates a vector from atomic values. +To sample values for a method that needs a vectorial parameter, it is advised to use an `$extra_trafo` transformation function that creates a vector from atomic values. -Assembling a vector from repeated parameters is aided by the parameter's `$tags`: Parameters that were generated by the `$rep()` command automatically get tagged as belonging to a group of repeated parameters. +Assembling a vector from repeated parameters is aided by the parameter's `$tags`: Parameters that were generated by the `pr_replicate()` command can be tagged as belonging to a group of repeated parameters. ```{r} -ps$tags +ps2d = ps_replicate(ps(x = p_dbl(0, 1), y = p_int(0, 10)), 2, tag_params = TRUE) +ps2d$values = list(rep1.x = 0.2, rep2.x = 0.4, rep1.y = 3, rep2.y = 4) +ps2d$tags +ps2d$get_values(tags = "param_x") ``` ### Parameter Sampling @@ -269,7 +258,7 @@ It is often useful to have a list of possible parameter values that can be syste In the latter case, it is possible to influence the sampling distribution in more or less fine detail. A point to always keep in mind while sampling is that only numerical and factorial parameters that are bounded can be sampled from, i.e. not `ParamUty`. -Furthermore, for most samplers `ParamInt` and `ParamDbl` must have finite lower and upper bounds. +Furthermore, for most samplers `p_int()` and `p_dbl()` must have finite lower and upper bounds. #### Parameter Designs @@ -282,12 +271,13 @@ The `generate_design_grid()` function is used to create grid designs that contai The resolution can be given for all numeric parameters, or for specific named parameters through the `param_resolutions` parameter. ```{r} -design = generate_design_grid(psSmall, 2) +ps_small = ps(A = p_dbl(0, 1), B = p_dbl(0, 1)) +design = generate_design_grid(ps_small, 2) print(design) ``` ```{r} -generate_design_grid(psSmall, param_resolutions = c(B = 1, C = 2)) +generate_design_grid(ps_small, param_resolutions = c(A = 3, B = 2)) ``` #### Random Sampling @@ -296,10 +286,12 @@ generate_design_grid(psSmall, param_resolutions = c(B = 1, C = 2)) The easiest way to get a uniformly random sample of parameters is `generate_design_random()`. It is also possible to create "[latin hypercube](https://en.wikipedia.org/wiki/Latin_hypercube_sampling)" sampled parameter values using `generate_design_lhs()`, which utilizes the `lhs` package. LHS-sampling creates low-discrepancy sampled values that cover the parameter space more evenly than purely random values. +`generate_design_sobol()` can be used to sample using the [Sobol sequence](https://en.wikipedia.org/wiki/Sobol_sequence). ```{r} -pvrand = generate_design_random(ps2d, 500) -pvlhs = generate_design_lhs(ps2d, 500) +pvrand = generate_design_random(ps_small, 500) +pvlhs = generate_design_lhs(ps_small, 500) +pvsobol = generate_design_sobol(ps_small, 500) ``` ```{r, echo = FALSE, out.width="45%", fig.show = "hold", fig.width = 4, fig.height = 4} @@ -307,6 +299,7 @@ pvlhs = generate_design_lhs(ps2d, 500) par(mar=c(4, 4, 2, 1)) plot(pvrand$data, main = "'random' design", xlim = c(0, 1), ylim=c(0, 1)) plot(pvlhs$data, main = "'lhs' design", xlim = c(0, 1), ylim=c(0, 1)) +plot(pvsobol$data, main = "'sobol' design", xlim = c(0, 1), ylim=c(0, 1)) ``` #### Generalized Sampling: The `Sampler` Class @@ -321,10 +314,10 @@ Every `Sampler` object has a `sample()` function, which takes one argument, the There is a variety of samplers that sample values for a single parameter. These are `Sampler1DUnif` (uniform sampling), `Sampler1DCateg` (sampling for categorical parameters), `Sampler1DNormal` (normally distributed sampling, truncated at parameter bounds), and `Sampler1DRfun` (arbitrary 1D sampling, given a random-function). -These are initialized with a single `Param`, and can then be used to sample values. +These are initialized with a one-dimensional `ParamSet`, and can then be used to sample values. ```{r} -sampA = Sampler1DCateg$new(parA) +sampA = Sampler1DCateg$new(ps(x = p_fct(letters))) sampA$sample(5) ``` @@ -339,13 +332,19 @@ The following example shows how this works: The `Int` parameter `B` depends on t In the cases where `A` is `FALSE`, `B` is set to `NA`. ```{r} -psSmall$add_dep("B", "A", CondEqual$new(TRUE)) -sampH = SamplerHierarchical$new(psSmall, - list(Sampler1DCateg$new(parA), - Sampler1DUnif$new(parB), - Sampler1DUnif$new(parC)) +p = ps( + A = p_lgl(), + B = p_int(0, 10, depends = A == TRUE) +) + +p_subspaces = p$subspaces() + +sampH = SamplerHierarchical$new(p, + list(Sampler1DCateg$new(p_subspaces$A), + Sampler1DUnif$new(p_subspaces$B)) ) sampled = sampH$sample(1000) +head(sampled$data) table(sampled$data[, c("A", "B")], useNA = "ifany") ``` @@ -357,8 +356,8 @@ However, `SamplerJointIndep` currently can not handle `ParamSet`s with dependenc ```{r} sampJ = SamplerJointIndep$new( - list(Sampler1DUnif$new(ParamDbl$new("x", 0, 1)), - Sampler1DUnif$new(ParamDbl$new("y", 0, 1))) + list(Sampler1DUnif$new(ps(x = p_dbl(0, 1))), + Sampler1DUnif$new(ps(y = p_dbl(0, 1)))) ) sampJ$sample(5) ``` @@ -370,25 +369,28 @@ The `Sampler` used in `generate_design_random()` is the `SamplerUnif` sampler, w ### Parameter Transformation While the different `Sampler`s allow for a wide specification of parameter distributions, there are cases where the simplest way of getting a desired distribution is to sample parameters from a simple distribution (such as the uniform distribution) and then transform them. -This can be done by assigning a function to the `$trafo` slot of a `ParamSet`. -The `$trafo` function is called with two parameters: +This can be done by constructing a `Domain` with a `trafo` argument, or assigning a function to the `$extra_trafo` field of a `ParamSet`. +The latter can also be done by passing an `.extra_trafo` argument to the `ps()` shorthand constructor. + +A `trafo` function in a `Domain` is called with a single parameter, the value to be transformed. +It can only operate on the dimension of a single parameter. + +The `$extra_trafo` function is called with two parameters: -* The list of parameter values to be transformed as `x` +* The list of parameter values to be transformed as `x`. + Unlike the `Domain`'s `trafo`, the `$extra_trafo` handles the whole parameter set and can even model "interactions" between parameters. * The `ParamSet` itself as `param_set` -The `$trafo` function must return a list of transformed parameter values. +The `$extra_trafo` function must return a list of transformed parameter values. The transformation is performed when calling the `$transpose` function of the `Design` object returned by a `Sampler` with the `trafo` ParamSet to `TRUE` (the default). The following, for example, creates a parameter that is exponentially distributed: ```{r} -psexp = ParamSet$new(list(ParamDbl$new("par", 0, 1))) -psexp$trafo = function(x, param_set) { - x$par = -log(x$par) - x -} -design = generate_design_random(psexp, 2) -print(design) +psexp = ps(par = p_dbl(0, 1, trafo = function(x) -log(x))) + +design = generate_design_random(psexp, 3) +print(design) # not transformed: between 0 and 1 design$transpose() # trafo is TRUE ``` @@ -398,6 +400,18 @@ Compare this to `$transpose()` without transformation: design$transpose(trafo = FALSE) ``` +Another way to get tihs effect, using `$extra_trafo`, would be: +```{r} +psexp = ps(par = p_dbl(0, 1)) +psexp$extra_trafo = function(x, param_set) { + x$par = -log(x$par) + x +} +``` +However, the `trafo` way is more recommended when transforming parameters independently. +`$extra_trafo` is more useful when transforming parameters that interact in some way, or when new parameters should be generated. + + #### Transformation between Types Usually the design created with one `ParamSet` is then used to configure other objects that themselves have a `ParamSet` which defines the values they take. @@ -413,31 +427,18 @@ The user can pass functions like `median()` or `mean()`, but could also pass qua This method would probably use the following `ParamSet`: ```{r} -methodPS = ParamSet$new( - list( - ParamUty$new("fun", - custom_check = function(x) checkmate::checkFunction(x, nargs = 1)) - ) -) +methodPS = ps(fun = p_uty(custom_check = function(x) checkmate::checkFunction(x, nargs = 1))) + print(methodPS) ``` If one wanted to sample this method, using one of four functions, a way to do this would be: ```{r} -samplingPS = ParamSet$new( - list( - ParamFct$new("fun", c("mean", "median", "min", "max")) - ) +samplingPS = ps( + fun = p_fct(c("mean", "median", "min", "max"), + trafo = function(x) get(x, mode = "function")) ) - -samplingPS$trafo = function(x, param_set) { - # x$fun is a `character(1)`, - # in particular one of 'mean', 'median', 'min', 'max'. - # We want to turn it into a function! - x$fun = get(x$fun, mode = "function") - x -} ``` ```{r} @@ -460,23 +461,32 @@ methodPS$check(xvals[[1]]) xvals[[1]]$fun(1:10) ``` +`p_fct()` has a shortcut for this kind of transformation, where a `character` is transformed into a specific set of (typically non-scalar) values. +When its `levels` argument is given as a named `list` (or named non-`character` vector), it constructs a `Domain` that does the trafo automatically. +A way to perform the above would therefore be: +```{r} +samplingPS = ps( + fun = p_fct(list("mean" = mean, "median" = median, "min" = min, "max" = max)) +) + +generate_design_random(samplingPS, 1)$transpose() +``` + Imagine now that a different kind of parametrization of the function is desired: The user wants to give a function that selects a certain quantile, where the quantile is set by a parameter. In that case the `$transpose` function could generate a function in a different way. -For interpretability, the parameter is called "`quantile`" before transformation, and the "`fun`" parameter is generated on the fly. + +For interpretability, the parameter should be called "`quantile`" before transformation, and the "`fun`" parameter is generated on the fly. +We therefore use an `extra_trafo` here, given as a function to the `ps()` call. ```{r} -samplingPS2 = ParamSet$new( - list( - ParamDbl$new("quantile", 0, 1) - ) +samplingPS2 = ps(quantile = p_dbl(0, 1), + .extra_trafo = function(x, param_set) { + # x$quantile is a `numeric(1)` between 0 and 1. + # We want to turn it into a function! + list(fun = function(input) quantile(input, x$quantile)) + } ) - -samplingPS2$trafo = function(x, param_set) { - # x$quantile is a `numeric(1)` between 0 and 1. - # We want to turn it into a function! - list(fun = function(input) quantile(input, x$quantile)) -} ``` ```{r} @@ -499,7 +509,6 @@ xvals[[1]]$fun(1:10) When running an optimization, it is important to inform the tuning algorithm about what hyperparameters are valid. Here the names, types, and valid ranges of each hyperparameter are important. All this information is communicated with objects of the class `ParamSet`, which is defined in `paradox`. -While it is possible to create `ParamSet`-objects using its `$new`-constructor, it is much shorter and readable to use the `ps`-shortcut, which will be presented here. Note, that `ParamSet` objects exist in two contexts. First, `ParamSet`-objects are used to define the space of valid parameter settings for a learner (and other objects). @@ -533,13 +542,13 @@ print(search_space) There are five domain constructors that produce a parameters when given to `ps`: -| Constructor | Description | Is bounded? | Underlying Class | -| :-----------------------: | :----------------------------------: | :--------------------------------: | :-----------------: | -| `p_dbl` | Real valued parameter ("double") | When `upper` and `lower` are given | `ParamDbl` | -| `p_int` | Integer parameter | When `upper` and `lower` are given | `ParamInt` | -| `p_fct` | Discrete valued parameter ("factor") | Always | `ParamFct` | -| `p_lgl` | Logical / Boolean parameter | Always | `ParamLgl` | -| `p_uty` | Untyped parameter | Never | `ParamUty` | +| Constructor | Description | Is bounded? | +| :-----------------------: | :----------------------------------: | :--------------------------------: | +| `p_dbl` | Real valued parameter ("double") | When `upper` and `lower` are given | +| `p_int` | Integer parameter | When `upper` and `lower` are given | +| `p_fct` | Discrete valued parameter ("factor") | Always | +| `p_lgl` | Logical / Boolean parameter | Always | +| `p_uty` | Untyped parameter | Never | These domain constructors each take some of the following arguments: @@ -550,6 +559,8 @@ These domain constructors each take some of the following arguments: * **`trafo`**: transformation function, see below. * **`depends`**: dependencies, see below. * **`tags`**: Further information about a parameter, used for example by the `hyperband` tuner. +* **`init`**: . + Not used for tuning search spaces. * **`default`**: Value corresponding to default behavior when the parameter is not given. Not used for tuning search spaces. * **`special_vals`**: Valid values besides the normally accepted values for a parameter. @@ -558,7 +569,7 @@ These domain constructors each take some of the following arguments: Not used for tuning search spaces. The `lower` and `upper` parameters are always in the first and second position respectively, except for `p_fct` where `levels` is in the first position. -It is preferred to omit the labels (ex: upper = 0.1 becomes just 0.1). This way of defining a `ParamSet` is more concise than the equivalent definition above. +It is preferred to omit the labels (ex: `upper = 0.1` becomes just `0.1`). This way of defining a `ParamSet` is more concise than the equivalent definition above. Preferred: ```{r} @@ -614,7 +625,7 @@ rbindlist(generate_design_grid(search_space, 3)$transpose()) The available types of search space parameters are limited: continuous, integer, discrete, and logical scalars. There are many machine learning algorithms, however, that take parameters of other types, for example vectors or functions. -These can not be defined in a search space `ParamSet`, and they are often given as `ParamUty` in the `Learner`'s `ParamSet`. +These can not be defined in a search space `ParamSet`, and they are often given as `p_uty()` in the `Learner`'s `ParamSet`. When trying to tune over these hyperparameters, it is necessary to perform a Transformation that changes the type of a parameter. An example is the `class.weights` parameter of the [Support Vector Machine](https://machinelearningmastery.com/cost-sensitive-svm-for-imbalanced-classification/) (SVM), which takes a named vector of class weights with one entry for each target class. @@ -712,7 +723,7 @@ This can be done in the same way that other hyperparameters are set to specific It can be understood as the hyperparameters being tagged for later tuning. The resulting `ParamSet` used for tuning can be retrieved using the `$search_space()` method. -```{r} +```{r, eval = FALSE} library("mlr3learners") learner = lrn("classif.svm") learner$param_set$values$kernel = "polynomial" # for example @@ -728,7 +739,7 @@ rbindlist(generate_design_grid( It is possible to omit `lower` here, because it can be inferred from the lower bound of the `degree` parameter itself. For other parameters, that are already bounded, it is possible to not give any bounds at all, because their ranges are already bounded. An example is the logical `shrinking` hyperparameter: -```{r} +```{r, eval = FALSE} learner$param_set$values$shrinking = to_tune() print(learner$param_set$search_space()) @@ -744,7 +755,7 @@ One could, for example, tune the `cost` as above on three given special values, Notice that a short form for `to_tune()` is a short form of `to_tune(p_fct())`. When introducing the dependency, we need to use the `degree` value from *before* the implicit trafo, which is the name or `as.character()` of the respective value, here `"val2"`! -```{r} +```{r, eval = FALSE} learner$param_set$values$type = "C-classification" # needs to be set because of a bug in paradox learner$param_set$values$cost = to_tune(c(val1 = 0.3, val2 = 0.7)) learner$param_set$values$shrinking = to_tune(p_lgl(depends = cost == "val2")) @@ -758,7 +769,7 @@ The `search_space()` picks up dependencies from the underlying `ParamSet` automa So if the `kernel` is tuned, then `degree` automatically gets the dependency on it, without us having to specify that. (Here we reset `cost` and `shrinking` to `NULL` for the sake of clarity of the generated output.) -```{r} +```{r, eval = FALSE} learner$param_set$values$cost = NULL learner$param_set$values$shrinking = NULL learner$param_set$values$kernel = to_tune(c("polynomial", "radial")) @@ -773,7 +784,7 @@ This may be especially useful for vector hyperparameters that should be searched This `ParamSet` must, however, have an `.extra_trafo` that returns a list with a single element, because it corresponds to a single hyperparameter that is being tuned. Suppose the `class.weights` hyperparameter should be tuned along two dimensions: -```{r} +```{r, eval = FALSE} learner$param_set$values$class.weights = to_tune( ps(spam = p_dbl(0.1, 0.9), nonspam = p_dbl(0.1, 0.9), .extra_trafo = function(x, param_set) list(c(spam = x$spam, nonspam = x$nonspam))