Problematic T/R-ratio… [Power / Sample Size]
❝ For example, if the pilot study data available for 14 subjects (Eg. T/R ratio is 84% & 90% CI is 79 to 89), I would like to know if we perform the pivotal study with the same test formulation in higher sample size (based on the intra CV), what would be the results? (Eg. in 36 subjects or 48 subjects).
❝ This will help us to take decision whether go/no go for the pivotal BE study.
If you believe (‼) that the CV and T/R-ratio will be exactly realized in the pivotal study, use the ‘carved in stone approach’ (for details see this article). Easy in the -package
PowerTOST
:library(PowerTOST)
m <- 14 # sample size of the pilot study
GMR <- 0.84 # observed T/R-ratio
lower <- 0.79 # lower 90% CL
upper <- 0.89 # upper 90% CL
tgt <- c(0.8, 0.9) # target (desired) powers of the pivotal study
design <- "2x2" # guess
CV <- signif(CI2CV(lower = lower, upper = upper, n = m), 3)
up2even <- function(x) 2 * (x %/% 2 + as.logical(x %% 2))
stoned1 <- sampleN.TOST(CV = CV, theta0 = GMR, design = design, targetpower = tgt[1],
print = FALSE)[["Sample size"]]
stoned2 <- sampleN.TOST(CV = CV, theta0 = GMR, design = design, targetpower = tgt[2],
print = FALSE)[["Sample size"]]
n <- seq(up2even(stoned1 * 0.80), up2even(stoned2 * 1.09), 2)
res <- data.frame(n = n, power = NA_real_, t1 = tgt[1], a1 = "", t2 = tgt[2], a2 = "")
for (j in seq_along(n)) {
res$power[j] <- signif(power.TOST(CV = CV, theta0 = GMR,
design = design, n = res$n[j]), 4)
if (n[j] == up2even(stoned1 * 0.80)) res$a1[j] <- "optimistic"
if (n[j] == stoned1) res$a1[j] <- "carved in stone"
if (n[j] == up2even(stoned1 * 1.09)) res$a1[j] <- "pessimistic"
if (n[j] == up2even(stoned2 * 0.80)) res$a2[j] <- "optimistic"
if (n[j] == stoned2) res$a2[j] <- "carved in stone"
if (n[j] == up2even(stoned2 * 1.09)) res$a2[j] <- "pessimistic"
}
names(res)[3:6] <- rep(c("target", "approach"), 2)
txt <- sprintf("Results for target powers of %.0f and %.0f%%:\n",
100 * tgt[1], 100 * tgt[2])
target <- 0.8 # for the following scripts
cat(txt); print(res, row.names = FALSE, right = FALSE)
Results for target powers of 80 and 90%:
n power target approach target approach
36 0.7419 0.8 optimistic 0.9
38 0.7626 0.8 0.9
40 0.7818 0.8 0.9
42 0.7997 0.8 0.9
44 0.8162 0.8 carved in stone 0.9
46 0.8315 0.8 0.9
48 0.8457 0.8 pessimistic 0.9 optimistic
50 0.8587 0.8 0.9
52 0.8708 0.8 0.9
54 0.8819 0.8 0.9
56 0.8921 0.8 0.9
58 0.9015 0.8 0.9 carved in stone
60 0.9102 0.8 0.9
62 0.9181 0.8 0.9
64 0.9254 0.8 0.9 pessimistic
However, both the CV and the T/R-ratio are estimates, i.e., are uncertain (the degree of uncertainty depends on the sample size of the pilot study). Power – and hence, the sample size – is less sensitive to the CV than to the T/R-ratio. The latter is a killer, especially in your case which is so close to the lower BE-limit:
f <- function(x, obj) power.TOST(theta0 = x, CV = CV, design = design, n = n) - obj
stoned <- sampleN.TOST(CV = CV, theta0 = GMR, design = design, targetpower = target, print = FALSE)
n <- stoned[["Sample size"]]
pwr <- 100 * stoned[["Achieved power"]]
obj <- c(50, 70)
GMRmin <- uniroot(f, obj = obj[1] / 100, interval = c(0.8, 1), tol = 1e-12)$root
GMR0.7 <- uniroot(f, obj = obj[2] / 100, interval = c(0.8, 1), tol = 1e-12)$root
GMRs <- sort(unique(c(GMRmin, GMR0.7, GMR, seq(0.8, 0.9, length.out = 201))))
power <- numeric(length(GMRs))
for (j in seq_along(GMRs)) {
power[j] <- 100 * power.TOST(CV = CV, theta0 = GMRs[j], design = design, n = n)
}
clr <- c("red", "blue", "darkgreen")
plot(GMRs, power, type = "n", ylim = c(0, 100), xlab = "GMR", axes = FALSE,
xaxs = "i", yaxs = "i", font.main = 1,
main = sprintf("%s design, CV = %.3g%%: n = %.0f", design, 100 * CV, n))
x.axis <- seq(0.8, 0.9, 0.025)
y.axis <- 100 * c(0.05, 0.5, 0.7, seq(0.2, 1, 0.2))
abline(v = x.axis, h = y.axis, col = "lightgrey", lty = 3)
lines(x = c(rep(GMRmin, 2), 0), y = c(0, rep(obj[1], 2)), lwd = 2, lty = 3, col = clr[1])
lines(GMRs[GMRs <= GMRmin], power[GMRs <= GMRmin], col = clr[1], lwd = 3)
mtext(1, line = 2.1, at = GMRmin, text = sprintf("%.4g", GMRmin), cex = 0.75, col = clr[1])
lines(x = c(rep(GMR0.7, 2), 0), y = c(0, rep(obj[2], 2)), lwd = 2, lty = 2, col = clr[2])
lines(GMRs[GMRs >= GMRmin & power <= pwr], power[GMRs >= GMRmin & power <= pwr],
col = clr[2], lwd = 3)
mtext(1, line = 2.1, at = GMR0.7, text = sprintf("%.4g", GMR0.7), cex = 0.75, col = clr[2])
lines(x = c(rep(GMR, 2), 0), y = c(0, rep(pwr, 2)), lwd = 2, col = clr[3])
lines(GMRs[power >= pwr], power[power >= pwr], col = clr[3], lwd = 3)
mtext(1, line = 2.1, at = GMR, text = sprintf("%.4g", GMR), cex = 0.75, col = clr[3])
axis(1, at = x.axis, labels = sprintf("%.3f", x.axis))
axis(1, at = c(GMRmin, GMR0.7, GMR), labels = FALSE)
axis(1, at = seq(0.8, 0.9, 0.005), labels = FALSE, tcl = -0.25)
axis(2, at = y.axis, labels = sprintf("%.0f%%", y.axis), las = 1)
axis(2, at = c(5, seq(10, 90, 10)), labels = FALSE, tcl = -0.25)
box()
cat("With", n, "subjects and", sprintf("GMR = %.4g", GMR0.7), "power will be",
"only 70%;", sprintf("any GMR < %.4g", GMRmin), "will fail BE.\n")
With 44 subjects and GMR = 0.834 power will be only 70%; any GMR < 0.8256 will fail BE.
Let’s explore some combinations of CVs and T/R-ratios:
sampleN.TOST.vec <- function(CVs, GMRs, ...) {
n <- matrix(ncol = length(CVs), nrow = length(GMRs))
for (j in seq_along(GMRs)) {
for (k in seq_along(CVs)) {
n[j, k] <- sampleN.TOST(CV = CVs[k], theta0 = GMRs[j], design = design, targetpower = target,
print = FALSE)[["Sample size"]]
}
}
dec <- function(x) match(TRUE, round(x, 1:15) == x)
fmt.col <- paste0("CV=%.", max(sapply(100 * CVs, dec), na.rm = TRUE), "f%%")
fmt.row <- paste0("GMR=%.", max(sapply(GMRs, dec), na.rm = TRUE), "f")
colnames(n) <- sprintf(fmt.col, 100 * CVs)
rownames(n) <- sprintf(fmt.row, GMRs)
return(as.data.frame(n))
}
CVs <- sort(unique(c(CV, seq(0.08, 0.1, 0.005))))
GMRs <- seq(0.82, 0.86, 0.01)
res <- sampleN.TOST.vec(CVs, GMRs, design, target)
cat("Sample sizes to achieve at least", sprintf("%2g%% power:", 100 * target), "\n"); print(res)
Sample sizes to achieve at least 80% power:
CV=8.00% CV=8.50% CV=8.86% CV=9.00% CV=9.50% CV=10.00%
GMR=0.82 132 148 160 166 184 204
GMR=0.83 60 68 74 76 84 94
GMR=0.84 36 40 44 44 50 54
GMR=0.85 24 26 28 30 32 36
GMR=0.86 18 20 20 22 24 26
Bayesian methods based on the expected power are implemented in
PowerTOST
, which take the uncertainty of estimates obtained in the pilot study into account.- Uncertain CV
res1 <- expsampleN.TOST(CV = CV, theta0 = GMR, targetpower = target, design = design,
prior.parm = list(m = m, design = design), prior.type = "CV",
details = FALSE, print = FALSE)
cat("Sample size estimation based on uncertain CV:",
sprintf("\nExpected power of %.4f with %.0f subjects.\n",
res1[["Achieved power"]], res1[["Sample size"]]))
Sample size estimation based on uncertain CV:
Expected power of 0.8016 with 48 subjects.
9% more subjects than in the ‘carved in stone approach’. However, the CV is not the main problem.
- Uncertain T/R-ratio
res2 <- expsampleN.TOST(CV = CV, theta0 = GMR, targetpower = target, design = design,
prior.parm = list(m = m, design = design), prior.type = "theta0",
details = FALSE, print = FALSE)
cat("Sample size estimation based on uncertain T/R-ratio:",
sprintf("\nExpected power of %.4f with %.0f subjects.\n",
res2[["Achieved power"]], res2[["Sample size"]]))
Sample size estimation based on uncertain T/R-ratio:
Expected power of 0.8013 with 120 subjects.
That hurts! If you propose that to your boss, likely you get fired.
- Uncertain CV and T/R-ratio
res3 <- expsampleN.TOST(CV = CV, theta0 = GMR, targetpower = target, design = design,
prior.parm = list(m = m, design = design), prior.type = "both",
details = FALSE, print = FALSE)
cat("Sample size estimation based on uncertain CV and T/R-ratio:",
sprintf("\nExpected power of %.4f with %.0f subjects.\n",
res3[["Achieved power"]], res3[["Sample size"]]))
Sample size estimation based on uncertain CV and T/R-ratio:
Expected power of 0.8005 with 146 subjects.
Ouch! Even with such an extreme sample size there is still a 20% chance of failure. If you want 90% power, you would need thousands (‼) of subjects…
Dif-tor heh smusma 🖖🏼 Довге життя Україна!
Helmut Schütz
The quality of responses received is directly proportional to the quality of the question asked. 🚮
Science Quotes
Complete thread:
- Go/No-go Decision for Pivotal Study NK 2023-12-27 12:15 [Power / Sample Size]
- Problematic T/R-ratio…Helmut 2023-12-27 13:27
- TSD? Helmut 2024-01-01 13:50
- sample size for TSD is better than for 1SD? mittyri 2024-01-01 19:54
- TSD? Helmut 2024-01-01 13:50
- Problematic T/R-ratio…Helmut 2023-12-27 13:27