1

I want to run several nested t.test and ttestBF (using tidyr::nest()) but I can't manage to either tidy or to unnest the S4: BFBayesFactor object that comes out the ttestBF function.

Example data:

set.seed(354654)
d = tibble(value = rnorm(100),
           category = sample(1:5, replace = TRUE, 100),
           group = sample(c('A', 'B'), replace = TRUE, 100)) %>% 
  arrange(category)

I run this piece of code for the t.test and it works just fine:

library('tidyverse')
library('broom')

d %>% 
  group_by(category, group) %>% 
  nest() %>% 
  spread(key = group, value = data) %>% 
  mutate(
    t_test = map2(A, B, ~{t.test(.x$value, .y$value) %>% tidy()}),
    A = map(A, nrow),
    B = map(B, nrow)
  ) %>% 
  unnest()

However, if I try this:

d %>% 
  group_by(category, group) %>% 
  nest() %>% 
  spread(key = group, value = data) %>% 
  mutate(
    t_test_bf = map2(A, B, ~{ttestBF(.x$value, .y$value, nullInterval = c(0, Inf)) %>% tidy() }),
    A = map(A, nrow),
    B = map(B, nrow)
  ) %>% 
  unnest()

I get: Error: No tidy method for objects of class BFBayesFactor. If I remove the tidy() call, so:

t_test_bf = map2(A, B, ~{ttestBF(.x$value, .y$value, nullInterval = c(0, Inf)) })

I still get the following error:

Error: All nested columns must have the same number of elements.

Any idea on how to unnest the ttestBF output?

niklai
  • 376
  • 3
  • 16

1 Answers1

1

You could pull the data frame out of each object's bayesFactor S4 slot using the @ notation for S4 objects:

d %>% 
  group_by(category, group) %>% 
  nest() %>% 
  spread(key = group, value = data) %>% 
  mutate(
    t_test_bf = map2(A, B, ~{ttestBF(.x$value, .y$value, 
                                     nullInterval = c(0, Inf))@bayesFactor}[,-3]),
    A = map(A, nrow),
    B = map(B, nrow)
  ) %>% 
  unnest()
#> # A tibble: 10 x 6
#> # Groups:   category [5]
#>    category     A     B     bf        error code        
#>       <int> <int> <int>  <dbl>        <dbl> <fct>       
#>  1        1    10    10 -1.04  0.0000592    159448f630f7
#>  2        1    10    10 -0.797 0.0000000429 1594124c5471
#>  3        2     7     6 -0.519 0.000000105  15946a5667c9
#>  4        2     7     6 -1.01  0.000141     15946b70910 
#>  5        3     8     9 -1.32  0.00000260   15944c833396
#>  6        3     8     9 -0.214 0.000000168  159433103012
#>  7        4    15    11 -0.709 0.0000450    15942a13701 
#>  8        4    15    11 -1.26  0.000123     15947c9d5ed8
#>  9        5    11    13 -1.11  0.000122     15945bcc7d07
#> 10        5    11    13 -0.850 0.00000969   1594311d17e2
Allan Cameron
  • 147,086
  • 7
  • 49
  • 87