TSD useful at all? [Two-Stage / GS Designs]

posted by Helmut Homepage – Vienna, Austria, 2023-12-26 13:50 (478 d 18:55 ago) – Posting: # 23811
Views: 4,524

❝ Hi Helumt,

Please learn my name…

❝ Thank you for the nmax info, didnt know.

Welcome.

❝ BTW your RSABE.TSD script seems very useful !!

Use the updated [image]-script at the end.

I don’t think that a TSD is useful at all, unless you use the observed GMR of stage 1 (argument usePE = TRUE) and a reasonable Nmax. But (‼) if your final GMR is really that bad, you will fail – even if the CVwR is larger (which means more scaling).

RSABE.TSD(n1 = 24, CVwR = 0.6978, GMR = 0.85, Nmax = 100,
          usePE = TRUE, CVwR.2 = 0.8, GMR.2 = 0.72)
adjusted alpha : 0.0294 (Pocock’s for superiority)
design         : 2x2x4  (2-sequence 4-period full replicate)
n1             :  24
futility on N  : 100
futility on PE : outside 0.8000 – 1.2500 (guidances)
CVwR           : 0.6978 (observed)
theta1         : 0.5700 (lower implied limit)
theta2         : 1.7545 (upper implied limit)
GMR            : 0.8500 (observed)
power          : 0.6369 (estimated)
Stage 2 initiated (insufficent power in stage 1)
target GMR     : 0.8500 (observed)
target power   : 0.8000 (fixed)
n2             :  54
N              :  78

CVwR           : 0.8000 (observed)
GMR            : 0.7200 (observed)
theta1         : 0.5338 (lower implied limit)
theta2         : 1.8735 (upper implied limit)

power          : 0.0932 (estimated, fails RSABE)

You can massage the numbers as you like, but – irrespective of the CVwR and sample size – with any GMR in the final analysis outside the PE-constraints {0.80, 1.25} you  will  must fail.

We could observe the PE-constraints according to the guidances:

Stop for futility in the interim if \(\small{GMR\notin\left\{>0.80\;\wedge<1.25\right\}}\).

How­ever, for such an approach the GMR has to be reasonably accurate, i.e., the stage 1 sample size sufficiently large. Don’t ask me what would be sufficient… Larger deviations between GMRs are a direct consequence of higher variability. The FDA requires at least 24 enrolled subjects in replicate designs intended for reference-scaling. If the CVwR is expected to be large, I would opt for substantially more in order to get a reliable estimate.
With the results of your first stage with 24 subjects:

RSABE.TSD(n1 = 24, CVwR = 0.6978, GMR = 0.72, final = FALSE)
adjusted alpha : 0.0294 (Pocock’s for superiority)
design         : 2x2x4  (2-sequence 4-period full replicate)
n1             :  24
futility on PE : outside 0.8000 – 1.2500 (guidances)
CVwR           : 0.6978 (observed)
theta1         : 0.5700 (lower implied limit)
theta2         : 1.7545 (upper implied limit)
GMR            : 0.7200 (observed)
power          : 0.1838 (estimated)

Study stopped for futility (lower PE constraint)



RSABE.TSD <- function(adj = 0.0294, design = "2x2x4", n1, CVwR, GMR,
                      target = 0.8, Nmax = Inf, usePE = FALSE, final = TRUE,
                      CVwR.2, GMR.2, risk = FALSE, details = TRUE) {
  # adj    : adjusted alpha (stage 1 and final analysis) like Potvin ‘Method B’
  #          defaults to 0.0294 (Pocock’s for superiority)
  # design : "2x2x4": 2-sequence 4-period full replicate (default)
  #          "2x2x3": 2-sequence 3-period full replicate
  #          "2x3x3": 3-sequence 3-period partial replicate
  # n1     : stage 1 sample size
  # CvwR   : observed within-subject CV of R in stage 1
  # GMR    : observed T/R-ratio in stage 1
  # target : target (desired) power for sample size re-estimation (default 0.8)
  # Nmax   : futility on total sample size (default: unrestricted)
  # usePE  : FALSE: use a fixed (assumed) GMR
  #          TRUE:  use the GMR observed in stage 1
  # final  : TRUE : final analysis (requires CVwR.2 and GMR.2)
  #          FALSE: interim analyis only
  # risk   : FALSE: TIE acc. to all publications based on the ‘implied limits’
  #          TRUE : additionallly TIE acc. to the ‘desired consumer risk model’
  # details: TRUE : output to the console
  #          FALSE: data.frame of results

  if (adj >= 0.05) warning ("Unadjusted alpha ", adj, " is not recommended.")
  designs  <- c("2x2x4", "2x2x3", "2x3x3")
  if (!design %in% designs) stop ("design ", design, " is not supported.")
  if (missing(n1)) stop ("Number of subjects in stage 1 (n1) must be given!")
  if (missing(CVwR)) stop ("CVwR in stage 1 must be given!")
  if (missing(GMR)) stop ("GMR in stage 1 must be given!")
  if (target <= 0.5 | target >= 1) stop ("target ", target, " doesn’t make sense.")
  nseq     <- as.integer(substr(design, 3, 3))
  if (Nmax <= n1 + nseq) stop (paste("Nmax <= n1 +", nseq, "doesn’t make sense."))
  fClower  <- 0.80 # lower boundary of the PE-constraints acc. to the guidance
  fCupper  <- 1.25 # upper boundary of the PE-constraints acc. to the guidance
  des.verb <- c(" (2-sequence 4-period full replicate)",
                " (2-sequence 3-period full replicate)",
                " (3-sequence 3-period partial replicate)")
  if (final) {
    if (missing(CVwR.2))
      stop ("CVwR in the final analysis (CVwR.2) must be given!")
    if (missing(GMR.2))
      stop ("GMR in the final analysis (GMR.2) must be given!")
  }
  suppressMessages(require(PowerTOST))             # ≥1.5-4 (2022-02-21)
  limits <- function(CVwR, risk = FALSE) {         # limits
    thetas <- scABEL(CV = CVwR, regulator = "FDA") # implied
    if (risk) {                                    # ‘desired consumer risk model’
      swR <- CV2se(CVwR)
      if (swR > 0.25) {
        thetas <- setNames(exp(c(-1, +1) * log(1.25) / 0.25 * swR),
                           c("lower", "upper"))
      } else {
        thetas <- setNames(c(0.8, 1.25), c("lower", "upper"))
      }
    }
    return(thetas)
  }
  power <- function(alpha = 0.05, CVwR, GMR, n, design) {
    return(suppressMessages(power.RSABE(alpha = alpha, CV = CVwR,
                                        theta0 = GMR, n = n, design = design)))
  }
  TIE <- function(alpha = 0.05, CVwR, n, design, risk) {
    return(suppressMessages(power.RSABE(alpha = alpha, CV = CVwR,
                                        theta0 = limits(CVwR, risk)[["upper"]],
                                        n = n, design = design, nsims = 1e6)))
  }
  TIE.1.1 <- TIE.1.2 <- TIE.2.1 <- TIE.2.2 <- N <- req <- NA
  pwr.1   <- power(adj, CVwR, GMR, n = n1, design)
  futile  <- FALSE
  sig     <- binom.test(0.05 * 1e6, 1e6, alternative = "less",
                        conf.level = 0.95)$conf.int[2]
  txt    <- paste("adjusted alpha :", sprintf("%.4f", adj))
  # Note: Pockock’s adjusted alphas are for group-sequential designs
  # with one interim analysis at exactly N/2 and known variances!

  if (adj == 0.0294) {
    txt <- paste(txt, "(Pocock’s for superiority)")
  } else {
    if (adj == 0.0304) {
      txt <- paste(txt, "(Pocock’s for equivalence)")
    } else {
      if (adj == 0.0250) {
        txt <- paste(txt, "(Bonferroni’s for two independent tests)")
      } else {
        txt <- paste(txt, "(custom)")
      }
    }
  }
  txt    <- paste(txt, "\ndesign        :", design,
                  des.verb[design == designs],
                  "\nn1            :", sprintf("%3.0f", n1))
  if (Nmax < Inf) {
    txt <- paste(txt, "\nfutility on N  :", sprintf("%3.0f", Nmax))
  }
  txt <- paste(txt, "\nfutility on PE : outside",
               sprintf("%.4f – %.4f (guidances)", fClower, fCupper))
  txt <- paste(txt, "\nCVwR           :",
               sprintf("%.4f (observed)", CVwR),
               "\ntheta1         :",
               sprintf("%.4f (lower implied limit)",
                       limits(CVwR)[["lower"]]))
  if (risk) {
    txt <- paste(txt, "\n                ",
                 sprintf("%.4f", limits(CVwR.2, risk)[["lower"]]),
                 "(lower limit of the ‘desired consumer risk model’)")
  }
  txt <- paste(txt, "\ntheta2         :",
               sprintf("%.4f (upper implied limit)",
                       limits(CVwR)[["upper"]]))
  if (risk) {
    txt <- paste(txt, "\n                ",
                 sprintf("%.4f", limits(CVwR.2, risk)[["upper"]]),
                 "(upper limit of the ‘desired consumer risk model’)")
  }
  txt <- paste(txt, "\nGMR            :", sprintf("%.4f", GMR), "(observed)")
  txt <- paste(txt, "\npower          :", sprintf("%.4f (estimated)", pwr.1))
  if (pwr.1 >= target) { # stop in stage 1
    TIE.1.1 <- TIE(adj, CVwR, n1, design, risk = FALSE)
    txt <- paste0(txt, "\nStudy stopped in stage 1 (sufficient power)",
                  "\nempirical TIE  :", sprintf(" %.4f", TIE.1.1),
                  " (all publications")
    if (TIE.1.1 > sig) {
      txt <- paste0(txt, "; significantly inflated)")
    } else {
      txt <- paste0(txt, ")")
    }
    if (risk) {
      TIE.1.2 <- TIE(adj, CVwR, n1, design, risk = TRUE)
      txt     <- paste(txt, "\n                ", sprintf("%.4f", TIE.1.2),
                       "(‘desired consumer risk model’")
      if (TIE.1.2 > sig) {
        txt <- paste0(txt, "; significantly inflated)")
      } else {
        txt <- paste0(txt, ")")
      }
    }
    if (TIE.1.1 > sig) {
      req <- scABEL.ad(alpha.pre = adj, theta0 = GMR, CV = CVwR,
                       design = design, regulator = "FDA", n = n1,
                       print = FALSE, details = FALSE)[["alpha.adj"]]
      txt <- paste(txt, "\nAn adjusted alpha of", sprintf("%.4f", req),
                   "(or less)\nwould be needed to control the Type I Error.")
    }
  } else {               # possibly initiate stage 2
    if (GMR > fClower & GMR < fCupper) {
      N <- sampleN.RSABE(alpha = adj, CV = CVwR, theta0 = GMR,
                         targetpower = target, design = design,
                         print = FALSE, details = FALSE)[["Sample size"]]
    }
    if (is.na(N) | N > Nmax | GMR <= fClower | GMR >= fCupper) {
      txt <- paste(txt, "\nStudy stopped for futility")
      if (GMR <= fClower | GMR >= fCupper) { # stop for GMR futility
        if (GMR <= fClower) txt <- paste(txt, "(lower PE constraint)")
        if (GMR >= fCupper) txt <- paste(txt, "(upper PE constraint)")

      } else {                               # stop for Nmax futility
        txt <- paste(txt, "(insufficent power in stage 1\nbut total sample size")
        if (!is.na(N)) txt <- paste(txt, N)
        txt <- paste(txt, "above futility limit)")
      }
    } else {
      if (final) {
        pwr.2 <- power(adj, CVwR.2, GMR.2, n = N, design)
        if (GMR.2 <= 0.8 | GMR.2 >= 1.25) {
          final.est <- FALSE
        } else {
          final.est <- TRUE
          TIE.2.1 <- TIE(adj, CVwR.2, N, design, risk = FALSE)
          if (risk) TIE.2.2 <- TIE(adj, CVwR.2, N, design, risk = TRUE)
        }
      } else {
        CVwR.2 <- GMR.2 <- pwr.2 <- TIE.2.1 <- TIE.2.2 <- NA
        theta1.1 <- theta1.2 <- req <- NA
      }
        txt <- paste(txt, "\nStage 2 initiated (insufficent power in stage 1)",
                     "\ntarget GMR     :", sprintf("%.4f", GMR))
        ifelse (usePE, txt <- paste(txt, "(observed)"),
                       txt <- paste(txt, "(fixed)"))
        txt <- paste(txt, "\ntarget power   :", sprintf("%.4f (fixed)", target),
                     "\nn2             :", sprintf("%3.0f", N - n1),
                     "\nN              :", sprintf("%3.0f", N))
        if (N < 24) txt <- paste0(txt,
                                  "; less than the FDA’s minimum of 24 subjects!")
      if (final) {
        txt <- paste(txt, "\nCVwR           :",
                     sprintf("%.4f (observed)", CVwR.2),
                     "\nGMR            :", sprintf("%.4f (observed)", GMR.2),
                     "\ntheta1         :",
                     sprintf("%.4f (lower implied limit)",
                             limits(CVwR.2)[["lower"]]))
        if (risk) {
          txt <- paste(txt, "\n                ",
                       sprintf("%.4f", limits(CVwR.2, risk)[["lower"]]),
                       "(lower limit of the ‘desired consumer risk model’)")
        }
        txt <- paste(txt, "\ntheta2         :",
                     sprintf("%.4f (upper implied limit)",
                             limits(CVwR.2)[["upper"]]))
        if (risk) {
          txt <- paste(txt, "\n                ",
                       sprintf("%.4f", limits(CVwR.2, risk)[["upper"]]),
                       "(upper limit of the ‘desired consumer risk model’))
        }
        txt <- paste(txt, "\npower          :", sprintf("%.4f (estimated,", pwr.2))
        ifelse (pwr.2 < 0.5, txt <- paste(txt, "fails RSABE)"),
                             txt <- paste(txt, "may pass RSABE)"))
        if (final.est) {
          txt <- paste0(txt, "\nempirical TIE  :", sprintf(" %.4f", TIE.2.1),
                        " (all publications")
          if (TIE.2.1 > sig) {
            txt <- paste0(txt, "; significantly inflated)")
          } else {
            txt <- paste0(txt, ")")
          }
          if (risk) {
            txt <- paste(txt, "\n                ", sprintf("%.4f", TIE.2.2),
                         "(‘desired consumer risk model’")
            if (TIE.2.2 > sig) {
              txt <- paste0(txt, "; significantly inflated)")
            } else {
              txt <- paste0(txt, ")")
            }
          }
          if (TIE.2.1 > sig) {
            req <- scABEL.ad(alpha.pre = adj, theta0 = GMR.2, CV = CVwR.2,
                             design = design, regulator = "FDA", n = N,
                             print = FALSE, details = FALSE)[["alpha.adj"]]
            txt <- paste(txt, "\nAn adjusted alpha of", sprintf("%.4f", req),
                         "(or less)\nwould be needed to control the Type I Error.")
          } else {
            req <- NA
          }
        }
      }
    }
  }
  if (details) { # output to the console
    cat(txt, "\n")
  } else {       # data.frame of results
    # limits in stage 1
    L.1.1 <- limits(CVwR, FALSE)[["lower"]]
    U.1.1 <- limits(CVwR, FALSE)[["upper"]]
    L.1.2 <- U.1.2 <- NA
    if (risk) {
      L.1.2 <- limits(CVwR, TRUE)[["lower"]]
      U.1.2 <- limits(CVwR, TRUE)[["upper"]]
    }
    if (final) {
      # limits in the final analysis
      L.2.1 <- limits(CVwR.2, FALSE)[["lower"]]
      U.2.1 <- limits(CVwR.2, FALSE)[["upper"]]
      L.2.2 <- U.2.2 <- NA
      if (risk) {
        L.2.2 <- limits(CVwR.2, TRUE)[["lower"]]
        U.2.2 <- limits(CVwR.2, TRUE)[["upper"]]
      }
    } else {
      L.2.1 <- U.2.1 <- L.2.2 <- U.2.2 <- NA
    }
    result <- data.frame(alpha.adj = adj, design = design, n1 = n1, CVwR = CVwR,
                         GMR = GMR, usePE = usePE, Nmax = Nmax, risk.model = risk,
                         L.1.1 = L.1.1, U.1.1 = U.1.1,
                         L.1.2 = L.1.2, U.1.2 = U.1.2, power.1 = pwr.1,
                         TIE.1.1 = TIE.1.1, TIE.1.2 = TIE.1.2, futile = futile,
                         n2 = N - n1, N = N)
    if (final) {
      res2  <- data.frame(CVwR.2 = CVwR.2, GMR.2 = GMR.2,
                          L.2.1 = L.2.1, U.2.1 = U.2.1,
                          L.2.2 = L.2.2, U.2.2 = U.2.2,
                          power.2 = pwr.2, TIE.2.1 = TIE.2.1,
                          TIE.2.2 = TIE.2.2, alpha.req = req)
     result <- cbind(result, res2)
    }
    result <- result[, colSums(is.na(result)) < nrow(result)]
    return(result)
  }
}


Dif-tor heh smusma 🖖🏼 Довге життя Україна! [image]
Helmut Schütz
[image]

The quality of responses received is directly proportional to the quality of the question asked. 🚮
Science Quotes

Complete thread:

UA Flag
Activity
 Admin contact
23,424 posts in 4,927 threads, 1,713 registered users;
26 visitors (0 registered, 26 guests [including 7 identified bots]).
Forum time: 09:46 CEST (Europe/Vienna)

Do not worry about your difficulties in mathematics.
I can assure you mine are still greater.    Albert Einstein

The Bioequivalence and Bioavailability Forum is hosted by
BEBAC Ing. Helmut Schütz
HTML5