[R] latticeExtra: useOuterStrips and axis.line$lwd

Deepayan Sarkar deepayan.sarkar at gmail.com
Wed Apr 29 00:55:51 CEST 2009


On Tue, Apr 28, 2009 at 7:40 AM, tyler <tyler.smith at mail.mcgill.ca> wrote:
> Hi,
>
> I'm working on some lattice wireframe figures that have two conditioning
> factors, and I want the strips labelled on the top and left of the
> entire plot, rather than above each individual panel. useOuterStrips()
> does this, but it draws internal axis lines, even after I explicitly set
> axis.line to 0. Is there a way to use useOuterStrips but without axis
> boxes?

Those are actually not axis lines, but the borders of the
0-width/height strips that still get drawn. Here's a modified
useOuterStrips() that doesn't draw the strips, which I'll include in
the next release (also, see below regarding lwd=0).

useOuterStrips <-
    function(x,
             strip = strip.default,
             strip.left = strip.custom(horizontal = FALSE),
             strip.lines = 1,
             strip.left.lines = strip.lines)
{
    dimx <- dim(x)
    stopifnot(inherits(x, "trellis"))
    stopifnot(length(dimx) == 2)
    opar <- if (is.null(x$par.settings)) list() else x$par.settings
    par.settings <-
        modifyList(opar,
                   list(layout.heights =
                        if (x$as.table) list(strip = c(strip.lines,
rep(0, dimx[2]-1)))
                        else list(strip = c(rep(0, dimx[2]-1), 1)),
                        layout.widths =
                        list(strip.left = c(strip.left.lines, rep(0,
dimx[1]-1)))))
    if (is.character(strip))
        strip <- get(strip)
    if (is.logical(strip) && strip)
        strip <- strip.default
    new.strip <-
        if (is.function(strip))
        {
            top.row <- if (x$as.table) 1 else nrow(trellis.currentLayout())
            function(which.given, which.panel, var.name, ...) {
                if (which.given == 1 && current.row() == top.row)
                    strip(which.given = 1,
                          which.panel = which.panel[1],
                          var.name = var.name[1],
                          ...)
            }
        }
        else strip
    if (is.character(strip.left))
        strip.left <- get(strip.left)
    if (is.logical(strip.left) && strip.left)
        strip.left <- strip.custom(horizontal = FALSE)
    new.strip.left <-
        if (is.function(strip.left))
        {
            function(which.given, which.panel, var.name, ...) {
                if (which.given == 2 && current.column() == 1)
                    strip.left(which.given = 1,
                               which.panel = which.panel[2],
                               var.name = var.name[2],
                               ...)
            }
        }
        else strip.left
    update(x,
           par.settings = par.settings,
           strip = new.strip,
           strip.left = new.strip.left,
           par.strip.text = list(lines = 0.5),
           layout = dimx)
}


> I've included a short example. I know the example looks odd without axis
> lines, but in my more complicated wireframe plots I think the axis
> lines are just extra clutter, so I'd like them to disappear.
>
> Thanks,
>
> Tyler
>
>
> library(lattice)
> my.trellis.pars <- trellis.par.get("axis.line")
> my.trellis.pars$lwd = 0

You should use

my.trellis.pars$col = "transparent"

(lwd=0 is not what you think it is).

-Deepayan

> mtcars$HP <- equal.count(mtcars$hp)
>
> trellis.par.set("axis.line", my.trellis.pars)
> xyplot(mpg ~ disp | HP + factor(cyl), mtcars)
>
> useOuterStrips(xyplot(mpg ~ disp | HP + factor(cyl), mtcars))
>
> --
> The purpose of models is not to fit the data but to sharpen the
> questions.                             --Samuel Karlin
>
> ______________________________________________
> R-help at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-help
> PLEASE do read the posting guide http://www.R-project.org/posting-guide.html
> and provide commented, minimal, self-contained, reproducible code.
>




More information about the R-help mailing list