Skip to content

Commit

Permalink
fix
Browse files Browse the repository at this point in the history
  • Loading branch information
strengejacke committed Nov 6, 2024
1 parent 70d038c commit d0d241c
Show file tree
Hide file tree
Showing 6 changed files with 29 additions and 14 deletions.
12 changes: 8 additions & 4 deletions R/format_bf.R
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,9 @@
#' @param exact Should very large or very small values be reported with a
#' scientific format (e.g., 4.24e5), or as truncated values (as "> 1000" and
#' "< 1/1000").
#' @param inferiority_star String, indicating the symbol that is used to
#' indicate inferiority, i.e. when the Bayes Factor is smaller than one third
#' (the thresholds are smaller than one third, 1/10 and 1/30).
#' @inheritParams format_p
#'
#' @return A formatted string.
Expand All @@ -22,6 +25,7 @@
format_bf <- function(bf,
stars = FALSE,
stars_only = FALSE,
inferiority_star = "°",
name = "BF",
protect_ratio = FALSE,
na_reference = NA,
Expand Down Expand Up @@ -84,13 +88,13 @@ format_bf <- function(bf,
)

## Add stars
bf_text <- ifelse(bf_orig < (1 / 30), paste0(bf_text, "\u00B0\u00B0\u00B0"),
ifelse(bf_orig < 0.1, paste0(bf_text, "\u00B0\u00B0"), # nolint
ifelse(bf_orig < (1 / 3), paste0(bf_text, "\u00B0"), bf_text) # nolint
bf_text <- ifelse(bf_orig < (1 / 30), paste0(bf_text, paste(rep_len(inferiority_star, 3), collapse = "")), # nolint
ifelse(bf_orig < 0.1, paste0(bf_text, paste(rep_len(inferiority_star, 2), collapse = "")), # nolint
ifelse(bf_orig < (1 / 3), paste0(bf_text, inferiority_star), bf_text) # nolint
)
)

out <- .add_prefix_and_remove_stars(p_text = bf_text, stars, stars_only, name)
out <- .add_prefix_and_remove_stars(p_text = bf_text, stars, stars_only, name, inferiority_star)
if (is.na(na_reference)) out[bad_bf] <- ""
out
}
10 changes: 6 additions & 4 deletions R/format_p.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,8 @@
#' Format p-values.
#'
#' @param p value or vector of p-values.
#' @param stars Add significance stars (e.g., p < .001***).
#' @param stars Add significance stars (e.g., p < .001***). For Bayes factors,
#' the thresholds for "significant" results are values larger than 3, 10, and 30.
#' @param stars_only Return only significance stars.
#' @param whitespace Logical, if `TRUE` (default), preserves whitespaces. Else,
#' all whitespace characters are removed from the returned string.
Expand Down Expand Up @@ -111,7 +112,8 @@ format_p <- function(p,
name,
missing = "",
whitespace = TRUE,
decimal_separator = NULL) {
decimal_separator = NULL,
inferiority_star = "°") {
missing_index <- is.na(p_text)

if (is.null(name)) {
Expand All @@ -121,10 +123,10 @@ format_p <- function(p,
}

if (stars_only) {
p_text <- gsub("[^(\\*|°)]", "", p_text)
p_text <- gsub(paste0("[^(\\*|", inferiority_star, ")]"), "", p_text)
} else if (!stars) {
p_text <- gsub("*", "", p_text, fixed = TRUE)
p_text <- gsub("\u00B0", "", p_text, fixed = TRUE)
p_text <- gsub(inferiority_star, "", p_text, fixed = TRUE)
}

# replace missing with related string
Expand Down
11 changes: 9 additions & 2 deletions man/format_bf.Rd

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

3 changes: 2 additions & 1 deletion man/format_p.Rd

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

3 changes: 2 additions & 1 deletion man/format_pd.Rd

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

4 changes: 2 additions & 2 deletions tests/testthat/test-format.R
Original file line number Diff line number Diff line change
Expand Up @@ -111,11 +111,11 @@ test_that("format others", {
c("< 0.001", "0.033", "", "> 1000", "3.54")
)
expect_identical(
format_bf(c(0.000045, 0.033, NA, 1557, 3.54), stars = TRUE),
format_bf(c(0.000045, 0.233, NA, 1557, 3.54), stars = TRUE),
c("BF < 0.001°°°", "BF = 0.233°", "", "BF > 1000***", "BF = 3.54*")
)
expect_identical(
format_bf(c(0.000045, 0.033, NA, 1557, 3.54), stars = TRUE, stars_only = TRUE),
format_bf(c(0.000045, 0.233, NA, 1557, 3.54), stars = TRUE, stars_only = TRUE),
c("°°°", "°", "", "***", "*")
)
expect_identical(
Expand Down

0 comments on commit d0d241c

Please sign in to comment.