[Rd] too-large notches in boxplot (PR #7690)

Ben Bolker bolker at zoo.ufl.edu
Mon Jan 23 20:37:18 CET 2006


   PR #7690 points out that if the confidence intervals (+/-1.58 
IQR/sqrt(n)) in a boxplot with notch=TRUE are larger than the
hinges -- which is most likely to happen for small n and asymmetric
distributions -- the resulting plot is ugly, e.g.:

set.seed(1001)
npts <- 5
X <- rnorm(2*npts,rep(3:4,each=npts),sd=1)
f <- factor(rep(1:2,each=npts))
boxplot(X~f)
boxplot(X~f,notch=TRUE)

   I can imagine debate about what should be done in this case --
you could just say "don't do that", since the notches are based
on an asymptotic argument ... the diff below just truncates
the notches to the hinges, but produces a warning saying that the 
notches have been truncated.

   ?? what should the behavior be ??

  the diff is against the 11 Jan version of R 2.3.0



*** newboxplot.R        2006-01-23 14:32:12.000000000 -0500
--- oldboxplot.R        2006-01-23 14:29:29.000000000 -0500
***************
*** 84,98 ****
       bplt <- function(x, wid, stats, out, conf, notch, xlog, i)
       {
         ## Draw single box plot
-       conf.ok <- TRUE
-       if(!any(is.na(stats))) {
-           ## check for overlap of notches and hinges
-           if (notch && (stats[2]>conf[1] || stats[4]<conf[2])) {
-              conf.ok <- FALSE
-              conf[1] <- max(conf[1],stats[2])
-              conf[2] <- min(conf[2],stats[4])
-            }

             ## stats = +/- Inf: polygon & segments should handle

             ## Compute 'x + w' -- "correctly" in log-coord. case:
--- 84,91 ----
       bplt <- function(x, wid, stats, out, conf, notch, xlog, i)
       {
         ## Draw single box plot

+       if(!any(is.na(stats))) {
             ## stats = +/- Inf: polygon & segments should handle

             ## Compute 'x + w' -- "correctly" in log-coord. case:
***************
*** 148,154 ****
                           domain = NA)
             }
         }
-       return(conf.ok)
       } ## bplt

       if(!is.list(z) || 0 == (n <- length(z$n)))
--- 141,146 ----
***************
*** 239,252 ****
           xysegments <- segments
       }

-     conf.ok <- numeric(n)
       for(i in 1:n)
!       conf.ok[i] <- bplt(at[i], wid=width[i],
              stats= z$stats[,i],
              out  = z$out[z$group==i],
              conf = z$conf[,i],
              notch= notch, xlog = xlog, i = i)
!     if (any(!conf.ok)) warning("some confidence limits > hinges: 
notches truncated")
       axes <- is.null(pars$axes)
       if(!axes) { axes <- pars$axes; pars$axes <- NULL }
       if(axes) {
--- 231,243 ----
           xysegments <- segments
       }

       for(i in 1:n)
!       bplt(at[i], wid=width[i],
              stats= z$stats[,i],
              out  = z$out[z$group==i],
              conf = z$conf[,i],
              notch= notch, xlog = xlog, i = i)
!
       axes <- is.null(pars$axes)
       if(!axes) { axes <- pars$axes; pars$axes <- NULL }
       if(axes) {

-- 
620B Bartram Hall                            bolker at zoo.ufl.edu
Zoology Department, University of Florida    http://www.zoo.ufl.edu/bolker
Box 118525                                   (ph)  352-392-5697
Gainesville, FL 32611-8525                   (fax) 352-392-3704



More information about the R-devel mailing list