Nothing
# ------------------------------------------------------------------------------
# Generated by 'pre-generate/generate-dials.R': do not edit by hand.
# ------------------------------------------------------------------------------
#' @title Tune Vectorizations of Persistent Homology
#'
#' @description These tuning functions govern the parameters of
#' vectorizations implemented in **TDAvec**.
#'
#' @details
#'
#' The parameter `num_coef` is passed to `m` in
#' [TDAvec::computeComplexPolynomial()].
#'
#' The parameter `poly_type` is passed to `polyType` in
#' [TDAvec::computeComplexPolynomial()].
#'
#' The parameter `img_sigma` is passed to `sigma` in
#' [TDAvec::computePersistenceImage()].
#'
#' The parameter `num_levels` is passed to `k` in
#' [TDAvec::computePersistenceLandscape()].
#'
#' The parameter `weight_func_pl` is passed to `kernel` in
#' [TDAvec::computePersistenceLandscape()].
#'
#' The parameter `bandwidth` is passed to `h` in
#' [TDAvec::computePersistenceLandscape()].
#'
#' The parameter `weight_power` is passed to `p` in
#' [TDAvec::computePersistenceSilhouette()].
#'
#' The parameter `num_bars` is passed to `r` in
#' [TDAvec::computeTropicalCoordinates()].
#'
#' The parameter `num_bins` is passed to `d` in
#' [TDAvec::computeTemplateFunction()].
#'
#' The parameter `tent_shift` is passed to `epsilon` in
#' [TDAvec::computeTemplateFunction()].
#'
#' @name vpd-dials
#' @inheritParams dials::Laplace
#' @param values A character string of possible values.
#' @inheritParams dials::finalize
#' @importFrom scales transform_log10
#' @inheritParams step_pd_degree
#' @returns A `param` object or list of `param` objects.
#' @example inst/examples/zzz-ex-vpd-param.R
NULL
#' @name vpd-dials
#' @export
num_coef <- function(
range = c(1L, unknown()), trans = NULL
) {
new_quant_param(
type = "integer",
range = range,
inclusive = c(TRUE, TRUE),
trans = trans,
label = c(num_coef = "# Polynomial coefficients"),
finalize = get_pairs_max
)
}
#' @name vpd-dials
#' @export
poly_type <- function(
values = c("R", "S", "T"), trans = NULL
) {
new_qual_param(
type = "character",
values = values,
label = c(poly_type = "Type of polynomial"),
finalize = NULL
)
}
#' @name vpd-dials
#' @export
img_sigma <- function(
range = c(unknown(), unknown()), trans = transform_log10()
) {
new_quant_param(
type = "double",
range = range,
inclusive = c(TRUE, TRUE),
trans = trans,
label = c(img_sigma = "Convolved Gaussian standard deviation"),
finalize = get_pers_max_frac
)
}
#' @name vpd-dials
#' @export
num_levels <- function(
range = c(1L, unknown()), trans = NULL
) {
new_quant_param(
type = "integer",
range = range,
inclusive = c(TRUE, TRUE),
trans = trans,
label = c(num_levels = "# Levels or envelopes"),
finalize = get_pairs_max
)
}
#' @name vpd-dials
#' @export
weight_func_pl <- function(
values = c("triangle", "epanechnikov", "tricubic"), trans = NULL
) {
new_qual_param(
type = "character",
values = values,
label = c(weight_func_pl = "Kernel distance weight function"),
finalize = NULL
)
}
#' @name vpd-dials
#' @export
bandwidth <- function(
range = c(unknown(), unknown()), trans = transform_log10()
) {
new_quant_param(
type = "double",
range = range,
inclusive = c(TRUE, TRUE),
trans = trans,
label = c(bandwidth = "Kernel bandwidth"),
finalize = get_pers_max_frac
)
}
#' @name vpd-dials
#' @export
weight_power <- function(
range = c(1, 2), trans = NULL
) {
new_quant_param(
type = "double",
range = range,
inclusive = c(TRUE, TRUE),
trans = trans,
label = c(weight_power = "Exponent weight"),
finalize = NULL
)
}
#' @name vpd-dials
#' @export
num_bars <- function(
range = c(1L, unknown()), trans = NULL
) {
new_quant_param(
type = "integer",
range = range,
inclusive = c(TRUE, TRUE),
trans = trans,
label = c(num_bars = "# Bars (persistence pairs)"),
finalize = get_pairs_max
)
}
#' @name vpd-dials
#' @export
num_bins <- function(
range = c(2L, 20L), trans = NULL
) {
new_quant_param(
type = "integer",
range = range,
inclusive = c(TRUE, TRUE),
trans = trans,
label = c(num_bins = "Discretization grid bins"),
finalize = NULL
)
}
#' @name vpd-dials
#' @export
tent_shift <- function(
range = c(unknown(), unknown()), trans = transform_log10()
) {
new_quant_param(
type = "double",
range = range,
inclusive = c(TRUE, TRUE),
trans = trans,
label = c(tent_shift = "Discretization grid shift"),
finalize = get_pers_min_mult
)
}
Any scripts or data that you put into this service are public.
Add the following code to your website.
For more information on customizing the embed code, read Embedding Snippets.