Skip to content

Commit

Permalink
Browse files Browse the repository at this point in the history
  • Loading branch information
mattansb committed Nov 29, 2020
1 parent 72c1b72 commit 4892756
Show file tree
Hide file tree
Showing 6 changed files with 53 additions and 28 deletions.
12 changes: 8 additions & 4 deletions R/cohens_d.R
Original file line number Diff line number Diff line change
Expand Up @@ -107,7 +107,7 @@ glass_delta <- function(x, y = NULL, data = NULL, correction = FALSE, ci = 0.95)



#' @importFrom stats sd na.omit
#' @importFrom stats sd na.omit complete.cases
#' @keywords internal
.effect_size_difference <- function(x,
y = NULL,
Expand All @@ -131,9 +131,13 @@ glass_delta <- function(x, y = NULL, data = NULL, correction = FALSE, ci = 0.95)

# Compute index
if (paired) {
d <- mean(x - y, na.rm = TRUE)
s <- stats::sd(x - y, na.rm = TRUE)
n <- length(stats::na.omit(x - y))
o <- stats::complete.cases(x,y)
x <- x[o]
y <- y[o]

d <- mean(x - y)
s <- stats::sd(x - y)
n <- length(x)
df <- n - 1
hn <- 1 / df
t <- d / (s / sqrt(n))
Expand Down
7 changes: 4 additions & 3 deletions R/convert_d_to_r.R
Original file line number Diff line number Diff line change
Expand Up @@ -26,15 +26,16 @@
#' @return Converted index.
#'
#' @details
#' Conversions between *OR* and *r* is done through these formulae.
#' - *d to r*: \eqn{d = \frac{2 * r}{\sqrt{1 - r^2}}}
#' - *r to d*: \eqn{r = \frac{d}{\sqrt{d^2 + 4}}}
#' - *OR to d*: \eqn{d = \frac{\log(OR)\times\sqrt{3}}{\pi}}
#' - *d to OR*: \eqn{log(OR) = d * \frac{\pi}{\sqrt(3)}}
#'
#' Conversions between *OR* and *r* is done through these formulae.
#' \cr\cr
#' When converting *d* to *r*, the resulting *r* is also called the binomial
#' effect size display (BESD; Rosenthal et al., 1982).
#' The conversion from *d* to *r* assumes equally sized groups. The resulting
#' *r* is also called the binomial effect size display (BESD; Rosenthal et al.,
#' 1982).
#'
#' @references
#' - Sánchez-Meca, J., Marín-Martínez, F., & Chacón-Moscoso, S. (2003). Effect-size indices for dichotomized outcomes in meta-analysis. Psychological methods, 8(4), 448.
Expand Down
20 changes: 13 additions & 7 deletions R/convert_tFz_to_r.R
Original file line number Diff line number Diff line change
Expand Up @@ -26,11 +26,15 @@
#' \cr\cr
#' \deqn{r_{partial} = z / \sqrt{z^2 + N}}
#' \cr\cr
#' \deqn{Cohen's d = 2 * t / \sqrt{df_{error}}}
#' \deqn{d = 2 * t / \sqrt{df_{error}}}
#' \cr\cr
#' \deqn{Cohen's d_z = t / \sqrt{df_{error}}}
#' \deqn{d_z = t / \sqrt{df_{error}}}
#' \cr\cr
#' \deqn{Cohen's d = 2 * z / \sqrt{N}}
#' \deqn{d = 2 * z / \sqrt{N}}
#'
#' The resulting `d` effect size is an *approximation* to Cohen's *d*, and
#' assumes equal group sizes. When possible, it is advised to directly estimate
#' Cohen's *d*, with [cohens_d()], [emmeans::eff_size()], or similar functions.
#'
#' @inheritSection cohens_d Confidence Intervals
#'
Expand Down Expand Up @@ -65,16 +69,18 @@
#' if (require(emmeans)) {
#' warp.lm <- lm(breaks ~ wool * tension, data = warpbreaks)
#'
#' conts <- summary(pairs(emmeans(warp.lm, ~ tension | wool)))
#' t_to_d(conts$t.ratio, conts$df)
#' }
#'
#' # Also see emmeans::eff_size()
#' em_tension <- emmeans(warp.lm, ~ tension)#'
#' diff_tension <- summary(pairs(em_tension))
#' t_to_d(diff_tension$t.ratio, diff_tension$df)
#' }
#' }
#'
#' @references
#' - Friedman, H. (1982). Simplified determinations of statistical power, magnitude of effect and research sample sizes. Educational and Psychological Measurement, 42(2), 521-526. \doi{10.1177/001316448204200214}
#' - Wolf, F. M. (1986). Meta-analysis: Quantitative methods for research synthesis (Vol. 59). Sage.
#' - Rosenthal, R. (1991). Meta-analytic procedures for social research. Newbury Park, CA: SAGE Publications, Incorporated.
#' - Rosenthal, R. (1994) Parametric measures of effect size. In H. Cooper and L.V. Hedges (Eds.). The handbook of research synthesis. New York: Russell Sage Foundation.
#' - Steiger, J. H. (2004). Beyond the F test: Effect size confidence intervals and tests of close fit in the analysis of variance and contrast analysis. Psychological Methods, 9, 164-182.
#' - Cumming, G., & Finch, S. (2001). A primer on the understanding, use, and calculation of confidence intervals that are based on central and noncentral distributions. Educational and Psychological Measurement, 61(4), 532-574.
#'
Expand Down
7 changes: 4 additions & 3 deletions man/d_to_r.Rd

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

20 changes: 13 additions & 7 deletions man/t_to_r.Rd

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

15 changes: 11 additions & 4 deletions vignettes/from_test_statistics.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -192,15 +192,22 @@ These can be useful in contrast analyses.
### Between-Subject Contrasts

```{r}
warp.lm <- lm(breaks ~ tension, data = warpbreaks)
m <- lm(breaks ~ tension, data = warpbreaks)
pairs(emmeans(warp.lm, ~ tension))
em_tension <- emmeans(m, ~ tension)
pairs(em_tension)
t_to_d(t = c(2.5, 3.7, 1.2),
t_to_d(t = c(2.53, 3.72, 1.20),
df_error = 51)
```

However, these are merely approximations of a *true* Cohen's *d*. It is advised to directly estimate Cohen's *d*, whenever possible. For example, here with `emmeans::eff_size()`:

```{r}
eff_size(em_tension, sigma = sigma(m), edf = df.residual(m))
```


### Within-Subject Contrasts

```{r}
Expand All @@ -213,7 +220,7 @@ t_to_d(t = c(-5.7,-5.9,-3.2),
```

(Note `paired = TRUE` to not over estimate the size of the effect; @rosenthal1991meta; @rosnow2000contrasts)
(Note set `paired = TRUE` to not over estimate the size of the effect; @rosenthal1991meta; @rosnow2000contrasts)


# References

0 comments on commit 4892756

Please sign in to comment.