Skip to content

Commit

Permalink
added medSurvCI, medSurvQuant as summary statistics for survival
Browse files Browse the repository at this point in the history
  • Loading branch information
bethatkinson committed May 15, 2024
1 parent 497db28 commit 15cb347
Show file tree
Hide file tree
Showing 4 changed files with 53 additions and 4 deletions.
6 changes: 3 additions & 3 deletions R/tableby.R
Original file line number Diff line number Diff line change
Expand Up @@ -126,7 +126,7 @@ tableby <- function(formula, data, na.action, subset=NULL, weights=NULL, strata,

Call <- match.call()
## Tell user if they passed an argument that was not expected, either here or in control
expectArgs <- c("formula", "data", "na.action", "subset", "weights", "strata", "control", names(control), "times")
expectArgs <- c("formula", "data", "na.action", "subset", "weights", "strata", "control", names(control), "times","survconf.type")
match.idx <- match(names(Call)[-1], expectArgs)
if(anyNA(match.idx)) warning("unused arguments: ", paste(names(Call)[1+which(is.na(match.idx))], collapse=", "), "\n")

Expand Down Expand Up @@ -401,11 +401,11 @@ tableby <- function(formula, data, na.action, subset=NULL, weights=NULL, strata,
for(bylev in by.levels) {
idx <- bycol == bylev
bystatlist[[bylev]] <- do.call(statfun, list(currcol[idx], levels=xlevels, na.rm=TRUE,
weights=weightscol[idx], conf.level=control$conf.level, times=control$times))
weights=weightscol[idx], conf.level=control$conf.level, times=control$times, survconf.type=control$survconf.type))
}
## add Total
bystatlist[[totallab]] <- do.call(statfun, list(currcol, levels=xlevels, na.rm=TRUE,
weights=weightscol, conf.level=control$conf.level, times=control$times))
weights=weightscol, conf.level=control$conf.level, times=control$times, survconf.type=control$survconf.type))
}
statList[[statfun2]] <- bystatlist
}
Expand Down
1 change: 1 addition & 0 deletions R/tableby.control.R
Original file line number Diff line number Diff line change
Expand Up @@ -149,6 +149,7 @@ add_tbc_stats_labels <- function(x) {
mean = "Mean", sd = "SD", var = "Var", max = "Max", min = "Min", meanCI = "Mean (CI)", sum = "Sum",
gmean = "Geom Mean", gsd = "Geom SD", gmeansd = "Geom Mean (Geom SD)", gmeanCI = "Geom Mean (CI)",
range="Range", Npct="N (%)", Nrowpct="N (%)", Nevents="Events", medSurv="Median Survival",
medSurvQuant="Median (Q1, Q3) Survival", medSurvCI="Median (CI)",
medTime = "Median Follow-Up", medianmad="Median (MAD)", Nsigntest = "N (sign test)",
overall = "Overall", total = "Total", difference = "Difference"
)
Expand Down
40 changes: 40 additions & 0 deletions R/tableby.stats.R
Original file line number Diff line number Diff line change
Expand Up @@ -313,6 +313,46 @@ medSurv <- function(x, na.rm = TRUE, weights = NULL, ...) {
as.tbstat(y)
}

## Median survival with confidence interval
#' @rdname tableby.stats
#' @export
medSurvCI <- function (x, na.rm = TRUE, weights = NULL, robust = FALSE, conf.type = 'log', ...) {
y <- if (na.rm && allNA(x)) {
NA_real_
}
else {
arsenal:::check_pkg("survival")
mat <- summary(survival::survfit(x ~ 1,
weights = weights,
robust = robust,
conf.type =conf.type))$table
m <- as.numeric(mat["median"])
ci <- c(as.numeric(mat["0.95LCL"]), as.numeric(mat["0.95UCL"]))
c(m, ci)
}
as.tbstat(y, fmt = "{y[1]} ({y[2]}, {y[3]})")
}

## Median survival with 25th/75th quantiles
#' @rdname tableby.stats
#' @export
medSurvQuant <- function (x, na.rm = TRUE, weights = NULL, robust = FALSE, ...) {
y <- if (na.rm && allNA(x)) {
NA_real_
}
else {
arsenal:::check_pkg("survival")
mat <- quantile(survival::survfit(x ~ 1,
weights = weights,
robust = robust
),
probs=c(0.5,0.25, 0.75))$quantile
mat
}
as.tbstat(y, fmt = "{y[1]} ({y[2]}, {y[3]})")
}


#' @rdname tableby.stats
#' @export
NeventsSurv <- function(x, na.rm = TRUE, weights = NULL, times=1:5, ...) {
Expand Down
10 changes: 9 additions & 1 deletion vignettes/tableby.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -319,7 +319,15 @@ summary(survfit(Surv(fu.time/365.25, fu.stat)~sex, data=mockstudy), times=1:5)
```

```{r, results='asis', eval=ge330}
summary(tableby(sex ~ Surv(fu.time/365.25, fu.stat), data=mockstudy, times=1:5, surv.stats=c("NeventsSurv","NriskSurv")))
summary(tableby(sex ~ Surv(fu.time/365.25, fu.stat), data=mockstudy, times=1:3, surv.stats=c("NeventsSurv")))
summary(tableby(sex ~ Surv(fu.time/365.25, fu.stat), data=mockstudy, times=1:5, surv.stats=c("NriskSurv")))
summary(tableby(sex ~ Surv(fu.time/365.25, fu.stat), data=mockstudy, surv.stats="medSurvCI", survconf.type='log-log'), digits=2)
summary(tableby(sex ~ Surv(fu.time/365.25, fu.stat), data=mockstudy, surv.stats="medSurvQuant"), digits=2)
```

## 5. Summarize date variables
Expand Down

0 comments on commit 15cb347

Please sign in to comment.