If you have data… [Design Issues]

posted by Helmut Homepage – Vienna, Austria, 2022-09-27 13:52 (570 d 02:57 ago) – Posting: # 23323
Views: 2,691

Hi Imph,

if you have individual half lives, you can calculate the geometric mean / SD and use any confidence interval you like. For planning the washout use the upper confidence limit.
[image]-script (results in blue):

g.fun <- function(x, alpha = 0.05, digits = 4, print.only = FALSE) {
  # calculate geometric mean, SD, and CI of geometric mean
  if (sum(is.na(x)) > 0) { # Remove NA(s)
    message("NA(s) removed from the vector.")
    x <- x[-is.na(x)]
  }
  if (sum(x <= 0) > 0) {   # Only positive numbers are allowed
    message("Geometric mean applicable to",
            "\npositive numbers only; others removed.")
    x <- x[-which(x <= 0)]
  }
  mean.log <- mean(log(x))
  SD.log   <- sd(log(x))
  gMean    <- exp(mean.log)
  gSD      <- exp(SD.log)
  # confidence interval based on the t-distribution with n–1 degrees of freedom
  CI       <- exp(mean.log + c(-1, +1) *
                  qt(alpha / 2, length(x) - 1, lower.tail = FALSE) * SD.log)
  loc.dis  <- setNames(c(gMean, gSD, CI),
                       c("Geom. mean", "Geom. SD",
                         paste0("lower ", 100 * (1 - alpha), "%"),
                         paste0("upper ", 100 * (1 - alpha), "%")))
  if (print.only) {
    print(signif(loc.dis, digits))
  } else {
    return(loc.dis)
  }
}

# give your data in a t12 vector, e.g.,
# t12 <- c(7.15, 5.44, 5.33, ...) and proceed with descriptive statistics


# lognormal-distributed example data
set.seed(123456)
n   <- 24   # sample size
mue <- 6    # geometric mean of half life
CV  <- 0.25 # coefficient of variation
t12 <- rlnorm(n = n,
              meanlog = log(mue) - 0.5 * log(CV^2 + 1),
              sdlog = sqrt(log(CV^2 + 1)))

exp(summary(log(t12)))        # descriptive statistics
 Min. 1st Qu.  Median    Mean 3rd Qu.    Max.
4.425   5.412   6.383   6.530   7.764  10.780


g.fun(t12, print.only = TRUE) # default: 95% CI
Geom. mean   Geom. SD  lower 95%  upper 95%
     6.530      1.275      3.951     10.790


alpha      <- 0.01            # conservative: 99% CI
g.fun(t12, alpha = alpha, print.only = TRUE)
Geom. mean   Geom. SD  lower 99%  upper 99%
     6.530      1.275      3.302     12.910


half.lives <- c(5, 7, 10)
col.name   <- paste0("upper ", 100 * (1 - alpha), "%")
res        <- data.frame(half.lives = half.lives,
                         washout = half.lives * g.fun(t12, alpha = alpha)[[col.name]])
res$days   <- ceiling(res$washout / 24) # round up washout (h) to days
print(round(res, 1), row.names = FALSE)
 half.lives washout days
          5    64.6    3
          7    90.4    4
         10   129.1    6


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
22,987 posts in 4,824 threads, 1,665 registered users;
95 visitors (0 registered, 95 guests [including 7 identified bots]).
Forum time: 16:49 CEST (Europe/Vienna)

The only way to comprehend what mathematicians mean by Infinity
is to contemplate the extent of human stupidity.    Voltaire

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