
Group: 🗸 a pod of killer whales
## Setup your dosing data (if you have it and even if you don't) {.smaller}
Normal dosing data setup: `PKNCAdose(dose~time|actarm+usubjid, data=d_dose)`
* Dose amount must be numeric — or it can be omitted
* `PKNCAdose(~time|actarm+usubjid, data=d_dose)`
* Time must be numeric and not be missing — or it can be omitted
* `PKNCAdose(dose~.|actarm+usubjid, data=d_dose)`
* Groups can be anything — may be grouped at a higher level than the individual
* Useful when all dose amounts and times are the same within an arm: `PKNCAdose(dose~time|actarm, data=d_dose)`
* Useful dose amount is the same at all times within an arm: `PKNCAdose(dose~.|actarm, data=d_dose)`
* Useful when times are all the same within an arm but dose may differ: `PKNCAdose(~time|actarm, data=d_dose)`
## Define your intervals
Intervals have columns for:
* `start` and `end` times for the interval,
* groups matching any level of grouping; intervals apply by a merge/join with the groups
* parameters to calculate (`TRUE` means to calculate it; `FALSE` means don't). The full list of available parameters is in the [selection of calculation intervals vignette](http://billdenney.github.io/pknca/articles/Selection-of-Calculation-Intervals.html#parameters-available-for-calculation-in-an-interval-1).
* You only have to specify the parameter you want, not all parameters.
## Define your intervals: example
* For time 0 to 24, calculate AUClast
* For time 0 to infinity, calculate cmax, tmax, half.life, and aucinf.obs
```{r}
PKNCA.options("single.dose.aucs") %>%
select(c(all_of(c("start", "end")), where(~is.logical(.x) && any(.x)))) %>%
pander::pander()
```
# Calculations above the hood
## Prepare your data for calculation
```{r echo=TRUE}
d_conc <-
datasets::Theoph %>%
mutate(
Treatment=
case_when(
Dose <= median(Dose)~"Low dose",
TRUE~"High dose"
)
)
# The study was single-dose
d_dose <-
d_conc %>%
select(Treatment, Subject, Dose) %>%
unique() %>%
mutate(dose_time=0)
```
## Calculate without dosing data {.build}
```{r echo=TRUE}
o_conc <- PKNCAconc(conc~Time|Treatment+Subject, data=d_conc)
try({
o_data <- PKNCAdata(o_conc)
summary(pk.nca(o_data))
})
```
Whoops! Without dosing, we need intervals.
## Calculate without dosing data, try 2
```{r echo=TRUE}
o_conc <- PKNCAconc(conc~Time|Treatment+Subject, data=d_conc)
d_intervals <- data.frame(start=0, end=Inf, cmax=TRUE, tmax=TRUE,
half.life=TRUE, aucinf.obs=TRUE)
o_data_manual_intervals <- PKNCAdata(o_conc, intervals=d_intervals)
summary(pk.nca(o_data_manual_intervals))
```
## Dosing data helps with interval setup
```{r echo=TRUE}
o_conc <- PKNCAconc(conc~Time|Treatment+Subject, data=d_conc)
o_dose <- PKNCAdose(Dose~dose_time|Treatment+Subject, data=d_dose)
o_data_auto_intervals <- PKNCAdata(o_conc, o_dose)
o_data_auto_intervals$intervals$aucint.inf.obs <- TRUE
summary(pk.nca(o_data_auto_intervals))
```
## AUC considerations with PKNCA (1/3) {.columns-2}
```{r auc-considerations-setup, warning=FALSE}
d_conc <-
datasets::Theoph %>%
filter(Subject == 1)
o_conc <- PKNCAconc(conc~Time, data=d_conc)
d_interval_int <- data.frame(start=0, end=Inf, half.life=TRUE)
o_data_int <- PKNCAdata(o_conc, intervals=d_interval_int)
o_nca_int <- suppressMessages(pk.nca(o_data_int))
lambda_z_int <-
o_nca_int %>%
as.data.frame() %>%
filter(PPTESTCD %in% "lambda.z") %>%
"[["("PPORRES")
d_interval_inf <- data.frame(start=0, end=24, half.life=TRUE)
o_data_inf <- PKNCAdata(o_conc, intervals=d_interval_inf)
o_nca_inf <- suppressMessages(pk.nca(o_data_inf))
lambda_z_inf <-
o_nca_inf %>%
as.data.frame() %>%
filter(PPTESTCD %in% "lambda.z") %>%
"[["("PPORRES")
tlast <-
o_nca_inf %>%
as.data.frame() %>%
filter(PPTESTCD %in% "tlast") %>%
"[["("PPORRES")
d_auc_calcs <-
d_conc %>%
bind_rows(
tibble(Time=seq(12, 60))
) %>%
mutate(
conc_all_int=
interp.extrap.conc(
conc=conc[!is.na(conc)],
time=Time[!is.na(conc)],
time.out=Time,
lambda.z=lambda_z_int
),
conc_all_inf=
interp.extrap.conc(
conc=conc[!is.na(conc) & Time <= 24],
time=Time[!is.na(conc) & Time <= 24],
time.out=Time,
lambda.z=lambda_z_inf
),
conc_last=
case_when(
Time <= 24~conc,
TRUE~NA_real_
),
conc_int=
case_when(
Time <= 24 & Time >= tlast~conc_all_int,
TRUE~NA_real_
),
conc_inf=
case_when(
Time >= tlast~conc_all_inf,
TRUE~NA_real_
)
) %>%
arrange(Time)
auc_figure_time_max <- 36
p_auc_calcs <-
ggplot(d_auc_calcs, aes(x=Time, y=conc)) +
# AUCinf (with a work-around for https://github.com/tidyverse/ggplot2/issues/4661)
geom_area(
data=d_auc_calcs %>% filter(Time <= auc_figure_time_max),
aes(y=conc_inf, colour="AUCinf", fill="AUCinf"),
alpha=0.2,
na.rm=TRUE
) +
geom_line(
data=d_auc_calcs,
aes(y=conc_inf, colour="AUCinf"),
na.rm=TRUE
) +
# AUCint
geom_area(
aes(y=conc_int, colour="AUCint", fill="AUCint"),
alpha=0.2,
na.rm=TRUE
) +
# AUClast
geom_area(
aes(y=conc_last, colour="AUClast", fill="AUClast"),
na.rm=TRUE
) +
geom_point(show.legend=FALSE,
na.rm=TRUE) +
geom_line(show.legend=FALSE,
na.rm=TRUE) +
geom_vline(xintercept=24, linetype="63") +
scale_x_continuous(breaks=seq(0, auc_figure_time_max, by=6)) +
coord_cartesian(xlim=c(0, auc_figure_time_max)) +
labs(
colour="AUC type",
fill="AUC type"
)
```
```{r warning=FALSE, out.width="100%"}
p_auc_calcs
```
Hey babe, did you get my 5 rows of data?
I only saw 4 rows. Are you sure you sent 5?
Yep, definitely 5 check that last slide. 😠
## Digression: How is λz automatically calculated? {.smaller}
* Filter the data from the first point after t~max~ (or from t~max~ if `allow.tmax.in.half.life=TRUE`) to t~last~ and excluding BLQ in the middle.
* Fit the semi-log line from 3 points before t~last~ (3 can be changed with the `min.hl.points` option) to t~last~.
* Repeat for all sets of points from there to the first point included.
* If that 3 points are not available, it is not calculated.
* Among the fits, select the best adjusted r^2^ (within a tolerance of `adj.r.squared.factor`).
* Require λz` > 0`.
* If more than one fit is available at this point, select the one with the most points included.
Note: WinNonlin first requires λz` > 0` then selects for adjusted r^2^. Therefore, WinNonlin will occasionally provide a half-life when PKNCA will not, but the fit line is not as good (as measured by r^2^). The selection of filtering order is an intentional feature with PKNCA, and it generally has minimal impact on summary statistics because the quality of the half-life fit is usually low in this scenario.
## λz control (manual exclusions and inclusions of data points)
Use the `exclude_half.life` or `include_half.life` argument for `PKNCAconc()`. The two arguments behave very differently in how points are selected for half-life.
`exclude_half.life` uses the same automatic point selection method of curve stripping (described before), but it excludes individual points from that calculation.
`include_half.life` uses no automatic point selection method, and only points specifically noted by the analyst are included.
# Less-common calculations
## Urine calculations
```{r echo=TRUE}
d_urine <-
data.frame(
conc=c(1, 2, 3),
urine_volume=c(200, 100, 300),
time=c(1, 2, 3)
)
o_conc <- PKNCAconc(data=d_urine, conc~time, volume="urine_volume")
d_intervals <- data.frame(start=0, end=24, ae=TRUE)
o_data <- PKNCAdata(o_conc, intervals=d_intervals)
o_nca <- suppressMessages(pk.nca(o_data))
summary(o_nca)
```
## Urine calculations: understanding what is happening and potential hiccups
Intervals for urine are treated the same as any other interval type. Specifically, PKNCA does not look outside the start and end of the interval.
* Watch out for e.g. a 24-hour urine amount to be included in more than one interval because start = 0 and end = 24.
* Watch out for an actual start or end time to be outside of the interval and therefore to be omitted from calculations.
# Calculations below the hood
## PKNCA only calculates what is required, not every possible parameter (1 of 2)
If you don't need a parameter, PKNCA won't calculate it.
For example, if all you need is `cmax`, all you'll get is `cmax`.
```{r echo=TRUE}
o_conc <- PKNCAconc(data=data.frame(conc=2^-(1:4), time=0:3), conc~time)
o_data <- PKNCAdata(o_conc, intervals=data.frame(start=0, end=Inf, cmax=TRUE))
o_nca <- suppressMessages(pk.nca(o_data))
as.data.frame(o_nca)
```
## PKNCA only calculates what is required, not every possible parameter (2 of 2) {.columns-2 .smaller}
If you need AUC~0-\infty~, PKNCA will calculate other required parameters behind the scenes.
```{r echo=TRUE}
o_data <-
PKNCAdata(
o_conc,
intervals=
data.frame(
start=0, end=Inf,
aucinf.obs=TRUE
)
)
o_nca <- suppressMessages(pk.nca(o_data))
```