Skip to content

Commit

Permalink
detrend without qqplotr
Browse files Browse the repository at this point in the history
  • Loading branch information
mattansb committed Jul 23, 2023
1 parent fcb386b commit 39b6b13
Show file tree
Hide file tree
Showing 2 changed files with 44 additions and 28 deletions.
66 changes: 41 additions & 25 deletions R/plot.check_normality.R
Original file line number Diff line number Diff line change
Expand Up @@ -12,8 +12,8 @@
#' @param alpha Numeric value specifying alpha level of the confidence bands.
#' @param colors Character vector of length two, indicating the colors (in
#' hex-format) for points and line.
#' @param detrend Logical that decides if Q-Q and P-P plots should be de-trended.
#' Defaults to `TRUE` if the *qqplotr* package is installed and `FALSE` otherwise.
#' @param detrend Logical that decides if Q-Q and P-P plots should be de-trended
#' (also known as _worm plots_).
#' @param method The method used for estimating the qq/pp bands. Default to
#' `"ell"` (equal local levels / simultaneous testing - recommended). Can also
#' be one of `"pointwise"` or `"boot"` for pointwise confidence bands, or
Expand Down Expand Up @@ -43,7 +43,7 @@ plot.see_check_normality <- function(x,
alpha = 0.2,
dot_alpha = 0.8,
colors = c("#3aaf85", "#1b6ca8"),
detrend = requireNamespace("qqplotr", quietly = TRUE),
detrend = TRUE,
method = "ell",
...) {
type <- match.arg(type)
Expand Down Expand Up @@ -209,32 +209,47 @@ plot.see_check_normality <- function(x,
detrend = detrend
)
)
y_lab <- "Sample Quantiles"
if (detrend) {
y_lab <- "Sample Quantile Deviations"
} else {
y_lab <- "Sample Quantiles"
}
} else {
insight::format_alert(
paste0(
"For confidence bands",
if (isTRUE(detrend)) " and detrending",
", please install `qqplotr`."
)
)
insight::format_alert("For confidence bands, please install `qqplotr`.")

gg_init <- ggplot2::ggplot(x, ggplot2::aes(sample = .data$y))

qq_stuff <- list(
ggplot2::geom_qq_line(
linewidth = size_line,
colour = colors[1],
na.rm = TRUE
),
if (detrend) {
ggplot2::geom_hline(
yintercept = 0,
linewidth = size_line,
colour = colors[1],
na.rm = TRUE
)
} else {
ggplot2::geom_qq_line(
linewidth = size_line,
colour = colors[1],
na.rm = TRUE
)
}
,
ggplot2::geom_qq(
mapping = if (detrend) ggplot2::aes(y = ggplot2::after_stat(sample) - ggplot2::after_stat(theoretical)),
shape = 16,
na.rm = TRUE,
stroke = 0,
size = size_point,
colour = colors[2] # "#2c3e50"
)
)
y_lab <- "Sample Quantiles"

if (detrend) {
y_lab <- "Sample Quantile Deviations"
} else {
y_lab <- "Sample Quantiles"
}
}

if (!isTRUE(show_dots)) {
Expand Down Expand Up @@ -284,36 +299,37 @@ plot.see_check_normality <- function(x,
detrend = detrend
)
} else if (requireNamespace("MASS", quietly = TRUE)) {
message(
"For confidence bands",
if (isTRUE(detrend)) " and detrending",
", please install `qqplotr`."
)
insight::format_alert("For confidence bands, please install `qqplotr`.")

x$probs <- stats::ppoints(x$res)
dparms <- MASS::fitdistr(x$res, densfun = "normal")
x$y <- do.call(stats::pnorm, c(list(q = x$res), dparms$estimate))

p_plot <- ggplot2::ggplot(x, ggplot2::aes(x = .data$probs, y = .data$y)) +
ggplot2::geom_abline(
slope = 1,
slope = if (detrend) 0 else 1,
linewidth = size_line,
colour = colors[1]
) +
geom_point2(
mapping = if (detrend) ggplot2::aes(y = .data$y - .data$probs),
colour = colors[2],
size = size_point,
alpha = dot_alpha_level
) # "#2c3e50"
} else {
stop("Package 'qqplotr' OR 'MASS' required for P-P plots. Please install one of them.", call. = FALSE)
insight::format_error("Package 'qqplotr' OR 'MASS' required for P-P plots. Please install one of them.")
}


y_lab <- "Sample Cummulative Probability"
if (detrend) y_lab <- paste0(y_lab, " Deviations")

p_plot +
ggplot2::labs(
title = "Normality of Residuals",
subtitle = "Dots should fall along the line",
y = "Sample Cummulative Probability",
y = y_lab,
x = "Standard Normal Cumulative Probability"
) +
theme_style(
Expand Down
6 changes: 3 additions & 3 deletions man/plot.see_check_normality.Rd

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

0 comments on commit 39b6b13

Please sign in to comment.