Skip to content

Commit

Permalink
Add domains
Browse files Browse the repository at this point in the history
  • Loading branch information
teunbrand committed Jul 25, 2023
1 parent b3df2fb commit 4cac736
Showing 1 changed file with 5 additions and 3 deletions.
8 changes: 5 additions & 3 deletions R/trans-numeric.r
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,8 @@ asn_trans <- function() {
trans_new(
"asn",
function(x) 2 * asin(sqrt(x)),
function(x) sin(x / 2)^2
function(x) sin(x / 2)^2,
domain = c(0, 1)
)
}

Expand Down Expand Up @@ -88,7 +89,7 @@ boxcox_trans <- function(p, offset = 0) {
}

trans_new(
paste0("pow-", format(p)), trans, inv
paste0("pow-", format(p)), trans, inv, domain = c(0, Inf)
)
}

Expand Down Expand Up @@ -276,7 +277,8 @@ probability_trans <- function(distribution, ...) {
trans_new(
paste0("prob-", distribution),
function(x) qfun(x, ...),
function(x) pfun(x, ...)
function(x) pfun(x, ...),
domain = c(0, 1)
)
}
#' @export
Expand Down

0 comments on commit 4cac736

Please sign in to comment.