diff --git a/DESCRIPTION b/DESCRIPTION
index 15ca5381..3d4d3608 100644
--- a/DESCRIPTION
+++ b/DESCRIPTION
@@ -87,6 +87,6 @@ Collate:
'predprob.R'
'predprobDist.R'
'runShinyPhase1b.R'
+ 'sumBetaDiff.R'
'sumTable.R'
- 'sumbetadiff.R'
Config/testthat/edition: 3
diff --git a/NAMESPACE b/NAMESPACE
index 66cd55ab..1253a03a 100644
--- a/NAMESPACE
+++ b/NAMESPACE
@@ -32,18 +32,18 @@ export(runShinyPhase1b)
export(sumBetaDiff)
export(sumTable)
import(checkmate)
+importFrom(ggplot2,annotate)
importFrom(ggplot2,geom_area)
importFrom(ggplot2,geom_bar)
importFrom(ggplot2,geom_line)
importFrom(ggplot2,ggtitle)
+importFrom(ggplot2,theme_light)
+importFrom(ggplot2,xlab)
+importFrom(ggplot2,ylab)
importFrom(graphics,abline)
importFrom(graphics,axis)
-importFrom(graphics,box)
-importFrom(graphics,grid)
importFrom(graphics,hist)
importFrom(graphics,lines)
-importFrom(graphics,mtext)
-importFrom(graphics,par)
importFrom(graphics,plot)
importFrom(graphics,polygon)
importFrom(lifecycle,deprecated)
@@ -56,3 +56,4 @@ importFrom(stats,optimize)
importFrom(stats,pbeta)
importFrom(stats,rbinom)
importFrom(stats,uniroot)
+importFrom(tibble,remove_rownames)
diff --git a/R/_snaps/plotDecision/plot-of-probability-of-difference-and-respective-go-and-stop-probabilities.svg b/R/_snaps/plotDecision/plot-of-probability-of-difference-and-respective-go-and-stop-probabilities.svg
new file mode 100644
index 00000000..a0582785
--- /dev/null
+++ b/R/_snaps/plotDecision/plot-of-probability-of-difference-and-respective-go-and-stop-probabilities.svg
@@ -0,0 +1,86 @@
+
+
diff --git a/R/plotBeta.R b/R/plotBeta.R
index 24f3bde6..a4415aeb 100644
--- a/R/plotBeta.R
+++ b/R/plotBeta.R
@@ -80,8 +80,8 @@ plotBetaDiff <- function(parX, # parameters of control or SOC
temp <- sumBetaDiff(
parX = parX,
parY = parY,
- go_cut = go_cut,
- stop_cut = stop_cut
+ go_cut = go_cut, # in response rate
+ stop_cut = stop_cut # in response rate
)
go_label <- paste("P(Go) is", round(temp$go * 100, digits = 2), "%")
diff --git a/R/plotDecision.R b/R/plotDecision.R
index 1a3a9594..3348718f 100644
--- a/R/plotDecision.R
+++ b/R/plotDecision.R
@@ -1,137 +1,79 @@
#' Plot a summary plot corresponding to the sumTable output
#'
-#' This function will return a plot showing a curve of the prob of a meaningful improvement over estunated diff
-#' and a curve of the prob of a poor improvement over estunated diff
-#' @param data the output object of \code{\link{sumTable}}
-#' @param Pos_cut a cut off for the prob of a meaningful improvement
-#' @param Neg_cut a cut off for the prob of a poor improvement
-#' @return the \code{data} item which was imputed to the function
+#' This function will return a plot showing a curve of the prob of a meaningful improvement over estimated diff
+#' and a curve of the prob of a poor improvement over estimated diff
#'
-#' @importFrom graphics lines abline polygon plot par grid mtext box axis
+#' @typed data : data.frame
+#' sourced [`data.frame`] from [(sumTable())]
+#' @typed efficacious_prob : number
+#' a cut off for the probability of a meaningful improvement
+#' @typed futile_prob : number
+#' a cut off for the probability of a poor improvement
+#' @return [`ggplot`] object
+#'
+#' @importFrom ggplot2 geom_line geom_area ggtitle theme_light annotate xlab ylab
+#' @importFrom tibble remove_rownames
#'
#' @example examples/plotDecision.R
#' @export
#' @keywords graphics
-plotDecision <- function(data, Pos_cut, Neg_cut) {
- xticks <- seq(from = -50, to = 100, by = 10)
-
- x <- as.numeric(data[1, ]) # number of response;
-
- x.mode <- as.numeric(data[3, ]) # the response diff mode
-
- y <- as.numeric(data[6, ]) # The Prob of a meaningful improvement
-
- z <- as.numeric(data[7, ]) # The Prob of a not meaningful improvement
-
- # Look up decision area;
- ShadeData <- t(data)
-
- colnames(ShadeData)
-
- # Green area;
- G_area <- ShadeData[ShadeData[, "prob.go [%]"] > Pos_cut, ]
- # Red ares;
- R_area <- ShadeData[ShadeData[, "prob.nogo [%]"] > Neg_cut, ]
-
- graphics::par(mar = c(5, 4, 4, 1) + .1)
-
-
- graphics::plot(x.mode, y,
- type = "n", xlim = range(x.mode), bty = "n", ylab = "Probability (%)", xaxt = "n", xaxs = "i", yaxs = "i",
- xlab = expression(paste("Estimated diff.", sep = "")), ylim = c(0, 100), panel.first = grid()
+plotDecision <- function(data, efficacious_prob, futile_prob) {
+ assert_data_frame(data, any.missing = FALSE)
+ assert_number(efficacious_prob, finite = TRUE)
+ assert_number(futile_prob, finite = TRUE)
+
+ data <- data.frame(t(data))
+
+ data <- tibble::remove_rownames(data)
+
+ colnames(data) <- c(
+ "responders",
+ "obs",
+ "mode",
+ "ci_lower",
+ "ci_upper",
+ "prob_go",
+ "prob_stop"
)
+ go_shade <- data[data$prob_go > efficacious_prob, ]
+ stop_shade <- data[data$prob_stop > futile_prob, ]
- # find the interaction;
-
-
- # Green area;
- aboveG <- ShadeData[, "prob.go [%]"] > Pos_cut
- # Red ares;
- aboveR <- ShadeData[, "prob.nogo [%]"] > Neg_cut
-
- # Points always intersect when above=TRUE, then FALSE or reverse
- intersect.pointsG <- which(diff(aboveG) != 0)
- intersect.pointsR <- which(diff(aboveR) != 0)
- # Find the slopes for each line segment.
- x1.slopesG <- (ShadeData[intersect.pointsG + 1, "prob.go [%]"] - ShadeData[intersect.pointsG, "prob.go [%]"]) /
- (ShadeData[intersect.pointsG + 1, "mode [%]"] - ShadeData[intersect.pointsG, "mode [%]"])
- x1.slopesR <- (ShadeData[intersect.pointsR + 1, "prob.nogo [%]"] - ShadeData[intersect.pointsR, "prob.nogo [%]"]) /
- (ShadeData[intersect.pointsR + 1, "mode [%]"] - ShadeData[intersect.pointsR, "mode [%]"])
-
- x2.slopes <- 0
- # Find the intersection for each segment.
- x.pointsG <- ShadeData[intersect.pointsG, "mode [%]"] +
- ((Pos_cut - ShadeData[intersect.pointsG, "prob.go [%]"]) / (x1.slopesG))
- y.pointsG <- Pos_cut
-
- x.pointsR <- ShadeData[intersect.pointsR, "mode [%]"] +
- ((Neg_cut - ShadeData[intersect.pointsR, "prob.nogo [%]"]) / (x1.slopesR))
- y.pointsR <- Neg_cut
-
-
- graphics::polygon(c(R_area[, "mode [%]"], x.pointsR, x.pointsR, rev(R_area[, "mode [%]"])),
- c(rep(0, dim(R_area)[1] + 1), y.pointsR, rev(R_area[, "prob.nogo [%]"])),
- col = "red"
- )
-
- graphics::mtext(
- paste(
- "Est. Diff=",
- round(x.pointsR),
- "%, Prob.nogo=",
- round(y.pointsR),
- "%",
- sep = ""
- ),
- side = 3,
- line = 2
+ annotation_go <- paste0(
+ "Probability of Go is ", efficacious_prob, "% when difference is at least ",
+ min(data$mode[data$prob_go > efficacious_prob]), "%"
)
-
- graphics::polygon(
- c(
- x.pointsG, G_area[, "mode [%]"],
- rev(G_area[, "mode [%]"]), x.pointsG
- ),
- c(
- rep(0, dim(G_area)[1] + 1),
- rev(G_area[, "prob.go [%]"]), y.pointsG
- ),
- col = "green"
- ) # meaningful part;
-
- graphics::mtext(
- paste(
- "Est. Diff=",
- round(x.pointsG),
- "%,Prob. go=",
- round(y.pointsG),
- "%",
- sep = ""
- ),
- side = 3,
- line = 1
+ annotation_stop <- paste0(
+ "Probability of Stop is ", futile_prob, "% when difference is at most ",
+ max(data$mode[data$prob_stop > futile_prob]), "%"
)
- graphics::lines(x.mode, y, col = "green", lwd = 3, type = "l") # Plot PDF of beta(R,NR);
-
- graphics::lines(x.mode, z, col = "red", lwd = 3, type = "l")
-
-
-
- if (Pos_cut == Neg_cut) {
- graphics::abline(h = Pos_cut, col = "black", lwd = 2)
- }
-
- graphics::box()
-
- LablePoint2 <- unique(sort(c(
- ceiling(min(x.mode) * 10) / 10,
- xticks, floor(max(x.mode) * 10) / 10
- ))) ## Can be modified
-
- graphics::axis(1, at = LablePoint2, labels = paste(LablePoint2, "%", sep = ""), las = 1, lwd = 2, cex.axis = 1)
-
- data
+ ggplot2::ggplot(data) +
+ ggplot2::geom_line(
+ ggplot2::aes(x = mode, y = prob_go),
+ linewidth = 1.5, colour = "#009E73"
+ ) +
+ ggplot2::theme_light() +
+ ggplot2::scale_x_continuous(breaks = seq(from = 0, to = round(max(data$mode), digits = 1), by = 5)) +
+ ggplot2::geom_area(
+ data = go_shade,
+ mapping = ggplot2::aes(x = mode, y = prob_go),
+ fill = "#009E73"
+ ) +
+ ggplot2::geom_line(
+ data = data,
+ mapping = ggplot2::aes(x = mode, y = prob_stop),
+ linewidth = 1.5, colour = "#FF0046"
+ ) +
+ ggplot2::geom_area(
+ data = stop_shade,
+ mapping = ggplot2::aes(x = mode, y = prob_stop),
+ fill = "#FF0046"
+ ) +
+ ggplot2::ggtitle("Probability of Difference and respective Go and Stop probabilities.") +
+ ggplot2::xlab("Difference between treatment in Response Rate (%)") +
+ ggplot2::ylab("Probability (%)") +
+ ggplot2::annotate("text", x = mean(data$mode), y = 90, label = annotation_go) +
+ ggplot2::annotate("text", x = mean(data$mode), y = 85, label = annotation_stop)
}
diff --git a/R/plotOc.R b/R/plotOc.R
index 316b1313..05ac1a10 100644
--- a/R/plotOc.R
+++ b/R/plotOc.R
@@ -48,7 +48,7 @@ h_get_dataframe_oc <- function(decision, all_sizes, all_looks) {
#' @inheritParams h_get_dataframe_oc
#' @typed wiggle_status : flag
#' from `wiggle` flag in object.
-#' @return ggplot object
+#' @return [`ggplot`] object
#'
#' @example examples/plotOc.R
#'
@@ -67,7 +67,7 @@ plotOc <- function(decision, all_sizes, all_looks, wiggle_status) {
all_looks = all_looks
)
barplot <-
- ggplot2::ggplot(df, ggplot2::aes(fill = decision, x = look, y = prop)) +
+ ggplot2::ggplot(df, ggplot2::aes(fill = decision, x = all_looks, y = prop)) +
ggplot2::geom_bar(position = "dodge", stat = "identity") +
ggplot2::ggtitle(
"Results from simulation : \nProportion of Go/Stop/Grey zone decisions per interim/final analysis"
diff --git a/R/sumbetadiff.R b/R/sumBetaDiff.R
similarity index 78%
rename from R/sumbetadiff.R
rename to R/sumBetaDiff.R
index e1899d84..4fd931df 100644
--- a/R/sumbetadiff.R
+++ b/R/sumBetaDiff.R
@@ -15,15 +15,28 @@
#'
#' @importFrom stats optimize integrate
#'
-#' @example examples/sumbetadiff.R
+#' @example examples/sumBetaDiff.R
#' @export
-sumBetaDiff <- function(parX, # Treatment group's parameters
- parY, # Control group's parameters
- ci_level = 0.9,
- go_cut,
- stop_cut) {
- assert_numeric(parY, len = 2, lower = .Machine$double.xmin, any.missing = FALSE, finite = TRUE)
- assert_numeric(parX, len = 2, lower = .Machine$double.xmin, any.missing = FALSE, finite = TRUE)
+sumBetaDiff <- function(
+ parX, # Treatment group's parameters
+ parY, # Control group's parameters
+ ci_level = 0.9,
+ go_cut,
+ stop_cut) {
+ assert_numeric(
+ parY,
+ len = 2,
+ lower = .Machine$double.xmin,
+ any.missing = FALSE,
+ finite = TRUE
+ )
+ assert_numeric(
+ parX,
+ len = 2,
+ lower = .Machine$double.xmin,
+ any.missing = FALSE,
+ finite = TRUE
+ )
assert_number(ci_level, finite = TRUE)
assert_number(go_cut, finite = TRUE)
assert_number(stop_cut, finite = TRUE)
@@ -38,17 +51,20 @@ sumBetaDiff <- function(parX, # Treatment group's parameters
maximum = TRUE
)$maximum
- lower <- qbetadiff( # to recover x when F(x) is at lower percentile
+ lower <- qbetadiff(
+ # to recover x when F(x) is at lower percentile
p = (1 - ci_level) / 2,
parY = parY,
parX = parX
)
- upper <- qbetadiff( # to recover x when F(x) is at upper percentile
+ upper <- qbetadiff(
+ # to recover x when F(x) is at upper percentile
p = (1 + ci_level) / 2,
parY = parY,
parX = parX
)
+
# Prob for Go:
prob_go <- stats::integrate(
f = dbetadiff,
@@ -81,7 +97,8 @@ sumBetaDiff <- function(parX, # Treatment group's parameters
silent = TRUE
)
# if there were any errors, fall back to Monte Carlo estimation
- if (inherits(result, "try-error")) { # try-error is a class
+ if (inherits(result, "try-error")) {
+ # try-error is a class
samples <- stats::rbeta(n = 2e6, parY[1], parY[2]) -
rbeta(n = 2e6, parX[1], parX[2])
diff --git a/R/sumTable.R b/R/sumTable.R
index 24fd35dd..dfa694e6 100644
--- a/R/sumTable.R
+++ b/R/sumTable.R
@@ -10,6 +10,8 @@
#'
#' @return A vector with the results.
#'
+#' @importFrom phase1b sumBetaDiff
+#'
#' @example examples/sumTable.R
#' @export
sumTable <- function(x,
diff --git a/README.rmd b/README.rmd
index 5f3e30d7..5436758b 100644
--- a/README.rmd
+++ b/README.rmd
@@ -23,7 +23,7 @@ The intended user is the early clinical trial statistician in the design and int
You can install the development version of `phase1b` from [GitHub](https://github.com/) with:
``` r
-devtools::install_github("https://github.com/Genentech/phase1b/", force = TRUE)
+# devtools::install_github("https://github.com/Genentech/phase1b/", force = TRUE)
library(phase1b)
```
diff --git a/examples/plotDecision.R b/examples/plotDecision.R
index a3d54119..063da71c 100644
--- a/examples/plotDecision.R
+++ b/examples/plotDecision.R
@@ -1,22 +1,28 @@
-# sumTable ----
-sumTable(
- x = 10,
- n = 20,
- parX = c(1, 1),
- go_cut = 0.8,
- stop_cut = 0.4
+summaries <- do.call(
+ cbind,
+ lapply(c(0:8),
+ sumTable,
+ n = 25,
+ parX = c(1, 52),
+ go_cut = 0.2,
+ stop_cut = 0.05
+ )
)
-# plotting more results
+plotDecision(summaries, efficacious_prob = 60, futile_prob = 60)
+
+# plotting different criteria
summaries <- do.call(
cbind,
lapply(c(0:8),
sumTable,
n = 25,
parX = c(1, 52),
- go_cut = 0.6,
- stop_cut = 0.2
+ # density when P( diff > 20% | B(1, 52) for control and B(0.5, 0.5) for treatment) :
+ go_cut = 0.2,
+ # density when P( diff < 10% | B(1, 52) for control and B(0.5, 0.5) for treatment) :
+ stop_cut = 0.1
)
)
-# plotDecision(summaries, Pos_cut = 60, Neg_cut = 60)
+plotDecision(summaries, efficacious_prob = 60, futile_prob = 80)
diff --git a/examples/sumTable.R b/examples/sumTable.R
index 64e9b5c4..9db595bb 100644
--- a/examples/sumTable.R
+++ b/examples/sumTable.R
@@ -14,7 +14,10 @@ summaries <- do.call(
sumTable,
n = 25,
parX = c(1, 52),
+ parY = c(0.5, 0.5), # default
+ # density when P( diff > 20% | B(1, 52) for control and B(0.5, 0.5) for treatment) :
go_cut = 0.2,
+ # density when P( diff < 5% | B(1, 52) for control and B(0.5, 0.5) for treatment) :
stop_cut = 0.05
)
)
diff --git a/inst/WORDLIST b/inst/WORDLIST
index 79ae2b4f..26553f93 100644
--- a/inst/WORDLIST
+++ b/inst/WORDLIST
@@ -218,7 +218,6 @@ simplifiedWeightedBayestwo
specialised
springer
Springer
-sumbetadiff
summerize
summerizes
sumTable
diff --git a/man/plotDecision.Rd b/man/plotDecision.Rd
index 0e90569c..85e461dd 100644
--- a/man/plotDecision.Rd
+++ b/man/plotDecision.Rd
@@ -4,44 +4,50 @@
\alias{plotDecision}
\title{Plot a summary plot corresponding to the sumTable output}
\usage{
-plotDecision(data, Pos_cut, Neg_cut)
+plotDecision(data, efficacious_prob, futile_prob)
}
\arguments{
-\item{data}{the output object of \code{\link{sumTable}}}
+\item{data}{(\code{data.frame}):\cr sourced \code{\link{data.frame}} from \link{(sumTable())}}
-\item{Pos_cut}{a cut off for the prob of a meaningful improvement}
+\item{efficacious_prob}{(\code{number}):\cr a cut off for the probability of a meaningful improvement}
-\item{Neg_cut}{a cut off for the prob of a poor improvement}
+\item{futile_prob}{(\code{number}):\cr a cut off for the probability of a poor improvement}
}
\value{
-the \code{data} item which was imputed to the function
+\code{\link{ggplot}} object
}
\description{
-This function will return a plot showing a curve of the prob of a meaningful improvement over estunated diff
-and a curve of the prob of a poor improvement over estunated diff
+This function will return a plot showing a curve of the prob of a meaningful improvement over estimated diff
+and a curve of the prob of a poor improvement over estimated diff
}
\examples{
-# sumTable ----
-sumTable(
- x = 10,
- n = 20,
- parX = c(1, 1),
- go_cut = 0.8,
- stop_cut = 0.4
+summaries <- do.call(
+ cbind,
+ lapply(c(0:8),
+ sumTable,
+ n = 25,
+ parX = c(1, 52),
+ go_cut = 0.2,
+ stop_cut = 0.05
+ )
)
-# plotting more results
+plotDecision(summaries, efficacious_prob = 60, futile_prob = 60)
+
+# plotting different criteria
summaries <- do.call(
cbind,
lapply(c(0:8),
sumTable,
n = 25,
parX = c(1, 52),
- go_cut = 0.6,
- stop_cut = 0.2
+ # density when P( diff > 20\% | B(1, 52) for control and B(0.5, 0.5) for treatment) :
+ go_cut = 0.2,
+ # density when P( diff < 10\% | B(1, 52) for control and B(0.5, 0.5) for treatment) :
+ stop_cut = 0.1
)
)
-# plotDecision(summaries, Pos_cut = 60, Neg_cut = 60)
+plotDecision(summaries, efficacious_prob = 60, futile_prob = 80)
}
\keyword{graphics}
diff --git a/man/plotOc.Rd b/man/plotOc.Rd
index b54506e6..ec29e82d 100644
--- a/man/plotOc.Rd
+++ b/man/plotOc.Rd
@@ -17,7 +17,7 @@ Different to \code{all_sizes} which is after the adjustment, if made.}
\item{wiggle_status}{(\code{flag}):\cr from \code{wiggle} flag in object.}
}
\value{
-ggplot object
+\code{\link{ggplot}} object
}
\description{
Plots results from simulated results of :
diff --git a/man/sumBetaDiff.Rd b/man/sumBetaDiff.Rd
index 474bb5ea..5cc1ae5e 100644
--- a/man/sumBetaDiff.Rd
+++ b/man/sumBetaDiff.Rd
@@ -1,5 +1,5 @@
% Generated by roxygen2: do not edit by hand
-% Please edit documentation in R/sumbetadiff.R
+% Please edit documentation in R/sumBetaDiff.R
\name{sumBetaDiff}
\alias{sumBetaDiff}
\title{Mode and Credible Interval Calculation for The Difference between Two Beta Distributions}
@@ -27,14 +27,3 @@ along with the \code{go} and \code{stop} probabilities.
A function to summarize the characters of a betadiff distribution \code{\link[=dbetadiff]{dbetadiff()}}.
May require use of random sample generator to calculate, use \code{\link[=set.seed]{set.seed()}} to reproduce results.
}
-\examples{
-parX <- c(1, 52) # Control group's parameters
-parY <- c(5.5, 20.5) # Treatment group's parameters
-sumBetaDiff(
- parX = parX,
- parY = parY,
- ci_level = 0.9,
- go_cut = 0.6,
- stop_cut = 0.2
-)
-}
diff --git a/man/sumTable.Rd b/man/sumTable.Rd
index 483f9179..b801bd20 100644
--- a/man/sumTable.Rd
+++ b/man/sumTable.Rd
@@ -45,7 +45,10 @@ summaries <- do.call(
sumTable,
n = 25,
parX = c(1, 52),
+ parY = c(0.5, 0.5), # default
+ # density when P( diff > 20\% | B(1, 52) for control and B(0.5, 0.5) for treatment) :
go_cut = 0.2,
+ # density when P( diff < 5\% | B(1, 52) for control and B(0.5, 0.5) for treatment) :
stop_cut = 0.05
)
)
diff --git a/tests/testthat/_snaps/plotBetaDiff/plot-of-distibution-of-difference-of-two-arms-with-beta-mixture.svg b/tests/testthat/_snaps/plotBetaDiff/plot-of-distibution-of-difference-of-two-arms-with-beta-mixture.svg
index a9c300df..102bf2b5 100644
--- a/tests/testthat/_snaps/plotBetaDiff/plot-of-distibution-of-difference-of-two-arms-with-beta-mixture.svg
+++ b/tests/testthat/_snaps/plotBetaDiff/plot-of-distibution-of-difference-of-two-arms-with-beta-mixture.svg
@@ -32,7 +32,7 @@
-P(Stop) is 59.5 %
+P(Stop) is 59.49 %
P(Go) is 24.5 %
@@ -60,6 +60,6 @@
(
x
)
-According to Beta difference density P(Go) is 24.5 % and P(Stop) is 59.5 %
+According to Beta difference density P(Go) is 24.5 % and P(Stop) is 59.49 %
diff --git a/tests/testthat/_snaps/plotDecision/plot-of-Probability-of-Difference-and-respective-Go-and-Stop-probabilities.svg b/tests/testthat/_snaps/plotDecision/plot-of-Probability-of-Difference-and-respective-Go-and-Stop-probabilities.svg
new file mode 100644
index 00000000..ec7af51f
--- /dev/null
+++ b/tests/testthat/_snaps/plotDecision/plot-of-Probability-of-Difference-and-respective-Go-and-Stop-probabilities.svg
@@ -0,0 +1,86 @@
+
+
diff --git a/tests/testthat/_snaps/plotOc/plot-of-simulation-result-for-single-arm-posterior-predictive-probability.svg b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-for-single-arm-posterior-predictive-probability.svg
index 482d2b5d..f9a4369a 100644
--- a/tests/testthat/_snaps/plotOc/plot-of-simulation-result-for-single-arm-posterior-predictive-probability.svg
+++ b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-for-single-arm-posterior-predictive-probability.svg
@@ -31,17 +31,23 @@
+
+
+
+
-
+
+
-
-
-
-
-
+
+
+
+
+
+
0.00
@@ -52,12 +58,16 @@
-
+
+
-
-10
-20
-NA
+
+
+5
+10
+15
+20
+25
look (n)
percentage
diff --git a/tests/testthat/_snaps/plotOc/plot-of-simulation-result-for-single-arm-posterior-probability.svg b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-for-single-arm-posterior-probability.svg
index cfdca283..8874241e 100644
--- a/tests/testthat/_snaps/plotOc/plot-of-simulation-result-for-single-arm-posterior-probability.svg
+++ b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-for-single-arm-posterior-probability.svg
@@ -32,24 +32,27 @@
+
+
+
+
-
-
-
-
-
-
-
-
-
-
-
-
-
+
+
+
+
+
+
+
+
+
+
+
+
0.0
@@ -62,14 +65,12 @@
-
-
-
-
-10
-20
-30
-NA
+
+
+
+10
+20
+30
look (n)
percentage
diff --git a/tests/testthat/_snaps/plotOc/plot-of-simulation-result-with-relativedelta-for-posterior-predictive-probability.svg b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-with-relativedelta-for-posterior-predictive-probability.svg
index c372bec8..be8037be 100644
--- a/tests/testthat/_snaps/plotOc/plot-of-simulation-result-with-relativedelta-for-posterior-predictive-probability.svg
+++ b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-with-relativedelta-for-posterior-predictive-probability.svg
@@ -31,17 +31,24 @@
+
+
+
+
-
-
-
-
-
-
+
+
+
+
+
+
+
+
+
0.0
@@ -54,10 +61,16 @@
-
-
-20
-30
+
+
+
+
+
+15
+20
+25
+30
+35
look (n)
percentage
diff --git a/tests/testthat/_snaps/plotOc/plot-of-simulation-result-without-relativedelta-for-posterior-predictive-probability.svg b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-without-relativedelta-for-posterior-predictive-probability.svg
index ae0e813e..55d61b5e 100644
--- a/tests/testthat/_snaps/plotOc/plot-of-simulation-result-without-relativedelta-for-posterior-predictive-probability.svg
+++ b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-without-relativedelta-for-posterior-predictive-probability.svg
@@ -30,15 +30,22 @@
+
+
+
+
-
-
-
-
-
-
+
+
+
+
+
+
+
+
+
0.0
@@ -47,10 +54,16 @@
-
-
-20
-30
+
+
+
+
+
+15
+20
+25
+30
+35
look (n)
percentage
diff --git a/tests/testthat/test-plotDecision.R b/tests/testthat/test-plotDecision.R
new file mode 100644
index 00000000..feac2273
--- /dev/null
+++ b/tests/testthat/test-plotDecision.R
@@ -0,0 +1,23 @@
+# plotDecision ----
+test_that("plotDecision gives a correct result", {
+ summaries <- do.call(
+ cbind,
+ lapply(c(0:8),
+ sumTable,
+ n = 25,
+ parX = c(1, 52),
+ go_cut = 0.2,
+ stop_cut = 0.05
+ )
+ )
+ result <- plotDecision(summaries, efficacious_prob = 60, futile_prob = 60)
+ testthat::expect_equal(result$data$responders, c(0, 1, 2, 3, 4, 5, 6, 7, 8))
+ expect_numeric(result$data$obs)
+ expect_numeric(result$data$mode)
+ expect_numeric(result$data$ci_lower)
+ expect_numeric(result$data$ci_upper)
+ expect_numeric(result$data$prob_go)
+ expect_numeric(result$data$prob_stop)
+ expect_identical(result$labels$title, "Probability of Difference and respective Go and Stop probabilities.")
+ vdiffr::expect_doppelganger("plot of Probability of Difference and respective Go and Stop probabilities", result)
+})
diff --git a/tests/testthat/test-plotOc.R b/tests/testthat/test-plotOc.R
index 15368569..344add1c 100644
--- a/tests/testthat/test-plotOc.R
+++ b/tests/testthat/test-plotOc.R
@@ -266,11 +266,11 @@ test_that("plotOc gives expected results for `ocPostprob` and `ocPredprob`", {
all_looks = res5$Looks,
wiggle_status = res5$params$wiggle
)
- vdiffr::expect_doppelganger(
+ vdiffr::expect_doppelganger( ##
title = "plot of simulation result for single arm posterior probability",
fig = result1
)
- vdiffr::expect_doppelganger(
+ vdiffr::expect_doppelganger( ##
title = "plot of simulation result for single arm posterior predictive probability",
fig = result2
)
@@ -325,11 +325,11 @@ test_that("plotOc gives expected results for `ocPredprobDist` with different rel
all_looks = res8$Looks,
wiggle_status = res8$params$wiggle
)
- vdiffr::expect_doppelganger(
+ vdiffr::expect_doppelganger( ##
title = "Plot of simulation result without relativeDelta for posterior predictive probability",
fig = result1
)
- vdiffr::expect_doppelganger(
+ vdiffr::expect_doppelganger( ##
title = "Plot of simulation result with relativeDelta for posterior predictive probability",
fig = result2
)
diff --git a/tests/testthat/test-sumbetadiff.R b/tests/testthat/test-sumbetadiff.R
index 1b2e339a..53b17648 100644
--- a/tests/testthat/test-sumbetadiff.R
+++ b/tests/testthat/test-sumbetadiff.R
@@ -1,5 +1,5 @@
# sumBetaDiff ----
-test_that("sumbetadiff works as expected", {
+test_that("sumBetaDiff works as expected", {
parX <- c(1, 52) # Control group's parameters
parY <- c(5.5, 20.5) # Treatment group's parameters
result <- sumBetaDiff(
@@ -20,7 +20,7 @@ test_that("sumbetadiff works as expected", {
)
})
-test_that("sumbetadiff gives a error when at least one alpha = 0", {
+test_that("sumBetaDiff gives a error when at least one alpha = 0", {
parX <- c(0, 10)
parY <- c(5.5, 20.5)
expect_error(sumBetaDiff(
diff --git a/tests/vdiffr.Rout.fail b/tests/vdiffr.Rout.fail
index 6e982dc9..e700615d 100644
--- a/tests/vdiffr.Rout.fail
+++ b/tests/vdiffr.Rout.fail
@@ -7765,3 +7765,17076 @@ Failed doppelganger: plot-of-simulation-result-for-single-arm-posterior-probabil
>
>
+
+Failed doppelganger: plot-of-simulation-result-for-single-arm-posterior-probability (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-for-single-arm-posterior-probability.svg)
+
+< before
+> after
+@@ 33,4 / 33,8 @@
+
+
+>
+>
+>
+>
+
+
+@@ 38,17 / 42,16 @@
+
+
+<
+<
+<
+>
+<
+>
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+
+
+@@ 63,12 / 66,10 @@
+
+
+<
+<
+<
+>
+<
+>
+>
+< 10
+> 10
+< 20
+> 20
+< 30
+> 30
+< NA
+ look (n
+ )
+ percentage
+
+
+Failed doppelganger: plot-of-simulation-result-for-single-arm-posterior-predictive-probability (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-for-single-arm-posterior-predictive-probability.svg)
+
+< before
+> after
+@@ 32,15 / 32,21 @@
+
+
+>
+>
+>
+>
+
+
+
+
+<
+>
+>
+
+<
+>
+>
+<
+>
+<
+>
+<
+>
+<
+>
+
+
+@@ 53,10 / 59,14 @@
+
+
+<
+>
+>
+
+<
+>
+< 10
+< 20
+>
+> 5
+> 10
+> 15
+> 20
+< NA
+> 25
+ look (n
+ )
+ percentage
+
+
+Failed doppelganger: plot-of-simulation-result-without-relativedelta-for-posterior-predictive-probability (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-without-relativedelta-for-posterior-predictive-probability.svg)
+
+< before
+> after
+@@ 31,13 / 31,20 @@
+
+
+>
+>
+>
+>
+
+
+
+<
+>
+<
+>
+>
+>
+>
+<
+>
+<
+>
+<
+>
+<
+>
+
+
+@@ 48,8 / 55,14 @@
+
+
+<
+>
+<
+< 20
+< 30
+>
+>
+>
+>
+> 15
+> 20
+> 25
+> 30
+> 35
+ look (n
+ )
+ percentage
+
+
+Failed doppelganger: plot-of-simulation-result-with-relativedelta-for-posterior-predictive-probability (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-with-relativedelta-for-posterior-predictive-probability.svg)
+
+< before
+> after
+@@ 32,4 / 32,8 @@
+
+
+>
+>
+>
+>
+
+
+@@ 37,10 / 41,13 @@
+
+
+<
+>
+<
+>
+>
+>
+>
+<
+>
+<
+>
+<
+>
+<
+>
+
+
+@@ 55,8 / 62,14 @@
+
+
+<
+>
+<
+< 20
+< 30
+>
+>
+>
+>
+> 15
+> 20
+> 25
+> 30
+> 35
+ look (n
+ )
+ percentage
+
+
+Failed doppelganger: plot-of-probability-of-difference-and-respective-go-and-stop-probabilities (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotDecision/plot-of-probability-of-difference-and-respective-go-and-stop-probabilities.svg)
+
+< before
+> after
+@@ 1,4 / 1,4 @@
+
+<
+
+@@ 63,12 / 66,10 @@
+
+
+<
+<
+<
+>
+<
+>
+>
+< 10
+> 10
+< 20
+> 20
+< 30
+> 30
+< NA
+ look (n
+ )
+ percentage
+
+
+Failed doppelganger: plot-of-simulation-result-for-single-arm-posterior-predictive-probability (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-for-single-arm-posterior-predictive-probability.svg)
+
+< before
+> after
+@@ 32,15 / 32,21 @@
+
+
+>
+>
+>
+>
+
+
+
+
+<
+>
+>
+
+<
+>
+>
+<
+>
+<
+>
+<
+>
+<
+>
+
+
+@@ 53,10 / 59,14 @@
+
+
+<
+>
+>
+
+<
+>
+< 10
+< 20
+>
+> 5
+> 10
+> 15
+> 20
+< NA
+> 25
+ look (n
+ )
+ percentage
+
+
+Failed doppelganger: plot-of-simulation-result-without-relativedelta-for-posterior-predictive-probability (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-without-relativedelta-for-posterior-predictive-probability.svg)
+
+< before
+> after
+@@ 31,13 / 31,20 @@
+
+
+>
+>
+>
+>
+
+
+
+<
+>
+<
+>
+>
+>
+>
+<
+>
+<
+>
+<
+>
+<
+>
+
+
+@@ 48,8 / 55,14 @@
+
+
+<
+>
+<
+< 20
+< 30
+>
+>
+>
+>
+> 15
+> 20
+> 25
+> 30
+> 35
+ look (n
+ )
+ percentage
+
+
+Failed doppelganger: plot-of-simulation-result-with-relativedelta-for-posterior-predictive-probability (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-with-relativedelta-for-posterior-predictive-probability.svg)
+
+< before
+> after
+@@ 32,4 / 32,8 @@
+
+
+>
+>
+>
+>
+
+
+@@ 37,10 / 41,13 @@
+
+
+<
+>
+<
+>
+>
+>
+>
+<
+>
+<
+>
+<
+>
+<
+>
+
+
+@@ 55,8 / 62,14 @@
+
+
+<
+>
+<
+< 20
+< 30
+>
+>
+>
+>
+> 15
+> 20
+> 25
+> 30
+> 35
+ look (n
+ )
+ percentage
+
+
+Failed doppelganger: plot-of-probability-of-difference-and-respective-go-and-stop-probabilities (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotDecision/plot-of-probability-of-difference-and-respective-go-and-stop-probabilities.svg)
+
+< before
+> after
+@@ 1,4 / 1,4 @@
+
+<
+>
+
+
+
+
+
+<
+>
+<
+>
+
+
+<
+>
+<
+>
+
+
+<
+>
+<
+>
+
+
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+< Prob
+: ability of Go is 60% when difference is at least 29.47%
+> Probabi
+: lity of Go is 60% when difference is at least 21.18%
+< Prob
+: ability of Stop is 60% when difference is at most 1.02%
+> Probabi
+: lity of Stop is 60% when difference is at most 1.02%
+<
+>
+
+<
+>
+< 0
+> 0
+< 25
+> 25
+< 50
+> 50
+< 75
+> 75
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+< 0
+> 0
+< 5
+> 5
+< 10
+> 10
+< 15
+> 15
+< 20
+> 20
+< 25
+> 25
+< Dif
+: ference between treatment in Response Rate (%)
+> Differ
+: ence between treatment in Response Rate (%)
+< Probability (%)
+> Probability (%)
+< Probability of Difference
+: and respective Go and Stop probabilities.
+> Probability of Difference and
+: respective Go and Stop probabilities.
+
+
+
+
+Failed doppelganger: plot-of-probability-of-difference-and-respective-go-and-stop-probabilities (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotDecision/plot-of-probability-of-difference-and-respective-go-and-stop-probabilities.svg)
+
+< before
+> after
+@@ 1,4 / 1,4 @@
+
+<
+>
+
+
+
+
+
+<
+>
+<
+>
+
+
+<
+>
+<
+>
+
+
+<
+>
+<
+>
+
+
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+< Prob
+: ability of Go is 60% when difference is at least 29.47%
+> Probabi
+: lity of Go is 60% when difference is at least 21.18%
+< Prob
+: ability of Stop is 60% when difference is at most 1.02%
+> Probabi
+: lity of Stop is 60% when difference is at most 1.02%
+<
+>
+
+<
+>
+< 0
+> 0
+< 25
+> 25
+< 50
+> 50
+< 75
+> 75
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+< 0
+> 0
+< 5
+> 5
+< 10
+> 10
+< 15
+> 15
+< 20
+> 20
+< 25
+> 25
+< Dif
+: ference between treatment in Response Rate (%)
+> Differ
+: ence between treatment in Response Rate (%)
+< Probability (%)
+> Probability (%)
+< Probability of Difference
+: and respective Go and Stop probabilities.
+> Probability of Difference and
+: respective Go and Stop probabilities.
+
+
+
+
+Failed doppelganger: plot-of-distibution-of-difference-of-two-arms-with-beta-mixture (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotBetaDiff/plot-of-distibution-of-difference-of-two-arms-with-beta-mixture.svg)
+
+< before
+> after
+@@ 33,5 / 33,5 @@
+
+
+< P(Stop) is 59.5 %
+> P(Stop) is 59.49 %
+ P(Go) is 24.5 %
+
+@@ 61,5 / 61,5 @@
+ x
+ text>
+ )
+ text>
+< According to Beta difference
+: density P(Go) is 24.5 % and P(Stop) is 59.5 %
+> According to Beta difference
+: density P(Go) is 24.5 % and P(Stop) is 59.49 %
+
+
+
+
+Failed doppelganger: plot-of-distibution-of-difference-of-two-arms (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotBetaDiff/plot-of-distibution-of-difference-of-two-arms.svg)
+
+< before
+> after
+@@ 1,4 / 1,4 @@
+
+<
+>
+
+
+@@ 17,75 / 14,56 @@
+
+
+<
+>
+<
+>
+
+
+<
+>
+<
+>
+
+
+<
+>
+<
+>
+
+
+<
+>
+<
+>
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+>
+>
+>
+>
+>
+< P(Stop) is 11.72 %
+> P(Stop) is 11.72 %
+< P(Go) is 10.12 %
+> P(Go) is 10.12 %
+>
+
+<
+>
+< 0
+> 0
+< 1
+> 1
+< 2
+> 2
+< 3
+> 3
+< 4
+> 4
+< 5
+> 5
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+< -1.0
+> -1.0
+< -0.5
+> -0.5
+< 0.0
+> 0.0
+< 0.5
+> 0.5
+< 1.0
+> 1.0
+< Dif
+: ference between treatment
+> Differ
+: ence between treatment
+<
+: f
+> f
+: text>
+< (
+> (
+: text>
+<
+: x
+> x
+: text>
+< )
+> )
+: text>
+< According to Beta differen
+: ce density P(Go) is 10.12 % and P(Stop) is 11.72 %
+> According to Beta difference
+: density P(Go) is 10.12 % and P(Stop) is 11.72 %
+
+
+
+
+Failed doppelganger: plot-of-distibution-of-difference-of-two-arms-with-beta-mixture (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotBetaDiff/plot-of-distibution-of-difference-of-two-arms-with-beta-mixture.svg)
+
+< before
+> after
+@@ 1,4 / 1,4 @@
+
+<
+>
+
+
+
+
+
+<
+>
+<
+>
+
+
+<
+>
+<
+>
+
+
+<
+>
+<
+>
+
+
+<
+>
+<
+>
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+>
+>
+>
+>
+>
+< P(Stop) is 11.72 %
+> P(Stop) is 59.49 %
+< P(Go) is 10.12 %
+> P(Go) is 24.5 %
+>
+
+<
+>
+< 0
+> 0
+< 1
+> 1
+< 2
+> 2
+< 3
+> 3
+< 4
+< 5
+<
+<
+<
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+>
+< -1.0
+> -1.0
+< -0.5
+> -0.5
+< 0.0
+> 0.0
+< 0.5
+> 0.5
+< 1.0
+> 1.0
+< Dif
+: ference between treatment
+> Differ
+: ence between treatment
+<
+: f
+> f
+: text>
+< (
+> (
+: text>
+<
+: x
+> x
+: text>
+< )
+> )
+: text>
+< According to Beta differen
+: ce density P(Go) is 10.12 % and P(Stop) is 11.72 %
+> According to Beta difference
+: density P(Go) is 24.5 % and P(Stop) is 59.49 %
+
+
+
+
+Failed doppelganger: plot-of-distibution-of-difference-of-two-arms (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotBetaDiff/plot-of-distibution-of-difference-of-two-arms.svg)
+
+< before
+> after
+@@ 1,4 / 1,4 @@
+
+<
+>
+
+
+@@ 17,75 / 14,56 @@
+
+
+<
+>
+<
+>
+
+
+<
+>
+<
+>
+
+
+<
+>
+<
+>
+
+
+<
+>
+<
+>
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+>
+>
+>
+>
+>
+< P(Stop) is 11.72 %
+> P(Stop) is 11.72 %
+< P(Go) is 10.12 %
+> P(Go) is 10.12 %
+>
+
+<
+>
+< 0
+> 0
+< 1
+> 1
+< 2
+> 2
+< 3
+> 3
+< 4
+> 4
+< 5
+> 5
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+< -1.0
+> -1.0
+< -0.5
+> -0.5
+< 0.0
+> 0.0
+< 0.5
+> 0.5
+< 1.0
+> 1.0
+< Dif
+: ference between treatment
+> Differ
+: ence between treatment
+<
+: f
+> f
+: text>
+< (
+> (
+: text>
+<
+: x
+> x
+: text>
+< )
+> )
+: text>
+< According to Beta differen
+: ce density P(Go) is 10.12 % and P(Stop) is 11.72 %
+> According to Beta difference
+: density P(Go) is 10.12 % and P(Stop) is 11.72 %
+
+
+
+
+Failed doppelganger: plot-of-distibution-of-difference-of-two-arms-with-beta-mixture (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotBetaDiff/plot-of-distibution-of-difference-of-two-arms-with-beta-mixture.svg)
+
+< before
+> after
+@@ 1,4 / 1,4 @@
+
+<
+>
+
+
+
+
+
+<
+>
+<
+>
+
+
+<
+>
+<
+>
+
+
+<
+>
+<
+>
+
+
+<
+>
+<
+>
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+<
+>
+>
+>
+>
+>
+< P(Stop) is 11.72 %
+> P(Stop) is 59.49 %
+< P(Go) is 10.12 %
+> P(Go) is 24.5 %
+>
+
+<
+>
+< 0
+> 0
+< 1
+> 1
+< 2
+> 2
+< 3
+> 3
+< 4
+< 5
+<
+<
+<
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+>
+< -1.0
+> -1.0
+< -0.5
+> -0.5
+< 0.0
+> 0.0
+< 0.5
+> 0.5
+< 1.0
+> 1.0
+< Dif
+: ference between treatment
+> Differ
+: ence between treatment
+<
+: f
+> f
+: text>
+< (
+> (
+: text>
+<
+: x
+> x
+: text>
+< )
+> )
+: text>
+< According to Beta differen
+: ce density P(Go) is 10.12 % and P(Stop) is 11.72 %
+> According to Beta difference
+: density P(Go) is 24.5 % and P(Stop) is 59.49 %
+
+
+
+
+Failed doppelganger: plot-of-simulation-result-for-single-arm-posterior-probability (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-for-single-arm-posterior-probability.svg)
+
+< before
+> after
+@@ 33,4 / 33,8 @@
+
+
+>
+>
+>
+>
+
+
+@@ 38,17 / 42,16 @@
+
+
+<
+<
+<
+>
+<
+>
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+<
+>
+
+
+@@ 63,12 / 66,10 @@
+
+
+<
+<
+<
+>
+<
+>
+>
+< 10
+> 10
+< 20
+> 20
+< 30
+> 30
+< NA
+ look (n
+ )
+ percentage
+
+
+Failed doppelganger: plot-of-simulation-result-for-single-arm-posterior-predictive-probability (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-for-single-arm-posterior-predictive-probability.svg)
+
+< before
+> after
+@@ 32,15 / 32,21 @@
+
+
+>
+>
+>
+>
+
+
+
+
+<
+>
+>
+
+<
+>
+>
+<
+>
+<
+>
+<
+>
+<
+>
+
+
+@@ 53,10 / 59,14 @@
+
+
+<
+>
+>
+
+<
+>
+< 10
+< 20
+>
+> 5
+> 10
+> 15
+> 20
+< NA
+> 25
+ look (n
+ )
+ percentage
+
+
+Failed doppelganger: plot-of-simulation-result-without-relativedelta-for-posterior-predictive-probability (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-without-relativedelta-for-posterior-predictive-probability.svg)
+
+< before
+> after
+@@ 31,13 / 31,20 @@
+
+
+>
+>
+>
+>
+
+
+
+<
+>
+<
+>
+>
+>
+>
+<
+>
+<
+>
+<
+>
+<
+>
+
+
+@@ 48,8 / 55,14 @@
+
+
+<
+>
+<
+< 20
+< 30
+>
+>
+>
+>
+> 15
+> 20
+> 25
+> 30
+> 35
+ look (n
+ )
+ percentage
+
+
+Failed doppelganger: plot-of-simulation-result-with-relativedelta-for-posterior-predictive-probability (/Users/audreyyeo/Documents/phase1b/phase1b/tests/testthat/_snaps/plotOc/plot-of-simulation-result-with-relativedelta-for-posterior-predictive-probability.svg)
+
+< before
+> after
+@@ 32,4 / 32,8 @@
+
+
+>
+>
+>
+>
+
+
+@@ 37,10 / 41,13 @@
+
+
+<
+>
+<
+>
+>
+>
+>
+<
+>
+<
+>
+<
+>
+<
+>
+
+
+@@ 55,8 / 62,14 @@
+
+
+<
+>
+<
+< 20
+< 30
+>
+>
+>
+>
+> 15
+> 20
+> 25
+> 30
+> 35
+ look (n
+ )
+ percentage
+
diff --git a/vignettes/introduction.Rmd b/vignettes/introduction.Rmd
index abad3b8d..db8d7c6a 100644
--- a/vignettes/introduction.Rmd
+++ b/vignettes/introduction.Rmd
@@ -142,7 +142,8 @@ function.
The first time you use `phase1b` on your own computer you will need to download
and install it, however, subsequent use will only require calling of the R-package.
```{r install-phase1b, eval=FALSE}
-install.packages("phase1b")
+library(devtools)
+devtools::install_github("https://github.com/Genentech/phase1b")
install.packages("ggplot2")
```
@@ -153,6 +154,8 @@ will have to load the R-package (assuming the R-package has been installed
following the instructions in the [Installation section](#installation) with the
following command:
```{r load}
+library(devtools)
+devtools::install_github("https://github.com/Genentech/phase1b")
library(phase1b)
library(ggplot2)
```
@@ -610,7 +613,7 @@ ex1_prior_caption <- paste(
)
```
-```{r ex1-prior, echo=TRUE, fig.cap = ex1_prior_caption}
+```{r fig:ex1-prior, echo=TRUE, fig.cap = ex1_prior_caption}
xx <- seq(0, 1, .001)
dens.control <- dbeta(xx, 75, 75) # Posterior of the control
dens.prior <- dbeta(xx, 5.75, 4.25) # Prior of the Phase 1b trial
@@ -827,7 +830,7 @@ ex1_betadiff_1_cap <- paste(
)
```
-```{r ex1:betadiff1, echo=TRUE, out.width="4in"}
+```{r fig:ex1:betadiff1, echo=TRUE, out.width="4in"}
parX <- c(75, 75)
parY <- c(5.75 + 55, 4.25 + 80 - 55)
xx <- seq(-0.5, 0.75, 0.001)