Skip to content

Commit

Permalink
Merge pull request #30 from ankemt/summary-20
Browse files Browse the repository at this point in the history
Create a summary of statistics from the treatment ratio object
  • Loading branch information
bvreede authored Dec 2, 2022
2 parents f1e9046 + 4944f63 commit 6ab47de
Show file tree
Hide file tree
Showing 6 changed files with 76 additions and 7 deletions.
15 changes: 8 additions & 7 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -12,13 +12,14 @@ Encoding: UTF-8
LazyData: true
RoxygenNote: 7.2.1
Imports:
brio,
dplyr,
magrittr,
robustbase (>= 0.93-6),
stringr,
tidyr,
tidyselect
brio,
dplyr,
magrittr,
robustbase (>= 0.93-6),
stats,
stringr,
tidyr,
tidyselect
Suggests:
testthat (>= 3.1.5)
Config/testthat/edition: 3
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -4,4 +4,5 @@ export(find_outliers)
export(parse_MEA_file)
export(parse_designfile)
export(treatment_ratio)
export(treatment_stats)
import(magrittr)
16 changes: 16 additions & 0 deletions R/treatment_stats.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
#' Generate statistics for a treatment dataframe
#'
#' @param ratio_df resulting dataframe of the `treatment_ratio` function
#'
#' @return dataframe with summary statistics
#' @export
treatment_stats <- function(ratio_df){

df <- ratio_df |>
dplyr::group_by(Metric_type, Parameter, Group) |>
dplyr::summarize(n_wells = dplyr::n(),
Ratio_avg = mean(Treatment_ratio, na.rm=T),
Ratio_stdv = stats::sd(Treatment_ratio),
Ratio_SEM = stats::sd(Treatment_ratio)/sqrt(n_wells))
return(df)
}
17 changes: 17 additions & 0 deletions man/treatment_stats.Rd

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

Binary file added tests/testthat/output_treatment_ratio.Rda
Binary file not shown.
34 changes: 34 additions & 0 deletions tests/testthat/test-treatment_stats.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,34 @@
test_that("Summary is calculated correctly",{
load("output_treatment_ratio.Rda")

statsum <- treatment_stats(output_treatment_ratio)
expect_true("tbl_df" %in% class(statsum))
expect_equal(nrow(statsum), 288)

expected_cols <- c("Ratio_avg",
"Ratio_stdv",
"Ratio_SEM",
"n_wells",
"Group",
"Metric_type",
"Parameter")
for(cname in expected_cols){
expect_true(cname %in% names(statsum),
info=paste("Variable:",cname))
}

# there are 8 wells per group in the example data
expect_true(mean(statsum$n_wells) == 8)

# check some values
vals <- statsum[statsum$Parameter == "Mean Firing Rate (Hz)",]$Ratio_SEM
vals <- round(vals, digits = 8)
known_vals <- c(0.15674431,
0.04957502,
0.09320916,
0.12364473,
0.28510038,
0.12974997)
expect_true(all(known_vals %in% vals))

})

0 comments on commit 6ab47de

Please sign in to comment.