Skip to content

Commit

Permalink
Merge branch 'main' into add-user-error-message-for-missing-strata
Browse files Browse the repository at this point in the history
  • Loading branch information
chrisorwa authored Aug 12, 2024
2 parents 3c271ee + 68eeb82 commit ee3d7ca
Show file tree
Hide file tree
Showing 3 changed files with 39 additions and 9 deletions.
25 changes: 24 additions & 1 deletion R/as_curve_params.R
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,20 @@
#'
#' print(curve_data)
as_curve_params <- function(data, antigen_isos = NULL) {

if(!is.data.frame(data))
{
cli::cli_abort(
class = "not data.frame",
message = c(
"Can't convert {.arg data} to {.cls curve_params}.",
"x" = "{.arg data} must be a {.cls data.frame}
(or a subclass of {.cls data.frame}).",
"i" = "You have supplied a {.cls {class(data)}}."
)
)
}

curve_data <-
data %>%
tibble::as_tibble()
Expand All @@ -22,9 +36,18 @@ as_curve_params <- function(data, antigen_isos = NULL) {

# check if object is curve (with columns)
if (!all(is.element(curve_cols, curve_data %>% names()))) {
# get columns from provided data
data_cols <- data %>% names()

# get any missing column(s)
missing_cols <- setdiff(x = curve_cols, y = data_cols)

cli::cli_abort(
class = "not curve_params",
message = c("Please provide curve data.") # TO DO: 'or check variable names' (message)
message = c(
"Can't convert {.arg data} to {.cls curve_params}.",
"x" = "The column{?s}: {.strong {.var {missing_cols}}} are missing."
)
)
}

Expand Down
13 changes: 9 additions & 4 deletions tests/testthat/test-as_curve_params.R
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,14 @@ test_that("`as_curve_params()` produces an error when non-curve data is provided
)
})

test_that("`as_curve_params()` produces an error when `data` is not a data.frame",
{
library(magrittr)
expect_error(object =
"https://osf.io/download//n6cp3/" %>% # pop data
as_curve_params(), class = "not data.frame")
})

test_that("`as_curve_params()` produces expected results", {
library(dplyr)
test_data <- "https://osf.io/download/rtw5k/" %>% # curve data
Expand All @@ -18,10 +26,7 @@ test_that("`as_curve_params()` produces expected results", {

expect_snapshot(test_data)

expect_snapshot_value(
x = test_data,
style = "serialize"
)
expect_snapshot_value(x = test_data, style = "serialize")


})
10 changes: 6 additions & 4 deletions vignettes/articles/enteric_fever_example.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -81,7 +81,7 @@ curves <-
We can graph the decay curves with an `autoplot()` method:

```{r}
curves %>% filter(antigen_iso == "HlyE_IgA"| antigen_iso == "HlyE_IgG") %>%autoplot()
curves %>% filter(antigen_iso == "HlyE_IgA"| antigen_iso == "HlyE_IgG") %>% autoplot()
```


Expand Down Expand Up @@ -190,16 +190,18 @@ In this plot, a steeper slope indicates a higher incidence. We can see that the
Next, we must set conditions based on some assumptions about the data and errors that may need to be accounted for. This will differ based on background knowledge of the data.


The biological noise, $\nu$ ("nu"), represents error from cross-reactivity to other antibodies. Measurement noise, $\varepsilon$ ("epsilon"), represents error from the laboratory testing process.
The biological noise, $\nu$ ("nu"), represents error from cross-reactivity to other antibodies. It is defined as the 95th percentile of the distribution of antibody responses to the antigen-isotype in a populaiton with no exposure.

Measurement noise, $\varepsilon$ ("epsilon"), represents measurement error from the laboratory testing process. It is defined by a CV (coeficient of variation) as the ratio of the standard deviation to the mean for replicates. Note that the CV should ideally me measured accross plates rather than within the same plate.

*Formatting Specifications*: Noise parameter data should be a dataframe with one row for each antigen isotype and columns for each noise parameter below.


Column Name | Description
----------- | -----------
y.low | Lower limit of detection of the antibody assay
y.low | Lower limit of detection of the assay
nu | Biologic noise
y.high | Upper limit of detection of the antibody assay
y.high | Upper limit of detection of the assay
eps | Measurement noise
*Note that variable names are case-sensitive.*

Expand Down

0 comments on commit ee3d7ca

Please sign in to comment.