Helmut
★★★
avatar
Homepage
Vienna, Austria,
2013-04-24 21:31
(4459 d 12:46 ago)

Posting: # 10491
Views: 4,580
 

 ISR (Rocci et al. 2007) [🇷 for BE/BA]

Dear all,

in case someone else is suffering…

#################################################################
# Mario L. Rocci, Jr., Viswanath Devanarayan, David B. Haughey, #
# and Paula Jardieu                                             #
# Confirmatory Reanalysis of Incurred Bioanalytical Samples     #
# AAPS J 9(3), E336–43 (2007)                                   #
#################################################################

ISR1 <- function(c1, c2, main, unit)
  {
    Pct.diff<- 100*(c2-c1)/((c1+c2)/2)
    Pos.d   <- length(Pct.diff[Pct.diff>0])
    Zero.d  <- length(Pct.diff[Pct.diff==0])
    Neg.d   <- length(Pct.diff[Pct.diff<0])
    diff.r  <- log10(c2) - log10(c1)         # Step 1
    Ratio   <- 10^(diff.r)                   #   sample ratios
    mean    <- mean(diff.r)                  #   global mean
    sd      <- sd(diff.r)                    #   global SD
    n       <- length(diff.r)                #   No of samples
    geo.mean<- sqrt(c1*c2)                   # Step 2
    MR      <- 10^(mean)                     # Step 3
    sig     <- c(-1, +1)                     #   helper to compute +/-
    RL      <- 10^(mean+sig*2*sd/sqrt(n))    #   Ratio limits (lo/hi)
    Bias    <- "– no"                        #   Bias (default: no)
    if (max(RL)<1) Bias <- "– negative"
    if (min(RL)>1) Bias <- "– positive"
    ifelse (Bias == "– no",                  #  Bias statement
      Bias.state <- "(ratio 1 within limits).",
      Bias.state <- "(ratio 1 outside limits).")
    LA      <- 10^(mean+sig*sd)              # Step 4
    Comp    <- length(Ratio[Ratio >= LA[1]   #   No of ratios within limits
                    & Ratio <= LA[2]])
    Comp.pct<- Comp/n                        #   Pct of included samples
    ifelse (Comp.pct >= 2/3,                 #   Assessment
      Pass <- "– passed LA (\u22652/3).",
      Pass <- "– failed LA (<2/3).")
    Abs.diff <- abs(Pct.diff)                #   absolute % differences
    y      <- length(Abs.diff[Abs.diff > 20])/n
                                             #   Fraction of samples
                                             #   with > 20% deviation
    ifelse (y <= 2/3,                        #   FDA/EMA Assessement
      Reg <- "– passed", Reg <- "– failed")  #     2/3 within ±20%
    split.screen(c(2, 1))
    screen(1)
    #####################
    # Difference plot   #
    #####################
    yscale <- max(abs(Pct.diff))
    if (yscale < 20) yscale <- 20
    plot(geo.mean, Pct.diff, ylim=c(-yscale, yscale), las=1, log="x", pch=16,
      main=paste0(main," ISR: Difference plot"),
      xlab="", ylab="% Measurement difference")
    abline(h=0, lty="dotted")                #   0%
    lines(range(geo.mean), rep(mean(Pct.diff), 2),
      lwd=2, col="blue")                     #   Mean difference
    lines(range(geo.mean), rep(-20, 2),      #   ±20% (Regulatory limits)
      lwd=2, col="red")
    lines(range(geo.mean), rep(20, 2), lwd=2, col="red")
    screen(2)
    #####################
    # Bland-Altman plot #
    #####################
    yscale <- max(max(Ratio), 1/min(Ratio))
    if (yscale < 1.25) yscale <- 1.25
    plot(geo.mean, Ratio, las=1, ylim=(c(1/yscale, yscale)), log="xy", pch=16,
      main=paste0(main," ISR: Bland-Altman plot"),
      xlab=paste0("Geometric mean ", unit), ylab="Measurement ratio")
    abline(h=1, lty="dotted")                #   Ratio 1
    lines(range(geo.mean), rep(MR, 2),       #   Mean ratio
      lwd=2, col="blue")
    lines(range(geo.mean), rep(RL[1], 2),    #   Ratio limits
      lwd=2, col="darkgreen")
    lines(range(geo.mean), rep(RL[2], 2), lwd=2, col="darkgreen")
    lines(range(geo.mean), rep(LA[1], 2),    #   Limits of agreement
      lwd=2, col="red")
    lines(range(geo.mean), rep(LA[2], 2), lwd=2, col="red")
    close.screen(all=TRUE)
    ###########
    # Results #
    ###########
    cat("\n", sprintf("%s%s %i %s", main, ":", n, "repeated samples\n"),
      sprintf("%s%i%s%i%s%i%s", "\u2206: ",
        Neg.d, " negative, ", Zero.d, " zero, ", Pos.d, " positive"), "\n",
      sprintf("%s%.2f%%", "Maximum |\u2206|: ",max(Abs.diff)), "\n")
    if (y == 0) {
      cat(" No samples")
    } else {
      cat(sprintf(" %.2f%% %s", 100*y, "of samples"))
    }
    cat(" showed >20% |\u2206|", Reg, "regulatory criterion (\u22652/3 within ±20%).\n\n")
    cat(" Mean ratio (2nd/1st analyses):", sprintf("%.2f%%", 100*MR), "\n",
      "Ratio limits:", sprintf("%.2f%%", 100*RL),
       Bias, "bias of repeats", Bias.state, "\n",
      "Limits of agreement:", sprintf("%.2f%%", 100*LA), "\n")
    if (Comp.pct == 0) cat(" No samples")
    if (Comp.pct == 1) cat(" All samples")
    if (Comp.pct > 0 | Comp.pct <1) {
      cat(sprintf(" %.2f%% %s", 100*Comp.pct, "of samples showed "))
    }
    cat("ratios within LsA", Pass, "\n\n")
  }


Gives with …

# Example 1
Reported <- c(478, 107, 826, 108, 248, 696,   141, 194, 548, 676,
              636, 635, 244, 527, 139, 107,   664, 187, 690, 187)
Repeated <- c(406, 107, 718, 109, 250, 674,   135, 179, 564, 598,
              676, 624, 240, 579, 117,  99.3, 583, 176, 610, 190)
ISR1(Reported, Repeated, "Expl.1, LC/MS-MS", "(ng/mL)")


Expl.1, LC/MS-MS: 20 repeated samples
∆: 13 negative, 1 zero, 6 positive
Maximum |∆|: 17.19%
No samples showed >20% |∆| – passed regulatory criterion (≥2/3 within ±20%).

Mean ratio (2nd/1st analyses): 95.31%
Ratio limits: 92.12% 98.61% – negative bias of repeats (ratio 1 outside limits).
Limits of agreement: 88.33% 102.85%
65.00% of samples showed ratios within LsA – failed LA (<2/3).


… and

[image]

Don’t blame the messenger. ;-)


Rocci ML, Devanarayan V, Haughey DB, Jardieu P. Confirmatory Reanalysis of Incurred Bioanalytical Samples. AAPS J. 2007;9(3):Article 40. online


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
UA Flag
Activity
 Admin contact
23,428 posts in 4,929 threads, 1,685 registered users;
52 visitors (0 registered, 52 guests [including 10 identified bots]).
Forum time: 10:17 CEST (Europe/Vienna)

To know that we know what we know,
and to know that we do not know what we do not know,
that is true knowledge.    Nicolaus Copernicus

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