[Rd] plot(x) in 2.7.0 (with y=NULL) proposed code correction

Sklyar, Oleg (MI London) osklyar at maninvestments.com
Tue Apr 22 18:34:24 CEST 2008


Hi all:

following the previous discussion, it looks like plot(x) with y=NULL
still does not work correctly. If one tries for example plot(1:5) it
works, but already for plot(runif(100)) it does not. I posted the
proposed correction for plot.POSIXct and plot.POSIXlt before. Please
voice your opinions whether the following fix for plot.default could be
reasonable? I include the full function and the diff.

Thanks,
Oleg

plot.default <-
    function(x, y = NULL, type = "p", xlim = NULL, ylim = NULL,
             log = "", main = NULL, sub = NULL, xlab = NULL, ylab =
NULL,
             ann = par("ann"), axes = TRUE, frame.plot = axes,
             panel.first = NULL, panel.last = NULL, asp = NA, ...)
{
    ## These col, bg, pch, cex can be vectors, so exclude them
    ## Also, axis and box accept some of these
    localAxis <- function(..., col, bg, pch, cex, lty, lwd) Axis(...)
    localBox <- function(..., col, bg, pch, cex, lty, lwd) box(...)
    localWindow <- function(..., col, bg, pch, cex, lty, lwd)
plot.window(...)
    localTitle <- function(..., col, bg, pch, cex, lty, lwd) title(...)
    if (!is.null(y)) {
        ## normal plot x against y 
        xlabel <- if (!missing(x)) deparse(substitute(x))
        ylabel <- deparse(substitute(y))
        xy <- xy.coords(x, y, xlabel, ylabel, log)
        xlab <- if (is.null(xlab)) xy$xlab else xlab
        ylab <- if (is.null(ylab)) xy$ylab else ylab
        xlim <- if (is.null(xlim)) range(xy$x[is.finite(xy$x)]) else
xlim
        ylim <- if (is.null(ylim)) range(xy$y[is.finite(xy$y)]) else
ylim
                
    } else {
        ## plot x on the vertical axis against index
        ## exchange given x* and y* attributes. One actually needs to
        ## exchange other attributes like xaxt/yaxt etc, but the same
flaw
        ## is in the original implementation
        xlabel <- "Index"
        ylabel <- if (!missing(x)) deparse(substitute(x))
        xy <- xy.coords(seq_along(x), x, "Index", ylabel, log)
        # if (!is.null(ylab)) warning("y is NULL, ylab will be ignored")
        ylab <- if (is.null(xlab)) xy$ylab else xlab
        xlab <- "Index"
        # if (!is.null(ylim)) warning("y is NULL, ylim is ignored")
        ylim <- if (is.null(xlim)) range(xy$y[is.finite(xy$y)]) else
xlim
        xlim <- range(xy$x[is.finite(xy$x)])
    }
    plot.new()
    localWindow(xlim, ylim, log, asp, ...)
    panel.first # eval() is wrong here {Ross I.}
    plot.xy(xy, type, ...)
    panel.last
    if (axes) {
    	localAxis(if(is.null(y)) xy$x else x, side = 1, ...)
    	localAxis(if(is.null(y))  x   else y, side = 2, ...)
    }
    if (frame.plot) localBox(...)
    if (ann) localTitle(main = main, sub = sub, xlab = xlab, ylab =
ylab, ...)
    invisible()
}

=================== diff
=====================================================
57,81c57,63
<     if (!is.null(y)) {
<         ## normal plot x against y
<         xlabel <- if (!missing(x)) deparse(substitute(x))
<         ylabel <- deparse(substitute(y))
<         xy <- xy.coords(x, y, xlabel, ylabel, log)
<         xlab <- if (is.null(xlab)) xy$xlab else xlab
<         ylab <- if (is.null(ylab)) xy$ylab else ylab
<         xlim <- if (is.null(xlim)) range(xy$x[is.finite(xy$x)]) else
xlim
<         ylim <- if (is.null(ylim)) range(xy$y[is.finite(xy$y)]) else
ylim
<
<     } else {
<         ## plot x on the vertical axis against index
<         ## exchange given x* and y* attributes. One actually needs to
<         ## exchange other attributes like xaxt/yaxt etc, but the same
flaw
<         ## is in the original implementation
<         xlabel <- "Index"
<         ylabel <- if (!missing(x)) deparse(substitute(x))
<         xy <- xy.coords(seq_along(x), x, "Index", ylabel, log)
<         # if (!is.null(ylab)) warning("y is NULL, ylab will be
ignored")
<         ylab <- if (is.null(xlab)) xy$ylab else xlab
<         xlab <- "Index"
<         # if (!is.null(ylim)) warning("y is NULL, ylim is ignored")
<         ylim <- if (is.null(xlim)) range(xy$y[is.finite(xy$y)]) else
xlim
<         xlim <- range(xy$x[is.finite(xy$x)])
<     }
---
>     xlabel <- if (!missing(x)) deparse(substitute(x))
>     ylabel <- if (!missing(y)) deparse(substitute(y))
>     xy <- xy.coords(x, y, xlabel, ylabel, log)
>     xlab <- if (is.null(xlab)) xy$xlab else xlab
>     ylab <- if (is.null(ylab)) xy$ylab else ylab
>     xlim <- if (is.null(xlim)) range(xy$x[is.finite(xy$x)]) else xlim
>     ylim <- if (is.null(ylim)) range(xy$y[is.finite(xy$y)]) else ylim
88,89c70,71
<       localAxis(if(is.null(y)) xy$x else x, side = 1, ...)
<       localAxis(if(is.null(y))  x   else y, side = 2, ...)
---
>       localAxis(xy$x, side = 1, ...)
>       localAxis(xy$y, side = 2, ...)


Dr Oleg Sklyar
Technology Group
Man Investments Ltd
+44 (0)20 7144 3803
osklyar at maninvestments.com


**********************************************************************
The contents of this email are for the named addressee(s) only.
It contains information which may be confidential and privileged.
If you are not the intended recipient, please notify the sender
immediately, destroy this email and any attachments and do not
otherwise disclose or use them. Email transmission is not a
secure method of communication and Man Investments cannot accept
responsibility for the completeness or accuracy of this email or
any attachments. Whilst Man Investments makes every effort to keep
its network free from viruses, it does not accept responsibility
for any computer virus which might be transferred by way of this
email or any attachments. This email does not constitute a request,
offer, recommendation or solicitation of any kind to buy, subscribe,
sell or redeem any investment instruments or to perform other such
transactions of any kind. Man Investments reserves the right to
monitor, record and retain all electronic communications through
its network to ensure the integrity of its systems, for record
keeping and regulatory purposes. 

Visit us at: www.maninvestments.com



More information about the R-devel mailing list