Skip to content

Commit

Permalink
version 0.3
Browse files Browse the repository at this point in the history
update decision curve function calling syntax to ‘decision_curve’.

make separate function names for different curve plots.

organize code.

still need to work on the ‘summary’ function
  • Loading branch information
mdbrown committed Nov 4, 2015
1 parent 74f19f1 commit ddfa1e1
Show file tree
Hide file tree
Showing 37 changed files with 59,828 additions and 721 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Package: DecisionCurve
Type: Package
Title: Calculate and Plot Decision Curves
Version: 0.2
Version: 0.3
Date: 2015-08-04
Author: Marshall Brown
Maintainer: <mdbrown@fredhutch.org>
Expand Down
6 changes: 4 additions & 2 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -2,5 +2,7 @@

S3method(summary,DecisionCurve)
export(Add_CostBenefit_Axis)
export(DecisionCurve)
export(PlotDecisionCurve)
export(decision_curve)
export(plot_clinical_impact)
export(plot_decision_curve)
export(plot_roc_components)
21 changes: 10 additions & 11 deletions R/DecisionCurve.R → R/decision_curve.R
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@
#' \item call: matched function call.
#' }
#'
#' @seealso \code{\link{summary.DecisionCurve}}, \code{\link{Add_CostBenefit_Axis}}
#' @seealso \code{\link{summary.decision.curve}}, \code{\link{Add_CostBenefit_Axis}}
#' @examples
#'#helper function
#' expit <- function(xx) exp(xx)/ (1+exp(xx))
Expand All @@ -35,18 +35,17 @@
#'dcaData$FullModel <- with(dcaData, expit(-10.5 + 0.22*Age - 0.01*Female + 0.91*Smokes + 2.03*Marker1 - 1.56*Marker2))
#'
#'#use DecisionCurve defaults (set bootstraps = 25 here to reduce computation time).
#'DecisionCurve(dcaData,
#'decision_curve(dcaData,
#' outcome = "Cancer", predictors = c("BasicModel", "FullModel"),
#' bootstraps = 25)
#'
#' @export

DecisionCurve <- function(formula,
decision_curve <- function(formula,
data,
family = binomial(link = "logit"),
fitted.risk = FALSE,
thresholds = seq(0, 1, by = .01),
standardize = TRUE,
confidence.intervals = 0.95,
bootstraps = 500){
call <- match.call()
Expand All @@ -70,21 +69,21 @@ DecisionCurve <- function(formula,
#first we fit the model

#extract the model name from formula
predictors <- c(Reduce(paste, deparse(formula[[3]])), "all", "none")
predictor.names <- c(Reduce(paste, deparse(formula)), "all", "none")
predictors <- c(Reduce(paste, deparse(formula[[3]])), "All", "None")
predictor.names <- c(Reduce(paste, deparse(formula)), "All", "None")

#indicate whether we are fitting a model with a formula or not
#the last two are FALSE since they correspond to 'all' and 'none'
formula.ind <- c(ifelse(fitted.risk, FALSE, TRUE), FALSE, FALSE)

data[["all"]] <- 1
data[["none"]] <- 0
data[["All"]] <- 1
data[["None"]] <- 0

n.preds <- length(predictors) #should always be three

n.out <- length(predictors)*length(thresholds)
dc.data <- data.frame("thresholds" = numeric(n.out),
"FPF" = numeric(n.out),"TPF" = numeric(n.out),
"FPR" = numeric(n.out),"TPR" = numeric(n.out),
"NB" = numeric(n.out), "sNB" = numeric(n.out),
"rho" = numeric(n.out),"prob.high.risk" = numeric(n.out),
"DP" = numeric(n.out),
Expand Down Expand Up @@ -117,6 +116,7 @@ DecisionCurve <- function(formula,
if(is.numeric(confidence.intervals)){
#calculate measures in each bootstrap
boot.data <- apply(B.ind, 2, function(x){

calculate.nb(d = outcome[x],
y = data[[predictors[[i]] ]][x],
rH = thresholds,
Expand Down Expand Up @@ -154,10 +154,9 @@ DecisionCurve <- function(formula,

#return list of elements
out <- list("derived.data" = dc.data,
"standardized" = standardize,
"confidence.intervals" = confidence.intervals,
"call" = call)
class(out) = "DecisionCurve"
class(out) = "decision_curve"
invisible(out)

}
Expand Down
213 changes: 0 additions & 213 deletions R/plot.DecisionCurve.R

This file was deleted.

Loading

0 comments on commit ddfa1e1

Please sign in to comment.