[R] Using sunflowerplot to add points in a xyplot panel
Sundar Dorai-Raj
sundar.dorai-raj at pdf.com
Tue Aug 14 16:35:14 CEST 2007
Ronaldo Reis Junior said the following on 8/14/2007 7:08 AM:
> Hi,
>
> I use panel.points to add points to a xyplot graphic. But I like to use the
> sunflowerplot to plot my points because this is very superimposed. It is
> possible to use this? I try but it dont work directly. It may be need to put
> this function inside a panel.???
>
> Thanks
> Ronaldo
You'll need to write your own panel function. Here's one shot at it.
Most of the code is from ?sunflowerplot with added touches for lattice
capability.
HTH,
--sundar
panel.sunflowerplot <- function(x, y, number, log = "", digits = 6,
rotate = FALSE,
cex.fact = 1.5, size = 1/8, seg.col =
2, seg.lwd = 1.5, ...) {
n <- length(x)
if(missing(number)) {
x <- signif(x, digits = digits)
y <- signif(y, digits = digits)
orderxy <- order(x, y)
x <- x[orderxy]
y <- y[orderxy]
first <- c(TRUE, (x[-1] != x[-n]) | (y[-1] != y[-n]))
x <- x[first]
y <- y[first]
number <- diff(c((1:n)[first], n + 1))
} else {
if(length(number) != n)
stop("'number' must have same length as 'x' and 'y'")
np <- number > 0
x <- x[np]
y <- y[np]
number <- number[np]
}
n <- length(x)
n.is1 <- number == 1
cex <- trellis.par.get("plot.symbol")$cex
if(any(n.is1))
lpoints(x[n.is1], y[n.is1], cex = cex, ...)
if(any(!n.is1)) {
lpoints(x[!n.is1], y[!n.is1], cex = cex/cex.fact, ...)
i.multi <- (1:n)[number > 1]
ppin <- par("pin")
pusr <- unlist(current.panel.limits())
xr <- size * abs(pusr[2] - pusr[1])/ppin[1]
yr <- size * abs(pusr[4] - pusr[3])/ppin[2]
i.rep <- rep.int(i.multi, number[number > 1])
z <- numeric()
for (i in i.multi) z <- c(z, 1:number[i] + if (rotate)
stats::runif(1) else 0)
deg <- (2 * pi * z)/number[i.rep]
lsegments(x[i.rep], y[i.rep], x[i.rep] + xr * sin(deg),
y[i.rep] + yr * cos(deg), col = seg.col, lwd = seg.lwd)
}
}
library(lattice)
xyplot(Petal.Width ~ Petal.Length, iris, panel = panel.sunflowerplot)
More information about the R-help
mailing list