Sample size for 3-way crossover [Power / Sample Size]
❝ Thank you for those who created the wonderful PowerTOST package and who are sharing their knowledge in this forum.
Welcome.
❝ […] 3-way crossover (e.g. 3x6x3). I want to demonstrate that both test drugs T1 and T2 are BE to the reference R. The althernative hypothesis is: T1 = R and T2 = R.
❝
❝ When performing the sample size calculation using PowerTOST for 3-way crossover, which alternative is considered? Since there are several ways to formulate the alternatives, I wasn't sure whether the current settings of PowerTOST correspond to the one that is of my interest. If it doesn't, what is your recommendation to deal with my scenario of interest?
Use the script mentioned in the previous post.
❝ Another question is related to the number of PK parameters included. Does the sample size calculation consider the number of PK parameters for the BE?
You have to demonstrate BE for all PK metrics. Therefore, it is a little bit more difficult to show BE for the FDA and China’s CDE (Cmax, AUC0–t, AUC0–∞) than in other jurisdictions, where AUC0–∞ is not required. Since the CV of Cmax is generally larger than the one of AUC, no problem. If you pass BE of Cmax, likely you will pass AUC as well.
You don’t have be worried about multiplicity issues because the Type I Error is controlled by the Intersection-Union Tests (IUT).* Therefore, you don’t need to adjust the α-level of the tests, i.e., the common 90% CI is just fine. Since you want to demonstrate equivalence of both test treatments to the reference, the same logic applies here. Hence, base the sample size estimation on the worst case, i.e., the PK metric of T1 or T2 where you expect the largest deviation from R and/or which shows the largest CV.
For the ‘Two at Time’ approach use the argument
bal = TRUE
:
library(PowerTOST)
target <- 0.80 # target power
alpha <- 0.05 # no adjustment for IUT
x <- data.frame(treatment = rep(c("A", "B"), each = 2),
metric = c("Cmax", "AUC"),
theta0 = c(0.94, 0.95,
0.96, 0.97),
CV = c(0.25, 0.20,
0.23, 0.18),
n = NA_integer_, power = NA_real_)
for (j in 1:nrow(x)) { # preliminary sample sizes for both treatments and metrics
x$n[j] <- sampleN.TOST(alpha = alpha, CV = x$CV[j], theta0 = x$theta0[j],
targetpower = target, print = FALSE)[["Sample size"]]
}
CV <- x$CV[x$n == max(x$n)] # extract the
theta0 <- x$theta0[x$n == max(x$n)] # worst case
y <- make.ibds(alpha = alpha, CV = CV, theta0 = theta0, ntmt = 3, ref = "C",
sep = "–", bal = TRUE, details = FALSE, print = FALSE)
x$n <- y$n # replace preliminary sample sizes with final one
for (j in 1:nrow(x)) {
x$power[j] <- signif(power.TOST(alpha = alpha, CV = x$CV[j],
theta0 = x$theta0[j], n = y$n), 4)
}
print(y$rand); cat(y$txt, "\n\n"); print(x, row.names = FALSE, right = FALSE)
subject seqno sequence IBD 1 IBD 2
1 1 4 BCA –CA BC–
2 2 5 CAB CA– C–B
3 3 6 CBA C–A CB–
4 4 2 ACB AC– –CB
5 5 2 ACB AC– –CB
6 6 5 CAB CA– C–B
7 7 3 BAC –AC B–C
8 8 3 BAC –AC B–C
9 9 6 CBA C–A CB–
10 10 1 ABC A–C –BC
11 11 4 BCA –CA BC–
12 12 1 ABC A–C –BC
13 13 1 ABC A–C –BC
14 14 6 CBA C–A CB–
15 15 4 BCA –CA BC–
16 16 1 ABC A–C –BC
17 17 5 CAB CA– C–B
18 18 3 BAC –AC B–C
19 19 4 BCA –CA BC–
20 20 3 BAC –AC B–C
21 21 6 CBA C–A CB–
22 22 5 CAB CA– C–B
23 23 2 ACB AC– –CB
24 24 2 ACB AC– –CB
25 25 4 BCA –CA BC–
26 26 3 BAC –AC B–C
27 27 3 BAC –AC B–C
28 28 1 ABC A–C –BC
29 29 1 ABC A–C –BC
30 30 6 CBA C–A CB–
31 31 2 ACB AC– –CB
32 32 2 ACB AC– –CB
33 33 5 CAB CA– C–B
34 34 5 CAB CA– C–B
35 35 4 BCA –CA BC–
36 36 6 CBA C–A CB–
Reference : C
Tests : A, B
Sequences : ABC, ACB, BAC, BCA, CAB, CBA
Subjects per sequence : 6 | 6 | 6 | 6 | 6 | 6 (balanced)
Estimated sample size : 32
Achieved power : 0.8180
Adjustment to obtain period-balance of IBDs
Adjusted sample size : 36
Achieved power : 0.8587
Randomized : 2022-08-10 11:29:39 CEST
Seed : 1823948
treatment metric theta0 CV n power
A Cmax 0.94 0.25 36 0.8587
A AUC 0.95 0.20 36 0.9751
B Cmax 0.96 0.23 36 0.9541
B AUC 0.97 0.18 36 0.9977
A
, B
, and C
for your T1
, T2
, and R
. Maybe I will modify the script later. No promises. An ugly quick-shot at the end. For period-balance of the IBDs we have to round 32 up to to next multiple of 6. Hence, we gain power for the worst case metric. Of course, power for the other metrics is pretty high. At least for those you have some room to navigate and are protected against surprises.Only if you would have an OR-conjunction (you are happy that either of the tests passes), you would have to use
alpha <- 0.025
and assess the study with 95% CIs because you get two chances (see there). In the example you would need 42 subjects.- Berger RL, Hsu JC. Bioequivalence Trials, Intersection-Union Tests and Equivalence Confidence Sets. Stat Sci. 1996; 11(4): 283–302. JSTOR:2246021. Open access.
library(PowerTOST)
library(randomizeBE)
make.equal <- function(n, ns) {
return(as.integer(ns * (n %/% ns + as.logical(n %% ns))))
}
T <- c("T1", "T2")
R <- c("R")
alpha <- 0.05
theta0 <- 0.94
CV <- 0.25
target <- 0.80
sep <- "–"
n <- sampleN.TOST(alpha = alpha, CV = CV, theta0 = theta0,
targetpower = target, print = FALSE)[["Sample size"]]
seqs <- williams(ntmt = 3)
n <- make.equal(n, length(seqs))
seqs <- gsub("", "\\1 \\2", seqs)
repeat {
rand <- RL4(nsubj = n, seqs = seqs, randctrl = FALSE)$rl
trts <- sub("[[:blank:]]+$", "",
sort(
unique(
unlist(
strsplit(Reduce(function(x, y) paste0(x, y), seqs), "")))))
trts <- trts[nzchar(trts)]
if (sum(c(nchar(T), nchar(R))) > length(trts) * 2)
stop("None of the treatments must be coded with more than two characters.")
s <- Reduce(function(x, y) paste0(x, y), trts)
refs <- substr(s, nchar(s), nchar(s))
tests <- trts[!trts %in% refs]
n.ibd <- length(tests) * length(refs)
for (j in 1:n.ibd) {
rand[[paste0("IBD.", j)]] <- NA
}
for (j in 1:nrow(rand)) {
c <- 3
for (k in seq_along(refs)) {
for (m in seq_along(tests)) {
c <- c + 1
excl <- tests[!tests == tests[m]]
excl <- c(excl, refs[!refs == refs[k]])
excl <- paste0("[", paste(excl, collapse = ", "), "]")
rand[j, c] <- gsub(excl, sep, rand$sequence[j])
rand[j, c] <- gsub(tests[m], T[m], rand[j, c])
rand[j, c] <- gsub(refs[k], R[k], rand[j, c])
rand[j, c] <- gsub(" ", " ", rand[j, c])
}
}
}
for (j in seq_along(refs)) {
rand$sequence <- gsub(refs[j], R[j], rand$sequence)
}
for (j in seq_along(tests)) {
rand$sequence <- gsub(tests[j], T[j], rand$sequence)
}
checks <- NA
ibd.seq <- as.data.frame(
matrix(data = NA,
nrow = n.ibd,
ncol = 4, byrow = TRUE,
dimnames = list(names(rand)[4:ncol(rand)],
paste0(rep(c("seq.", "n."), 2),
rep(1:2, each = 2)))))
for (j in 1:n.ibd) {
ibd <- gsub("[^[:alnum:], ]", "", rand[3 + j])
ibd <- gsub("c", "", ibd)
ibd <- gsub(" ", "", unlist(strsplit(ibd, ",")))
ibd.seq[j, c(1, 3)] <- sort(unique(ibd))
ibd.seq[j, c(2, 4)] <- c(length(ibd[ibd == sort(unique(ibd))[1]]),
length(ibd[ibd == sort(unique(ibd))[2]]))
checks[j] <- ibd.seq[j, 2] == ibd.seq[j, 4]
}
if (sum(checks) == length(trts) - 1) break
}
print(rand, row.names = FALSE)
subject seqno sequence IBD.1 IBD.2
1 2 T1 R T2 T1 R – – R T2
2 6 R T2 T1 R – T1 R T2 –
3 1 T1 T2 R T1 – R – T2 R
4 2 T1 R T2 T1 R – – R T2
5 4 T2 R T1 – R T1 T2 R –
6 5 R T1 T2 R T1 – R – T2
7 5 R T1 T2 R T1 – R – T2
8 1 T1 T2 R T1 – R – T2 R
9 3 T2 T1 R – T1 R T2 – R
10 6 R T2 T1 R – T1 R T2 –
11 3 T2 T1 R – T1 R T2 – R
12 4 T2 R T1 – R T1 T2 R –
13 2 T1 R T2 T1 R – – R T2
14 4 T2 R T1 – R T1 T2 R –
15 1 T1 T2 R T1 – R – T2 R
16 6 R T2 T1 R – T1 R T2 –
17 1 T1 T2 R T1 – R – T2 R
18 2 T1 R T2 T1 R – – R T2
19 5 R T1 T2 R T1 – R – T2
20 4 T2 R T1 – R T1 T2 R –
21 3 T2 T1 R – T1 R T2 – R
22 3 T2 T1 R – T1 R T2 – R
23 5 R T1 T2 R T1 – R – T2
24 6 R T2 T1 R – T1 R T2 –
25 6 R T2 T1 R – T1 R T2 –
26 2 T1 R T2 T1 R – – R T2
27 4 T2 R T1 – R T1 T2 R –
28 1 T1 T2 R T1 – R – T2 R
29 1 T1 T2 R T1 – R – T2 R
30 5 R T1 T2 R T1 – R – T2
31 2 T1 R T2 T1 R – – R T2
32 5 R T1 T2 R T1 – R – T2
33 3 T2 T1 R – T1 R T2 – R
34 4 T2 R T1 – R T1 T2 R –
35 3 T2 T1 R – T1 R T2 – R
36 6 R T2 T1 R – T1 R T2 –
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:
- Sample size for 3-way crossover chrisk 2022-08-09 18:55 [Power / Sample Size]
- Sample size for 3-way crossoverHelmut 2022-08-10 11:30
- Sample size for 3-way crossover chrisk 2022-08-10 15:24
- AND or OR, that’s the question Helmut 2022-08-10 15:58
- AND or OR, that’s the question chrisk 2022-08-10 17:46
- AND or OR, that’s the question Helmut 2022-08-10 20:59
- AND or OR, that’s the question chrisk 2022-08-10 22:00
- AND or OR, that’s the question Helmut 2022-08-11 15:25
- AND or OR, that’s the question chrisk 2022-08-12 16:02
- The unknown ρ Helmut 2022-08-17 15:04
- AND or OR, that’s the question chrisk 2022-08-12 16:02
- AND or OR, that’s the question Helmut 2022-08-11 15:25
- AND or OR, that’s the question chrisk 2022-08-10 22:00
- AND or OR, that’s the question Helmut 2022-08-10 20:59
- AND or OR, that’s the question chrisk 2022-08-10 17:46
- AND or OR, that’s the question Helmut 2022-08-10 15:58
- Sample size for 3-way crossover chrisk 2022-08-10 15:24
- Sample size for 3-way crossoverHelmut 2022-08-10 11:30