[Rd] graphics::Axis loosing S3/S4 class attributes of 'x' in 2.7.0 RC

Sklyar, Oleg (MI London) osklyar at maninvestments.com
Tue Apr 22 16:26:40 CEST 2008


Ok, so what's wrong with the following fix for plot(x) that would
actually fix what needs to be fixed instead of changing plot.default?
Fix means reverting plot.default in 2.7.0 to what it was (if testing in
2.7.0, copy and paste the OLD plot.default into the .GlobalEnv):

plot.POSIXct <- function(x, y, xlab = "", ...) {
    if (!missing(y)) {
        side = 1
        plotDef <- function(x, y, xaxt, xlab, ...) plot.default(x, y,
xaxt="n", xlab=xlab, ...)
        plotDef(x, y, xlab=xlab, ...)
    } else {
        side = 2
        plotDef <- function(x, y, yaxt, xlab, ...) plot.default(x, y,
yaxt="n", xlab=xlab, ...)
        plotDef(seq_along(x), x, xlab=xlab, ...)
    }
    ## trick to remove arguments intended for title() or plot.default()
    axisInt <- function(x, type, main, sub, xlab, ylab, col, lty, lwd,
                        xlim, ylim, bg, pch, log, asp, axes, frame.plot,
...)
        axis.POSIXct(side, x, ...)
    dots <- list(...)
    axes <- if("axes" %in% names(dots)) dots$axes else TRUE
    xaxt <- if("xaxt" %in% names(dots)) dots$xaxt else par("xaxt")
    if(axes && xaxt != "n") axisInt(x, ...)
}

plot.POSIXlt <- function(x, y, xlab = "", ...) {
    if (missing(y)) plot.POSIXct(as.POSIXct(x), xlab=xlab, ...)
    else plot.POSIXct(as.POSIXct(x), y=y, xlab=xlab, ...)
}

And try with:
x = Sys.time() + runif(100,1,7200)
plot(x)
plot(x,1:100)
plot(1:100,x)

plot(as.POSIXlt(x))
plot(as.POSIXlt(x),1:100)
plot(1:100,as.POSIXlt(x))


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

> -----Original Message-----
> From: Duncan Murdoch [mailto:murdoch at stats.uwo.ca] 
> Sent: 22 April 2008 14:24
> To: Sklyar, Oleg (MI London)
> Cc: R-devel at r-project.org
> Subject: Re: [Rd] graphics::Axis loosing S3/S4 class 
> attributes of 'x' in 2.7.0 RC
> 
> On 4/22/2008 9:08 AM, Sklyar, Oleg (MI London) wrote:
> > Duncan,
> > 
> > looking further, what has changed from 2.6.2 into 2.7.0 are the 
> > following two lines in plot.default, which I think were 
> logical before 
> > and are not really logical now:
> 
> I believe it is behaving as documented now, so the behaviour 
> is "logical", even if it may not be convenient.  In your example
> 
> x = Sys.time() + runif(100,1,7200) ## time over two hours, 
> POSIXct plot(x, 1:100) plot(1:100, x)
> 
> the 1st works in 2.6.2 and 2.7.0 and the second only works in 2.6.2. 
> But the change below was designed to fix the case
> 
> plot(x)
> 
> which works in 2.7.0 and *not* in 2.6.2, so reverting the 
> change is not the way to address this.
> 
> Duncan Murdoch
> 
> > 
> > plot.R: plot.default (2.6.2):
> > if (axes) {
> > 	localAxis(x, side=1, ...)
> > 	localAxis(y, side=2, ...)
> > }
> > 
> > plot.R: plot.default (2.7.0):
> > ...
> > if (axes) {
> > 	localAxis(xy$x, side=1, ...)
> > 	localAxis(xy$y, side=2, ...)
> > }
> > 
> > The fact that xy.coords is called does not really matter.
> > 
> > 
> > Dr Oleg Sklyar
> > Technology Group
> > Man Investments Ltd
> > +44 (0)20 7144 3803
> > osklyar at maninvestments.com
> > 
> >> -----Original Message-----
> >> From: Duncan Murdoch [mailto:murdoch at stats.uwo.ca]
> >> Sent: 22 April 2008 13:01
> >> To: Sklyar, Oleg (MI London)
> >> Cc: R-devel at r-project.org
> >> Subject: Re: [Rd] graphics::Axis loosing S3/S4 class attributes of 
> >> 'x' in 2.7.0 RC
> >> 
> >> On 22/04/2008 7:25 AM, Sklyar, Oleg (MI London) wrote:
> >> > Following my previous post on S3 method despatch, I put
> >> debug messages
> >> > in the code of Axis, Axis.default and plot.default in 
> >> > graphics/R/axis.R and graphics/R/plot.R to print the 
> class of x, at 
> >> > and y on plot. After recompiling R, what I see is that x 
> *lost* its 
> >> > class attribute (at least for classes not known to 
> 'graphics') in 
> >> > Axis, called directly from plot.default and this could be
> >> the reason
> >> > why R did not despatch on Axis.MyClass from my previous 
> post. This 
> >> > happens for both S3 and S4 classes as in the code below!
> >> Funny enough,
> >> > even "integer" was reset to numeric in Axis...
> >> 
> >> If you look at plot.default, you'll see it passes x and y through 
> >> xy.coords to get coordinates.  That function ends with
> >> 
> >> return(list(x=as.double(x), y=as.double(y), xlab=xlab, ylab=ylab))
> >> 
> >> so that's where classes get removed.  If you don't want this to 
> >> happen, shouldn't you be defining plot.MyClass, or calling the 
> >> default with axes=F, and then calling Axis on your object yourself?
> >> 
> >> > Is this really an intended behaviour? It looks very wrong to me!
> >> 
> >> This is documented:  ?plot.default tells you to look at ?xy.coords 
> >> for details of how x and y are handled, and xy.coords says "In any 
> >> other case, the 'x' argument is coerced to a vector and
> >>       returned as *y* component where the resulting 'x' is just the
> >>       index vector '1:n'.  In this case, the resulting 'xlab' 
> >> component
> >>       is set to '"Index"'."
> >> 
> >> Duncan Murdoch
> >> 
> >> > Thanks,
> >> > Oleg
> >> > 
> >> > *** R version 2.7.0 RC (2008-04-20 r45403)
> >> [/research/osklyar/R-devel]
> >> > ***
> >> >> Axis
> >> > function (x = NULL, at = NULL, ..., side, labels = NULL) {
> >> >     cat("In Axis() class(x)=", class(x), "; class(at)=", 
> class(at),
> >> >         "\n", sep = "")
> >> >     if (!is.null(x))
> >> >         UseMethod("Axis", x)
> >> >     else if (!is.null(at))
> >> >         UseMethod("Axis", at)
> >> >     else axis(side = side, at = at, labels = labels, ...) }
> >> > <environment: namespace:graphics>
> >> >> graphics:::Axis.default
> >> > function (x = NULL, at = NULL, ..., side, labels = NULL) {
> >> >     cat("In Axis.default() class(x)=", class(x), "; class(at)=",
> >> >         class(at), "\n", sep = "")
> >> >     if (is.null(at) && !is.null(x))
> >> >         at = pretty(x)
> >> >     axis(side = side, at = at, labels = labels, ...) }
> >> > <environment: namespace:graphics>
> >> >> setClass("MyClass", representation(smth="character"),
> >> > contains="numeric")
> >> > [1] "MyClass"
> >> >> a = new("MyClass", runif(10))
> >> >> a
> >> > An object of class "MyClass"
> >> >  [1] 0.773237167 0.548630205 0.987956687 0.212667925 0.337135151
> >> > 0.112210501
> >> >  [7] 0.007140895 0.972028903 0.443581963 0.536452424 Slot "smth":
> >> > character(0)
> >> >> plot(1:10,a)
> >> > In plot.default() class(x)=integer; class(y)=MyClass In Axis() 
> >> > class(x)=numeric; class(at)=NULL In Axis.default()
> >> class(x)=numeric;
> >> > class(at)=NULL In Axis() class(x)=numeric; class(at)=NULL In
> >> > Axis.default() class(x)=numeric; class(at)=NULL
> >> >> plot(a,1:10)
> >> > In plot.default() class(x)=MyClass; class(y)=integer In Axis() 
> >> > class(x)=numeric; class(at)=NULL In Axis.default()
> >> class(x)=numeric;
> >> > class(at)=NULL In Axis() class(x)=numeric; class(at)=NULL In
> >> > Axis.default() class(x)=numeric; class(at)=NULL
> >> >> b = runif(10)
> >> >> class(b)="AnotherClass"
> >> >> plot(b,1:10)
> >> > In plot.default() class(x)=AnotherClass; 
> class(y)=integer In Axis() 
> >> > class(x)=numeric; class(at)=NULL In Axis.default()
> >> class(x)=numeric;
> >> > class(at)=NULL In Axis() class(x)=numeric; class(at)=NULL In
> >> > Axis.default() class(x)=numeric; class(at)=NULL
> >> >> plot(1:10)
> >> > In plot.default() class(x)=integer; class(y)=NULL In Axis() 
> >> > class(x)=numeric; class(at)=NULL In Axis.default()
> >> class(x)=numeric;
> >> > class(at)=NULL In Axis() class(x)=numeric; class(at)=NULL In
> >> > Axis.default() class(x)=numeric; class(at)=NULL>
> >> >> sessionInfo()
> >> > R version 2.7.0 RC (2008-04-20 r45403) x86_64-unknown-linux-gnu
> >> > 
> >> > locale:
> >> > 
> >> 
> LC_CTYPE=en_GB.UTF-8;LC_NUMERIC=C;LC_TIME=en_GB.UTF-8;LC_COLLATE=C;LC
> >> _
> >> > MO
> >> > 
> >> 
> NETARY=C;LC_MESSAGES=en_GB.UTF-8;LC_PAPER=en_GB.UTF-8;LC_NAME=C;LC_AD
> >> D
> >> > RE
> >> SS=C;LC_TELEPHONE=C;LC_MEASUREMENT=en_GB.UTF-8;LC_IDENTIFICATION=C
> >> > 
> >> > attached base packages:
> >> > [1] stats     graphics  grDevices utils     datasets  
> methods   base
> >> > 
> >> > 
> >> > 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
> >> > 
> >> > ______________________________________________
> >> > R-devel at r-project.org mailing list
> >> > https://stat.ethz.ch/mailman/listinfo/r-devel
> >> 
> >> 
> 
> 



More information about the R-devel mailing list