[Rd] format: different S4 behavior in a package

2010-06-23 Thread Daniel Murphy
R-Devel-ers:

I have an S4 method that simply formats an object:

setGeneric("formatMe", function(x) standardGeneric("formatMe"))
setMethod("formatMe", "ANY", function(x) format(x))

If I issue the above in an R session, then define an S4 class with its own
format method, I get the desired result:

> setClass("A",contains="numeric")
[1] "A"
> setMethod("format","A", function(x, ...) "Hey Jude")
Creating a new generic function for "format" in ".GlobalEnv"
[1] "format"
> a<-new("A",1968)
> formatMe(a)
[1] "Hey Jude"


However, if I put the two "formatMe" definitions into a package ("Test"), I
do not get the desired result.


> library(Test)
> setClass("A",contains="numeric")
[1] "A"
> setMethod("format","A", function(x, ...) "Hey Jude")
Creating a new generic function for "format" in ".GlobalEnv"
[1] "format"
> a<-new("A",1968)
> formatMe(a)
[1] "1968"


The "disconnect" does not occur, however, if the S4 format method is an S3
incarnation:

> setClass("B",contains="numeric",S3methods=TRUE)
[1] "B"
> format.B <- function(x, ...) "Don't make it bad"
> b<-new("B",1968)
> formatMe(b)
[1] "Don't make it bad"

Could the problem be in Test's NAMESPACE file? There is only one line:
exportMethods(formatMe)

Here is Test's DESCRIPTION file:
Package: Test
Type: Package
Title: Testing format
Version: 1.0
Date: 2010-06-22
Author: Dan Murphy
Maintainer: Dan Murphy 
Depends: methods
Description: Does format in a package work with S4 format method?
License: GPL (>= 2)
LazyLoad: yes

(I would send the Help file, but I don't think that is the problem.)

I am using version 2.11.1 on a Windows Vista machine.

Any guidance would be appreciated. Thank you

Dan Murphy

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] format: different S4 behavior in a package

2010-06-23 Thread Daniel Murphy
Thank you, Martin. That worked. And fyi 'export(format)' alone was not
sufficient.
Best,
Dan

On Wed, Jun 23, 2010 at 5:15 AM, Martin Morgan  wrote:

> On 06/23/2010 12:16 AM, Daniel Murphy wrote:
> > R-Devel-ers:
> >
> > I have an S4 method that simply formats an object:
> >
> > setGeneric("formatMe", function(x) standardGeneric("formatMe"))
> > setMethod("formatMe", "ANY", function(x) format(x))
> >
> > If I issue the above in an R session, then define an S4 class with its
> own
> > format method, I get the desired result:
> >
> >> setClass("A",contains="numeric")
> > [1] "A"
> >> setMethod("format","A", function(x, ...) "Hey Jude")
> > Creating a new generic function for "format" in ".GlobalEnv"
> > [1] "format"
> >> a<-new("A",1968)
> >> formatMe(a)
> > [1] "Hey Jude"
> >
> >
> > However, if I put the two "formatMe" definitions into a package ("Test"),
> I
> > do not get the desired result.
> > 
> >
> >> library(Test)
> >> setClass("A",contains="numeric")
> > [1] "A"
> >> setMethod("format","A", function(x, ...) "Hey Jude")
> > Creating a new generic function for "format" in ".GlobalEnv"
>
> This is the clue -- you're creating a new S4 generic, so there's a
> base::format, and a .GlobalEnv::format. Test::formatMe respects its name
> space, and sees base::format.
>
> In the S3 case, base::format is already an S3 generic, and you're just
> adding a method, so there's only base::format for everyone to find.
>
> In Test, you could setGeneric(format) and then export(format). It might
> also be enough to just export(format); I'm not sure.
>
> Martin
>
> > [1] "format"
> >> a<-new("A",1968)
> >> formatMe(a)
> > [1] "1968"
> >
> >
> > The "disconnect" does not occur, however, if the S4 format method is an
> S3
> > incarnation:
> >
> >> setClass("B",contains="numeric",S3methods=TRUE)
> > [1] "B"
> >> format.B <- function(x, ...) "Don't make it bad"
> >> b<-new("B",1968)
> >> formatMe(b)
> > [1] "Don't make it bad"
> >
> > Could the problem be in Test's NAMESPACE file? There is only one line:
> > exportMethods(formatMe)
> >
> > Here is Test's DESCRIPTION file:
> > Package: Test
> > Type: Package
> > Title: Testing format
> > Version: 1.0
> > Date: 2010-06-22
> > Author: Dan Murphy
> > Maintainer: Dan Murphy 
> > Depends: methods
> > Description: Does format in a package work with S4 format method?
> > License: GPL (>= 2)
> > LazyLoad: yes
> >
> > (I would send the Help file, but I don't think that is the problem.)
> >
> > I am using version 2.11.1 on a Windows Vista machine.
> >
> > Any guidance would be appreciated. Thank you
> >
> > Dan Murphy
> >
> >   [[alternative HTML version deleted]]
> >
> > __
> > R-devel@r-project.org mailing list
> > https://stat.ethz.ch/mailman/listinfo/r-devel
>
>
> --
> Martin Morgan
> Computational Biology / Fred Hutchinson Cancer Research Center
> 1100 Fairview Ave. N.
> PO Box 19024 Seattle, WA 98109
>
> Location: Arnold Building M1 B861
> Phone: (206) 667-2793
>

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


[Rd] Attributes of 1st argument in ...

2010-07-02 Thread Daniel Murphy
R-Devel:

I am trying to get an attribute of the first argument in a call to a
function whose formal arguments consist of dots only and do something, e.g.,
call 'cbind', based on the attribute
f<- function(...) {get first attribute; maybe or maybe not call 'cbind'}

I thought of (ignoring "deparse.level" for the moment)

f<-function(...) {x <- attr(list(...)[[1L]], "foo"); if (x=="bar")
cbind(...) else x}

but I feared my solution might do some extra copying, with a performance
penalty if the dotted objects in the actual call to "f' are very large.

I thought the following alternative might avoid a potential performance hit
by evaluating the attribute in the parent.frame (and therefore avoid extra
copying?):

f<-function(...)
{
   L<-match.call(expand.dots=FALSE)[[2L]]
   x <- eval(substitute(attr(x,"foo"), list(x=L[[1L]])))
   if (x=="bar") cbind(...) else x
}

system.time tests showed this second form to be only marginally faster.

Is my fear about extra copying unwarranted? If not, is there a better way to
get the "foo" attribute of the first argument other than my two
alternatives?

Thanks,
Dan Murphy

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] Attributes of 1st argument in ...

2010-07-03 Thread Daniel Murphy
Hi Hadley,

My actual goal is to have a cbind method in the mondate package that behaves
just like the base cbind function: class and shape of the result, names,
etc. Perhaps it's due to the fact that 'cbind' uses its own internal
dispatching, but I have not found a way to implement a "true" S3-style cbind
method. (This is probably ancient news to the development team.) An S4 cbind
method will utilize callNextMethod with just setGeneric("cbind"), which has
no 'x' in the formal arguments. With no 'x', there's no "first argument" on
which to dispatch a "mondate" method. I can make the cbind of mondates also
be a mondate with an all-encompassing setMethod("cbind","ANY", etc) method,
but that wrests dispatch control from cbind which makes no sense whatsoever.
 So, to make a long story even longer, I settled for a "cbindmondate
function" that utilizes the speed of base::cbind and (with one exception)
gives me the hoped-for "base cbind behavior."

I can send examples of my trial-and-error attempts under separate email if
you're interested.

Best regards,
Dan

On Sat, Jul 3, 2010 at 9:17 AM, Hadley Wickham  wrote:

> Hi Dan,
>
> Is there a reason you can't change the function to
>
> f <- function(x, ...) {}
>
> ?
>
> Hadley
>
> On Fri, Jul 2, 2010 at 4:26 PM, Daniel Murphy 
> wrote:
> > R-Devel:
> >
> > I am trying to get an attribute of the first argument in a call to a
> > function whose formal arguments consist of dots only and do something,
> e.g.,
> > call 'cbind', based on the attribute
> > f<- function(...) {get first attribute; maybe or maybe not call 'cbind'}
> >
> > I thought of (ignoring "deparse.level" for the moment)
> >
> > f<-function(...) {x <- attr(list(...)[[1L]], "foo"); if (x=="bar")
> > cbind(...) else x}
> >
> > but I feared my solution might do some extra copying, with a performance
> > penalty if the dotted objects in the actual call to "f' are very large.
> >
> > I thought the following alternative might avoid a potential performance
> hit
> > by evaluating the attribute in the parent.frame (and therefore avoid
> extra
> > copying?):
> >
> > f<-function(...)
> > {
> >   L<-match.call(expand.dots=FALSE)[[2L]]
> >   x <- eval(substitute(attr(x,"foo"), list(x=L[[1L]])))
> >   if (x=="bar") cbind(...) else x
> > }
> >
> > system.time tests showed this second form to be only marginally faster.
> >
> > Is my fear about extra copying unwarranted? If not, is there a better way
> to
> > get the "foo" attribute of the first argument other than my two
> > alternatives?
> >
> > Thanks,
> > Dan Murphy
> >
> >[[alternative HTML version deleted]]
> >
> > __
> > R-devel@r-project.org mailing list
> > https://stat.ethz.ch/mailman/listinfo/r-devel
> >
>
>
>
> --
> Assistant Professor / Dobelman Family Junior Chair
> Department of Statistics / Rice University
> http://had.co.nz/
>

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] Attributes of 1st argument in ...

2010-07-04 Thread Daniel Murphy
Thank you, Professor, for drawing my attention to the nifty tracemem
function. I'm using the ..1 syntax to check the properties of the S4 class
at function call.

The Description at ?"cBind" tells me that I'm not alone in this predicament.
Just as Matrix needs its own cBind function, my package will need its own
cbindMondate function. Alas, subclasses of mondate will also need their own
binding functions, thus defeating one of the purposes of the class paradigm
(for binding, anyway).

As an aside, I wonder why, on around line 75, cBind uses 'rep.int("",
ncol(r))' rather than the slightly faster 'character(ncol(r))'.

Thanks again,
Dan

On Sun, Jul 4, 2010 at 4:36 AM, Prof Brian Ripley wrote:

> I think you have missed the use of ..1 etc: see e.g. cBind() in package
> Matrix.
>
> So x <- attr(list(...)[[1L]], "foo") can be x <- attr(..1, "foo")
>
> As for 'extra copying', it all depends on exactly what you are doing, but
> compare
>
>  foo1 <- function(...) length(..1)
>> foo2 <- function(...) length(list(...)[[1L]])
>> tracemem(x <- runif(1000))
>>
> [1] "<0x1b27800>"
>
>> foo1(x)
>>
> [1] 1000
>
>> tracemem(x <- runif(1000))
>>
> [1] "<0x1b29800>"
>
>> foo2(x)
>>
> tracemem[0x1b29800 -> 0x10a2200]: foo2
> [1] 1000
>
>
>
> 
> --
> Brian D. Ripley,  rip...@stats.ox.ac.uk
> Professor of Applied Statistics,  http://www.stats.ox.ac.uk/~ripley/
> University of Oxford, Tel:  +44 1865 272861 (self)
> 1 South Parks Road, +44 1865 272866 (PA)
> Oxford OX1 3TG, UKFax:  +44 1865 272595
>

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] Attributes of 1st argument in ...

2010-07-05 Thread Daniel Murphy
I truly am grateful for all the help.

I never would have thought defining a class union for objects that can be
combined with cbind, as you do in Rmpfr. That does the trick.

Is it true that the only difference in behavior between the S4 cbind and
base::cbind is that, unlike base::cbind, the S4 cbind does not seem to know
the symbol of unnamed arguments? E.g.,
x<-mpfr(0:7,100)
cbind(x,x)
If so, that seems a small price to pay for the S4 functionality.

Thanks again.

Cheers,
Dan

On Mon, Jul 5, 2010 at 2:47 AM, Martin Maechler
wrote:

> >>>>> "DM" == Daniel Murphy 
> >>>>> on Sun, 4 Jul 2010 11:11:43 -0700 writes:
>
>DM> Thank you, Professor, for drawing my attention to the nifty tracemem
>DM> function. I'm using the ..1 syntax to check the properties of the S4
> class
>DM> at function call.
>
>DM> The Description at ?"cBind" tells me that I'm not alone in this
> predicament.
>
>
>DM> Just as Matrix needs its own cBind function, my package will need
> its own
>DM> cbindMondate function. Alas, subclasses of mondate will also need
> their own
>DM> binding functions, thus defeating one of the purposes of the class
> paradigm
>DM> (for binding, anyway).
>
> I don't think you see the full picture:
>
> Matrix::cBind() builds on methods::cbind2()
>
> and cbind2 / rbind2  are there (in package methods) for you to
> use setMethod() on them.
>
> BTW: When Matrix::cBind() -- and cbind2 / rbind2 in package
> methods were written,
>
> R did not have the possibility yet to write methods for "...",
> which it now does.
>
> In the package Rmpfr (arbitrary-precision number ["mpfr"] computing),
> where I also define methods for matrices of such "mpfr" numbers
> (classes "mpfrMatrix" and "mpfrArray"),
> I use the new feature of defining methods for "..." :
>
> setGeneric("cbind", signature = "...")
>
> setMethod("cbind", "Mnumber",
>  function(..., deparse.level = 1) {
>  args <- list(...)
>  if(all(sapply(args, is.atomic)))
>  return( base::cbind(..., deparse.level = deparse.level) )
>  ## else: at least one is "mpfr(Matrix/Array)"
>
>  if(any(sapply(args, is.character))) {
>  ## result will be   matrix !
>  isM <- sapply(args, is, class2 = "mpfr")
>  args[isM] <- lapply(args[isM], as, Class = "character")
>  return(do.call(base::cbind,
> c(args,
> list(deparse.level=deparse.level
>
>  } else if(any(sapply(args, is.complex))) {
>  ## result will be   matrix;
>  ## in the future   ???
>
>  stop("cbind(...) of 'complex' and 'mpfr' objects is not
> implemented")
>  ## give at least warning !!
>  }
>  ## else
>
> ..
> ..
>  })
>
>
> where I use a useful class union
>
>  setClassUnion("Mnumber",
>members = c("array_or_vector", # *but* must be numeric-like
>"mpfr", "mpfrArray", "mpfrMatrix"))
>
> 
>
> As always, I'd recommend to read the R source, rather than just
> investigate the installed package.
> You can get the *source* tarbal, i.e., the *.tar.gz file from
> CRAN, or, as it's all on R-forge,
> http://rmpfr.r-forge.r-project.org/
> you can get the source tarball here,
>   https://r-forge.r-project.org/R/?group_id=386
> or browse the source at
>   https://r-forge.r-project.org/scm/viewvc.php/pkg/?root=rmpfr
>
> But if I were you I'd get it via
>   svn checkout svn://svn.r-forge.r-project.org/svnroot/rmpfr/pkg Rmpfr
>
>
>
>DM> As an aside, I wonder why, on around line 75, cBind uses 'rep.int
> ("",
>DM> ncol(r))' rather than the slightly faster 'character(ncol(r))'.
>
> Well, I would not remember, but the first one is a more self-explaining,
> ... and I would guess strongly that time difference is
> irrelevant in the context where it's used...
> ... but then thanks for your hint :-)
>
> Martin
>
> 

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] Attributes of 1st argument in ...

2010-07-05 Thread Daniel Murphy
I stand corrected. It is possible for the S4 cbind to know the symbol of
unnamed arguments, by "cheating": colnames(base::cbind(...,deparse.level =
deparse.level)) -- which tells me that there ought to be a non-cheating way.

I note that the Rmpfr class union, Mnumber, means that the simple cbind(1:3)
must go through the S4 cbind. Now I know why your method, Martin, tests for
all is.atomic at the beginning (which will not work for mondates, which test
TRUE). This actually increases the price of an S4 cbind, a price increase
that I believe could be avoided if S4 dispatch on dots occurred based on the
first argument, which is back to my original post. I'm guessing that's too
difficult to implement.

Again, thanks to everyone for your time in schooling me on the issues. :-)

Dan

On Mon, Jul 5, 2010 at 10:35 PM, Daniel Murphy wrote:

> I truly am grateful for all the help.
>
> I never would have thought defining a class union for objects that can be
> combined with cbind, as you do in Rmpfr. That does the trick.
>
> Is it true that the only difference in behavior between the S4 cbind and
> base::cbind is that, unlike base::cbind, the S4 cbind does not seem to know
> the symbol of unnamed arguments? E.g.,
> x<-mpfr(0:7,100)
> cbind(x,x)
> If so, that seems a small price to pay for the S4 functionality.
>
> Thanks again.
>
> Cheers,
> Dan
>
> On Mon, Jul 5, 2010 at 2:47 AM, Martin Maechler <
> maech...@stat.math.ethz.ch> wrote:
>
>> >>>>> "DM" == Daniel Murphy 
>> >>>>> on Sun, 4 Jul 2010 11:11:43 -0700 writes:
>>
>>DM> Thank you, Professor, for drawing my attention to the nifty
>> tracemem
>>DM> function. I'm using the ..1 syntax to check the properties of the
>> S4 class
>>DM> at function call.
>>
>>DM> The Description at ?"cBind" tells me that I'm not alone in this
>> predicament.
>>
>>
>>DM> Just as Matrix needs its own cBind function, my package will need
>> its own
>>DM> cbindMondate function. Alas, subclasses of mondate will also need
>> their own
>>DM> binding functions, thus defeating one of the purposes of the class
>> paradigm
>>DM> (for binding, anyway).
>>
>> I don't think you see the full picture:
>>
>> Matrix::cBind() builds on methods::cbind2()
>>
>> and cbind2 / rbind2  are there (in package methods) for you to
>> use setMethod() on them.
>>
>> BTW: When Matrix::cBind() -- and cbind2 / rbind2 in package
>> methods were written,
>>
>> R did not have the possibility yet to write methods for "...",
>> which it now does.
>>
>> In the package Rmpfr (arbitrary-precision number ["mpfr"] computing),
>> where I also define methods for matrices of such "mpfr" numbers
>> (classes "mpfrMatrix" and "mpfrArray"),
>> I use the new feature of defining methods for "..." :
>>
>> setGeneric("cbind", signature = "...")
>>
>> setMethod("cbind", "Mnumber",
>>  function(..., deparse.level = 1) {
>>  args <- list(...)
>>  if(all(sapply(args, is.atomic)))
>>  return( base::cbind(..., deparse.level = deparse.level) )
>>  ## else: at least one is "mpfr(Matrix/Array)"
>>
>>  if(any(sapply(args, is.character))) {
>>  ## result will be   matrix !
>>  isM <- sapply(args, is, class2 = "mpfr")
>>  args[isM] <- lapply(args[isM], as, Class = "character")
>>  return(do.call(base::cbind,
>> c(args,
>> list(deparse.level=deparse.level
>>
>>  } else if(any(sapply(args, is.complex))) {
>>  ## result will be   matrix;
>>  ## in the future   ???
>>
>>  stop("cbind(...) of 'complex' and 'mpfr' objects is not
>> implemented")
>>  ## give at least warning !!
>>  }
>>  ## else
>>
>> ..
>> ..
>>  })
>>
>>
>> where I use a useful class union
>>
>>  setClassUnion("Mnumber",
>>members = c("array_or_vector", # *but* must be numeric-like
>>"mpfr", "mpfrArray", "mpfrMatrix"))
>>
>> 
>>
>> As always, I'd recommend

[Rd] S4 class extends "data.frame", getDataPart sees "list"

2010-07-11 Thread Daniel Murphy
R-Devel:

When I get the data part of an S4 class that contains="data.frame", it gives
me a list, even when the "data.frame" is the S4 version:

> d<-data.frame(x=1:3)
> isS4(d)
[1] FALSE   # of course
> dS4<-new("data.frame",d)
> isS4(dS4)
[1] TRUE# ok
> class(dS4)
[1] "data.frame"   # good
attr(,"package")
[1] "methods"
> setClass("A", representation(label="character"), contains="data.frame")
[1] "A"
> a<-new("A",dS4, label="myFrame")
> getDataPart(a)
[[1]]  # oh?
[1] 1 2 3

> class(a...@.data)
[1] "list"   # hmm
> names(a)
[1] "x" # sure, that makes sense
> a
Object of class "A"
  x
1 1
2 2
3 3
Slot "label":
[1] "myFrame"


Was I wrong to have expected the "data part" of 'a' to be a "data.frame"?

Thanks.

Dan Murphy

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] S4 class extends "data.frame", getDataPart sees "list"

2010-07-13 Thread Daniel Murphy
Thank you. For "getDataPart" I was following (my interpretation of) advice
from the documentation for "Classes": The functions
getDataPart<http://127.0.0.1:15455/library/methods/help/getDataPart>
 and setDataPart <http://127.0.0.1:15455/library/methods/help/setDataPart> are
a cleaner, but essentially equivalent way to deal with the data part.
I interpreted "cleaner" to mean "preferred." From your reply, John, it
sounds like I should go back to the obj...@.data construct.
-Dan
On Tue, Jul 13, 2010 at 5:57 AM, John Chambers  wrote:

> On 7/11/10 9:08 PM, Daniel Murphy wrote:
>
>> R-Devel:
>>
>> When I get the data part of an S4 class that contains="data.frame", it
>> gives
>> me a list, even when the "data.frame" is the S4 version:
>>
>>  d<-data.frame(x=1:3)
>>> isS4(d)
>>>
>> [1] FALSE   # of course
>>
>>> dS4<-new("data.frame",d)
>>> isS4(dS4)
>>>
>> [1] TRUE# ok
>>
>>> class(dS4)
>>>
>> [1] "data.frame"   # good
>> attr(,"package")
>> [1] "methods"
>>
>>> setClass("A", representation(label="character"), contains="data.frame")
>>>
>> [1] "A"
>>
>>> a<-new("A",dS4, label="myFrame")
>>> getDataPart(a)
>>>
>> [[1]]  # oh?
>> [1] 1 2 3
>>
>>  class(a...@.data)
>>>
>> [1] "list"   # hmm
>>
>>> names(a)
>>>
>> [1] "x" # sure, that makes sense
>>
>>> a
>>>
>> Object of class "A"
>>   x
>> 1 1
>> 2 2
>> 3 3
>> Slot "label":
>> [1] "myFrame"
>>
>>
>> Was I wrong to have expected the "data part" of 'a' to be a "data.frame"?
>>
>
> Yes.  Also, there is a clue in the documentation for getDataPart: "rarely
> suitable to be called directly"
> The data part, aka "data slot", generally does not have a class (S4 or S3).
>
> You are probably looking for S3Part():
>
> > setClass("myFrame", contains = "data.frame")
> [1] "myFrame"
> > z = new("myFrame", data.frame(x=1:3))
> > z
> Object of class "myFrame"
>
>  x
> 1 1
> 2 2
> 3 3
> > S3Part(z)
> Object of class "data.frame"
>
>  x
> 1 1
> 2 2
> 3 3
> > S3Part(z, strictS3 = TRUE)
>
>  x
> 1 1
> 2 2
> 3 3
>
>
>
>
>> Thanks.
>>
>> Dan Murphy
>>
>>[[alternative HTML version deleted]]
>>
>> __
>> R-devel@r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-devel
>>
>>

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] S4 class extends "data.frame", getDataPart sees "list"

2010-07-13 Thread Daniel Murphy
OK, I see. Thanks.
-Dan

On Tue, Jul 13, 2010 at 9:11 AM, John Chambers  wrote:

>
> On 7/13/10 8:43 AM, Daniel Murphy wrote:
>
>> Thank you. For "getDataPart" I was following (my interpretation of)
>> advice from the documentation for "Classes": The functions |getDataPart
>> <http://127.0.0.1:15455/library/methods/help/getDataPart>| and
>> |setDataPart <http://127.0.0.1:15455/library/methods/help/setDataPart>|
>>
>> are a cleaner, but essentially equivalent way to deal with the data part.
>> I interpreted "cleaner" to mean "preferred." From your reply, John, it
>> sounds like I should go back to the obj...@.data construct.
>>
>
> No, that's not the distinction.  Preferred for what, is the question. In
> order for a class to extend a basic type, it has to have that type. Then the
> .Data "slot" is a sort of fiction needed for the metadata.
> (Because of some "features" of R implementation, it's not quite that
> simple.  Matrices act like a basic type, and some types, such as
> "environment" require a second kludge.)
>
>
> If you really want that slot, the advice holds, but only because there is
> no actual ".Data" slot (i.e., attribute).
>
> But you weren't talking about that at all.  In fact (just to contradict my
> previous mail) you probably wanted to turn your object into a data.frame.
>  If so, best to say so:
>
> > as(z, "data.frame")
>
> Object of class "data.frame"
>  x
> 1 1
> 2 2
> 3 3
>
> and, for that matter:
>
> > as(z, "list")
> [[1]]
> [1] 1 2 3
>
>  -Dan
>> On Tue, Jul 13, 2010 at 5:57 AM, John Chambers > <mailto:j...@r-project.org>> wrote:
>>
>>On 7/11/10 9:08 PM, Daniel Murphy wrote:
>>
>>R-Devel:
>>
>>When I get the data part of an S4 class that
>>contains="data.frame", it gives
>>me a list, even when the "data.frame" is the S4 version:
>>
>>d<-data.frame(x=1:3)
>>isS4(d)
>>
>>[1] FALSE   # of course
>>
>>dS4<-new("data.frame",d)
>>isS4(dS4)
>>
>>[1] TRUE# ok
>>
>>class(dS4)
>>
>>[1] "data.frame"   # good
>>attr(,"package")
>>[1] "methods"
>>
>>setClass("A", representation(label="character"),
>>contains="data.frame")
>>
>>[1] "A"
>>
>>a<-new("A",dS4, label="myFrame")
>>getDataPart(a)
>>
>>[[1]]  # oh?
>>[1] 1 2 3
>>
>>class(a...@.data)
>>
>>[1] "list"   # hmm
>>
>>names(a)
>>
>>[1] "x" # sure, that makes sense
>>
>>a
>>
>>Object of class "A"
>>   x
>>1 1
>>2 2
>>3 3
>>Slot "label":
>>[1] "myFrame"
>>
>>
>>Was I wrong to have expected the "data part" of 'a' to be a
>>"data.frame"?
>>
>>
>>Yes.  Also, there is a clue in the documentation for getDataPart:
>>"rarely suitable to be called directly"
>>The data part, aka "data slot", generally does not have a class (S4
>>or S3).
>>
>>You are probably looking for S3Part():
>>
>> > setClass("myFrame", contains = "data.frame")
>>[1] "myFrame"
>> > z = new("myFrame", data.frame(x=1:3))
>> > z
>>Object of class "myFrame"
>>
>>  x
>>1 1
>>2 2
>>3 3
>> > S3Part(z)
>>Object of class "data.frame"
>>
>>  x
>>1 1
>>2 2
>>3 3
>> > S3Part(z, strictS3 = TRUE)
>>
>>  x
>>1 1
>>2 2
>>3 3
>>
>>
>>
>>
>>Thanks.
>>
>>Dan Murphy
>>
>>[[alternative HTML version deleted]]
>>
>>__
>>R-devel@r-project.org <mailto:R-devel@r-project.org> mailing list
>>
>>https://stat.ethz.ch/mailman/listinfo/r-devel
>>
>>
>>

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


[Rd] Extract callNextMethod "array" calls "matrix"?

2010-07-20 Thread Daniel Murphy
I have a class that extends array and my method for "[" stops with an error:

> setClass("A", contains="array")
[1] "A"
> setMethod("[", "A", function(x, i, j, ..., drop = TRUE) new("A",
callNextMethod()))
[1] "["
> a<-new("A",array(1:12,c(4,3,1)))
> a
An object of class "A"
, , 1

 [,1] [,2] [,3]
[1,]159
[2,]26   10
[3,]37   11
[4,]48   12

> a[1:2,2:3,1]
Error in x[i = i, j = j, NULL, ...] : incorrect number of dimensions
Error in callNextMethod() : error in evaluating a 'primitive' next method
>

A similar error does not occur when extending a matrix:
> setClass("M", contains="matrix")
[1] "M"
> setMethod("[", "M", function(x, i, j, ..., drop = TRUE) new("M",
callNextMethod()))
[1] "["
> a<-new("M",matrix(1:12,4,3))
> a[1:2,2:3]
An object of class "M"
 [,1] [,2]
[1,]59
[2,]6   10
>

Is there a problem with my method definition for the array-extending class?

My work-around is as follows:
> setMethod("[", "A", function(x, i, j, ..., drop = TRUE) new("A",
`[`(as(x,"array"), i=i, j=j, ..., drop=drop)))
[1] "["
> a[1:2,2:3,1]
An object of class "A"
 [,1] [,2]
[1,]59
[2,]6   10
>

Cheers,
Dan

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] Extract callNextMethod "array" calls "matrix"?

2010-07-21 Thread Daniel Murphy
Thanks, John. Enjoy Gaithersburg!

On Wed, Jul 21, 2010 at 8:58 AM, John Chambers  wrote:

> There does indeed seem to be a bug in the C code that implements
> callNextMethod, with the effect of adding a spurious index to calls to the
> primitive `[` code with more than 2 subscripts.
>
> The message "incorrect number of dimensions" is telling the truth, the
> primitive code gets 4 subscripts instead of 3 (note the "x[i = i, j = j,
> NULL, ...]" in the error message).
>
> Given the time of year, meetings, and the obscurity of this piece of code,
> the bug won't likely be fixed soon, so any workaround that avoids the use of
> callNextMethod on `[` with 3 or more subscripts is a good idea.
>
>
> On 7/20/10 1:41 PM, Daniel Murphy wrote:
>
>> I have a class that extends array and my method for "[" stops with an
>> error:
>>
>>  setClass("A", contains="array")
>>>
>> [1] "A"
>>
>>> setMethod("[", "A", function(x, i, j, ..., drop = TRUE) new("A",
>>>
>> callNextMethod()))
>> [1] "["
>>
>>> a<-new("A",array(1:12,c(4,3,1)))
>>> a
>>>
>> An object of class "A"
>> , , 1
>>
>>  [,1] [,2] [,3]
>> [1,]159
>> [2,]26   10
>> [3,]37   11
>> [4,]48   12
>>
>>  a[1:2,2:3,1]
>>>
>> Error in x[i = i, j = j, NULL, ...] : incorrect number of dimensions
>> Error in callNextMethod() : error in evaluating a 'primitive' next method
>>
>>>
>>>
>> A similar error does not occur when extending a matrix:
>>
>>> setClass("M", contains="matrix")
>>>
>> [1] "M"
>>
>>> setMethod("[", "M", function(x, i, j, ..., drop = TRUE) new("M",
>>>
>> callNextMethod()))
>> [1] "["
>>
>>> a<-new("M",matrix(1:12,4,3))
>>> a[1:2,2:3]
>>>
>> An object of class "M"
>>  [,1] [,2]
>> [1,]59
>> [2,]6   10
>>
>>>
>>>
>> Is there a problem with my method definition for the array-extending
>> class?
>>
>> My work-around is as follows:
>>
>>> setMethod("[", "A", function(x, i, j, ..., drop = TRUE) new("A",
>>>
>> `[`(as(x,"array"), i=i, j=j, ..., drop=drop)))
>> [1] "["
>>
>>> a[1:2,2:3,1]
>>>
>> An object of class "A"
>>  [,1] [,2]
>> [1,]59
>> [2,]6   10
>>
>>>
>>>
>> Cheers,
>> Dan
>>
>>[[alternative HTML version deleted]]
>>
>> __
>> R-devel@r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-devel
>>
>>

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


[Rd] Incorrect formatted output after subtracting non-integer seconds from POSIXt origin

2010-09-03 Thread Daniel Murphy
> x<-as.POSIXct("1970-1-1", tz="UTC")-.5
> y<-as.POSIXct("1970-1-1", tz="UTC")+.5
> x==y
[1] FALSE  # of course
but x and y "appear" to be the same when formatted, even with extra
precision:
> format(x, format="%Y-%m-%d %H:%M:%OS2")
[1] "1970-01-01 00:00:00.50"
> format(y, format="%Y-%m-%d %H:%M:%OS2")
[1] "1970-01-01 00:00:00.50"

Formatted output is fine for integral difference points ...
> x<-as.POSIXct("1970-1-1", tz="UTC")-1
> y<-as.POSIXct("1970-1-1", tz="UTC")+1
> format(x, format="%Y-%m-%d %H:%M:%OS2")
[1] "1969-12-31 23:59:59.00"
> format(y, format="%Y-%m-%d %H:%M:%OS2")
[1] "1970-01-01 00:00:01.00"

... but seems to be a second "off" for non-integers:
> format(as.POSIXct("1970-1-1", tz="UTC")-1.5, format="%Y-%m-%d %H:%M:%OS2")
[1] "1969-12-31 23:59:59.50"   # a second later than expected
> format(as.POSIXct("1970-1-1", tz="UTC")-86400, format="%Y-%m-%d
%H:%M:%OS2")
[1] "1969-12-31 00:00:00.00"   # OK
> format(as.POSIXct("1970-1-1", tz="UTC")-86400.5, format="%Y-%m-%d
%H:%M:%OS2")
[1] "1969-12-31 00:00:00.50"   # why "after" previous time?

Bug, or user misunderstanding?
"R version 2.11.1 (2010-05-31)" on Windows
Thanks.
Dan Murphy

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] Incorrect formatted output after subtracting non-integer seconds from POSIXt origin

2010-09-03 Thread Daniel Murphy
Thanks. Yes, negative POSIX time would correspond to dates prior to
1970-1-1, or to dates prior to a more recent origin that borrows
functionality from the POSIXt class: as.POSIXct(-.5,
origin=as.POSIXct("2011-1-1")).


>
> If negative POSIX time is supposed to work then it's a bug in as.POSIXlt().
> Now fixed in R-devel (and patched).
>
> Cheers,
> Simon
>
>
> before:
> > str(unclass(as.POSIXlt(as.POSIXct("1970-1-1", tz="UTC")-0.2)))
> List of 9
>  $ sec  : num 0.8
>  $ min  : int 0
>  $ hour : int 0
>  $ mday : int 1
>  $ mon  : int 0
>  $ year : int 70
>  $ wday : int 4
>  $ yday : int 0
>  $ isdst: int 0
>  - attr(*, "tzone")= chr "UTC"
>
> R-devel:
> > str(unclass(as.POSIXlt(as.POSIXct("1970-1-1", tz="UTC")-0.2)))
> List of 9
>  $ sec  : num 59.8
>  $ min  : int 59
>  $ hour : int 23
>  $ mday : int 31
>  $ mon  : int 11
>  $ year : int 69
>  $ wday : int 3
>  $ yday : int 364
>  $ isdst: int 0
>  - attr(*, "tzone")= chr "UTC"
>
>
>
>
> > "R version 2.11.1 (2010-05-31)" on Windows
> > Thanks.
> > Dan Murphy
> >
> >   [[alternative HTML version deleted]]
> >
> > __
> > R-devel@r-project.org mailing list
> > https://stat.ethz.ch/mailman/listinfo/r-devel
> >
> >
>
>

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


[Rd] Help in 2.10 lost its "Find" feature

2009-11-11 Thread Daniel Murphy
Sirs:

I understand that no one wanted to maintain the old Help, but one feature I
used extensively -- as a newbie to R or to an unfamiliar package -- was the
capability of searching for a word or phrase on the Help page itself.
Ctrl-F/Command-F (Windows/mac) 'differently-phrased-capability' was a fast
way to find out how to specify the arguments for a function call to
accommodate a "capability" phrased differently than could be found in the
author's designed argument list, especially for long and informative Help's.
If new-Help could easily be enhanced to resurrect that feature, I believe
many users would appreciate it. Thanks.

Dan Murphy

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] Help in 2.10 lost its "Find" feature

2009-11-11 Thread Daniel Murphy
That did it. Was having trouble searching 'help' for how to optionally
configure 'help'. Thanks.
-Dan

On Wed, Nov 11, 2009 at 8:57 AM, Henrik Bengtsson wrote:

> For the text based help, there is no search feature on Windows, e.g.
>
> options(help_type="text");
> help(readLines);
>
> but if you use the HTML-based help, you can use the browser's search
> features as suggested/wanted:
>
> options(help_type="html");
> help(readLines);
>
> /Henrik
>
>
> On Wed, Nov 11, 2009 at 5:40 PM, hadley wickham 
> wrote:
> >> I understand that no one wanted to maintain the old Help, but one
> feature I
> >> used extensively -- as a newbie to R or to an unfamiliar package -- was
> the
> >> capability of searching for a word or phrase on the Help page itself.
> >> Ctrl-F/Command-F (Windows/mac) 'differently-phrased-capability' was a
> fast
> >> way to find out how to specify the arguments for a function call to
> >> accommodate a "capability" phrased differently than could be found in
> the
> >> author's designed argument list, especially for long and informative
> Help's.
> >> If new-Help could easily be enhanced to resurrect that feature, I
> believe
> >> many users would appreciate it. Thanks.
> >
> > Most browsers offer this feature - it certainly works in safari and
> > firefox, and I'm sure in internet explorer too.
> >
> > Hadley
> >
> > --
> > http://had.co.nz/
> >
> > __
> > R-devel@r-project.org mailing list
> > https://stat.ethz.ch/mailman/listinfo/r-devel
> >
>

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


[Rd] choose.files() latent highlighting in console

2009-12-09 Thread Daniel Murphy
Greetings,

When I call choose.files() from within a Windows (Vista or XP) Rgui.exe
(2.10.0) session and double-click my choice, a large section of the text in
the 'R Console' window appears as "selected" (highlighted in blue) when
control returns to the console. The end point of the selected text is the
mouse position at the time the 'Select files' window closes. Once a key is
pressed in the R console, of course, the highlighted region vanishes.
(Curiously, that "highlighted" section is not the actual "selected region"
within the console, as hitting Ctrl-C ends up copying the text from the
mouse position to the R prompt!) Is there a way to call choose.files() --
otherwise a work-around (sending a phantom, non-functioning keystroke?) --
so that this potentially confusing "selection" is not highlighted?

Thanks,
Dan

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


[Rd] S4 method execution time

2010-04-30 Thread Daniel Murphy
Hello:

I have written some an elementary S4 classes around a matrix to strengthen
control of some key attributes. When I run a fairly elementary function
("f") on the matrix outside the class it runs instantaneously (elapsed
system.time = 0) but when I setMethod "f" on myClass -- returning an
instance of myClass -- it runs perceptibly slower (elapsed system.time =
.06). I suspect my initialization and/or validity functions are
inefficiently written. I thought I read in this list of a function that will
trace the execution time of each of the functions called during the
evaluation of an R expression, but now I can't find that message. Is there
such a function, or was I mistaken?

Thank you.

Dan Murphy

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


[Rd] Validity glitch when contains="matrix"

2010-05-05 Thread Daniel Murphy
Sirs:

My validity function did not run when my class contains="matrix". But if I
first define the class with contains="numeric", then define it again
with contains="matrix", validity runs. Here's the session:

> f <- function(object) "BAD CLASS" # force error to
> setClass("A", contains="matrix", validity=f)
[1] "A"
> new("A",as.matrix(1)) # should generate a validity error, does not
An object of class “A”
 [,1]
[1,]1
> setClass("B", contains="numeric", validity=f)
[1] "B"
> new("B",1) # generates the error
Error in validObject(.Object) : invalid class "B" object: BAD CLASS
> setClass("B", contains="matrix", validity=f)
[1] "B"
> new("B",as.matrix(1)) # generates the error
Error in validObject(.Object) : invalid class "B" object: BAD CLASS

On the other hand, when I define the class with "matrix" in its
representation, validity is called, no work-around necessary:

> setClass("C", representation(a="matrix"), validity=f)
[1] "C"
> new("C",a=as.matrix(1)) # error, as desired
Error in validObject(.Object) : invalid class "C" object: BAD CLASS

Should I
1) always put "matrix" into the setClass representation argument instead of
the contains argument, or
2) use contains="numeric", put the matrix's dims and dimnames attributes
into slots, and rely on a constructor to populate the instance?

Option 2 seems most "stable".

Thanks,
Dan Murphy

Windows Vista, R version 2.11.0 (2010-04-22)

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] Validity glitch when contains="matrix"

2010-05-06 Thread Daniel Murphy
Thank you, John. Understood. The "is a" construct makes more sense for my
purposes as the class users will "expect" matrix behavior.

Initially (no pun intended) it was counter-intuitive to me that initialize
checked validity, but now it seems like a reasonable compromise.

In the long term I will probably take advantage of the Matrix package.

Thanks, all.

No-longer-dead-in-the-water,
Dan

On Thu, May 6, 2010 at 9:34 AM, John Chambers  wrote:

> Re: the validity bug.  It's just as your example suggests:  the inherited
> initialize() method for "matrix" fails to call validObject().  Should be
> easy to fix.  (Although it points out that the code should perhaps be
> reorganized so the initialize() method is not responsible for checking
> validity.)
>
>
> Re: your other question:
>
>
> On 5/6/10 4:09 AM, Martin Maechler wrote:
>
>> Daniel Murphy
>>>>>>> on Wed, 5 May 2010 22:08:06 -0700 writes:
>>>>>>>
>>>>>> 
>
>  >  Should I
>> >  1) always put "matrix" into the setClass representation argument
>> instead of
>> >  the contains argument, or
>> >  2) use contains="numeric", put the matrix's dims and dimnames
>> attributes
>> >  into slots, and rely on a constructor to populate the instance?
>>
>>
> Either is possible, but if you really want your new objects to inherit the
> properties of a matrix, your initial idea of contains="matrix" is the
> natural choice for 2) (once the bug is fixed, but even before for most
> purposes). The choice is to inherit from matrix or have matrix as a slot
> (what Smalltalk called "is a" versus "has a").
>
> The choice is as always whether you want to inherit all the methods and
> then override the ones that DON'T make sense, or put the matrix in a slot
> and write all the methods that DO make sense.
>
> Neither choice fits all examples but "matrix" is special, because R treats
> them in a special (perhaps "weird" would apply) way:  they are not a class
> (not even an S3 class) but much code recognizes them internally, meaning you
> inherit a great deal of stuff.
>
> If your new class of objects are supposed to act like matrices most of the
> time, the contains= version may require a lot less programming. On the other
> hand, if you planned to store the data in a non-standard way (as the Matrix
> package does) then you really don't want to inherit the standard methods
> because any you failed to override could be disastrous.
>
>
>
>  Well, one can go the very long and "stable" way as we did in the
>> Matrix package...
>>
>> I'm not sure I would recommend that for you in your situation.
>> ...
>> not the least because you *could* use the Matrix package if you
>> want to use such formal matrices with its thousands of methods.
>>
>> Martin Maechler,
>> ETH Zurich
>>
>> >  Option 2 seems most "stable".
>>
>> >  Thanks,
>> >  Dan Murphy
>>
>> >  Windows Vista, R version 2.11.0 (2010-04-22)
>>
>> >  [[alternative HTML version deleted]]
>>
>> >  __
>> >  R-devel@r-project.org mailing list
>> >  https://stat.ethz.ch/mailman/listinfo/r-devel
>>
>> __
>> R-devel@r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-devel
>>
>

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


[Rd] format.data.frame containing S4 class with format method

2010-05-16 Thread Daniel Murphy
Hi again,

I must be misunderstanding something fundamental about how an S4 class
stored in a data.frame can be persuaded to print according to a desired
format. The help page says:

format.data.frame formats the data frame column by column, applying the
appropriate method of format for each column.

Here is my class:
> setClass("A",contains="character")
[1] "A"
> a <- new("A", "aaa")
> a
An object of class "A"
[1] "aaa"

I defined my format method to display in uppercase:
> setMethod("format","A", function(x, ...) toupper(x))
[1] "format"
> format(a)
An object of class "A"
[1] "AAA"

I looked at the S4 class definition for data.frame (getClass("data.frame"))
which prompted me to store the instance 'a' into a data.frame as follows:
> adf<-new("data.frame",list(a), names="a", row.names="1")
> adf
Object of class "data.frame"
a
1 aaa

... not upper case. The str function clearly shows that the object was
successfully stored in the data.frame:
> str(adf)
'data.frame':   1 obs. of  1 variable:
'data.frame':   1 obs. of  1 variable:
Formal class 'data.frame' [package "methods"] with 4 slots
  ..@ .Data:List of 1
  .. ..$ :Formal class 'A' [package ".GlobalEnv"] with 1 slots
  .. .. .. ..@ .Data: chr "aaa"
  ..@ names: chr "a"
  ..@ row.names: chr "1"
  ..@ .S3Class : chr "data.frame"

Is there another step I should be taking so that "A"'s format method is
found and used?

Thank you,

Dan Murphy

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


[Rd] pretty.Date(): new "halfmonth" time step

2010-05-19 Thread Daniel Murphy
>Much better to implement directly what this is trying to do: i.e. to
>have a "halfmonth" time step. This is just the union of two "monthly"
>sequences, one on the 1st of each month and another on the 15th of
>each month.

For some applications that might be true. But not for others. For a month
with 31 days, there are 14 days before the 15th of the month and 16 days
after the 15th, so, for example, March 16th (specifically noon) rather than
March 15th would be the halfway point if you define "halfway" in terms of
the distances to the beginning and end of the month. For a month with 30
days -- like April -- the halfway point would be the instant between the
15th and the 16th of the month. Do you label that instant April 15 or April
16?  (I prefer "15".) Don't get me started on February.

- Dan Murphy

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] pretty.Date(): new "halfmonth" time step

2010-05-20 Thread Daniel Murphy
Felix,

I see your point about the "halfway" point acting like the first day of the
month in its relativity to the ending date of the month: they're both
variable.

I'm an actuary. Like accountants, actuaries tend to measure "financial" time
in months because of how the books close. But in our mathematical models
time takes on a continuous nature. So our problem is how to build a computer
representation of time that reflects both its continuous nature as well as
the varying-length, "discrete" nature of financial months. I've found that a
fixed value for a halfway point complicates actuarial calculations. It could
serve other purposes just fine, however.

Best regards,
Dan

On Wed, May 19, 2010 at 7:48 PM, Felix Andrews  wrote:

> On 20 May 2010 11:56, Daniel Murphy  wrote:
> >>Much better to implement directly what this is trying to do: i.e. to
> >>have a "halfmonth" time step. This is just the union of two "monthly"
> >>sequences, one on the 1st of each month and another on the 15th of
> >>each month.
> >
> > For some applications that might be true. But not for others. For a month
> > with 31 days, there are 14 days before the 15th of the month and 16 days
> > after the 15th, so, for example, March 16th (specifically noon) rather
> than
> > March 15th would be the halfway point if you define "halfway" in terms of
> > the distances to the beginning and end of the month. For a month with 30
> > days -- like April -- the halfway point would be the instant between the
> > 15th and the 16th of the month. Do you label that instant April 15 or
> April
> > 16?  (I prefer "15".) Don't get me started on February.
>
> Dan, you are correct: the midpoint of a 30 day month is the 16th at
> 00:00. That instant is called the 16th according to print.POSIXt.
>
> junstart <- as.POSIXct("2000-06-01 00:00", tz="GMT")
> julstart <- as.POSIXct("2000-07-01 00:00", tz="GMT")
> junstart + ((julstart - junstart) / 2)
> #[1] "2000-06-16 GMT"
>
> How embarassing...
> So I think it would be better to use 16 rather than 15 for the
> "halfmonth" time step.
>
> Yes, months have variable lengths, but I think it is best to use a
> consistent date (the 16th) than to calculate exact midpoints, just as
> a normal monthly series has a consistent date (the 1st) and has
> variable lengths.
>
> Regards
> -Felix
>
>
> >
> > - Dan Murphy
> >
> >[[alternative HTML version deleted]]
> >
> > __
> > R-devel@r-project.org mailing list
> > https://stat.ethz.ch/mailman/listinfo/r-devel
> >
>
>
>
> --
> Felix Andrews / 安福立
> Postdoctoral Fellow
> Integrated Catchment Assessment and Management (iCAM) Centre
> Fenner School of Environment and Society [Bldg 48a]
> The Australian National University
> Canberra ACT 0200 Australia
> M: +61 410 400 963
> T: + 61 2 6125 4670
> E: felix.andr...@anu.edu.au
> CRICOS Provider No. 00120C
> --
> http://www.neurofractal.org/felix/
>

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] pretty.Date(): new "halfmonth" time step

2010-05-20 Thread Daniel Murphy
Yes. I looked at that feature of zoo. But it forced me to keep track of
fractional months in the "Date" world. Square one. I ended up implementing a
class under the paradigm of whole and fractional months. It allows me to do
all my time arithmetic in ways that accountants expect. For example,
accountants think of the close of business June 30th as being the halfway
point of the year, but it's certainly not half the year "as the crow flies."
-Dan

On Thu, May 20, 2010 at 4:01 AM, Gabor Grothendieck  wrote:

> Note that in the zoo package that as.Date.yearmon has a frac= argument,
> e.g.
>
> > library(zoo)
> > ym <- as.yearmon("2010-01")
> > as.Date(ym, frac = 0.5)
> [1] "2010-01-16"
>
>
> On Wed, May 19, 2010 at 9:56 PM, Daniel Murphy 
> wrote:
> >>Much better to implement directly what this is trying to do: i.e. to
> >>have a "halfmonth" time step. This is just the union of two "monthly"
> >>sequences, one on the 1st of each month and another on the 15th of
> >>each month.
> >
> > For some applications that might be true. But not for others. For a month
> > with 31 days, there are 14 days before the 15th of the month and 16 days
> > after the 15th, so, for example, March 16th (specifically noon) rather
> than
> > March 15th would be the halfway point if you define "halfway" in terms of
> > the distances to the beginning and end of the month. For a month with 30
> > days -- like April -- the halfway point would be the instant between the
> > 15th and the 16th of the month. Do you label that instant April 15 or
> April
> > 16?  (I prefer "15".) Don't get me started on February.
> >
> > - Dan Murphy
> >
> >[[alternative HTML version deleted]]
> >
> > __
> > R-devel@r-project.org mailing list
> > https://stat.ethz.ch/mailman/listinfo/r-devel
> >
>

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] Extract/format/show for S4 objects (Johann Hibschman)

2010-06-09 Thread Daniel Murphy
Johann,

Following up on Gabor's reply, the mondate package (new on CRAN last week)
will accomplish your needs.

>I'm trying to make an integer-backed quarter (as in fraction of year)
>class, but I can't quite it to work.  I want integer-backed so I don't
>have to worry about floating-point effects when doing math, and so that
>I can use it as in data.table.

mondate represents a date internally as a numeric, not an integer, but the
integer part corresponds to months, not years, so a zero fractional part of
a mondate corresponds to a "complete month." Every third whole number,
therefore, would correspond to a complete quarter. Arithmetic in months (or
quarters by dividing by 3) returns a numeric with a "timeunits" attribute.
mondate's can be stored in a data.frame.

> (A<-mondate.ymd(2010,3*(1:4)))  # display format is "U.S.", my location
mondate: timeunits="months"
[1] 03/31/2010 06/30/2010 09/30/2010 12/31/2010
> diff(A) # 3 months apart
[1] 3 3 3
> A-mondate("12/31/2009") #  months since the end of last year; date
input format also works for my location
[1]  3  6  9 12
attr(,"timeunits")
[1] "months"
> c((A-mondate("12/31/2009"))/3) # divide by 3 and remove the attribute and
you have quarters
[1] 1 2 3 4
> data.frame(QtrEnd=A, Amount=rep(1000,4))
  QtrEnd Amount
1 03/31/2010   1000
2 06/30/2010   1000
3 09/30/2010   1000
4 12/31/2010   1000

If the date you are subtracting off is somewhere in the fourth quarter of
2009 but you still want to treat it as being representative of the fourth
quarter, the floor function will remove the fractional part of the
difference in quarters (I will enter November 1st in non-US format):
> floor(c((A-mondate("2009-11-1"))/3))
[1] 1 2 3 4

>First of all, is there a good reference for this anywhere?  All of the
>S4 tutorials that I've found have been too high-level, and I can't find
>any examples of implementing extract.  In S3, I can use [.Date as my
>example, but I can't find the equivalent for S4.

See the source code for an S4 "[" method. I was unable to convert all S3
methods to S4, so you will see that some S3 methods remain (e.g.,
as.data.frame.mondate); S3methods=TRUE in the class definition as a result.

I wrote this package to solve essentially your problem. If it falls short
for you somehow, please me know.
Thanks,
- Dan Murphy

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


[Rd] Match .3 in a sequence

2009-03-16 Thread Daniel Murphy
Hello:I am trying to match the value 0.3 in the sequence seq(.2,.3). I get
> 0.3 %in% seq(from=.2,to=.3)
[1] FALSE
Yet
> 0.3 %in% c(.2,.3)
[1] TRUE
For arbitrary sequences, this "invisible .3" has been problematic. What is
the best way to work around this?
Thank you.
Dan

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] Match .3 in a sequence

2009-03-16 Thread Daniel Murphy
I have a matrix whose columns were filled with values which were functions
of cvseq<-seq(.2,.3,by=.1) (and a row value of mode integer). To do a lookup
for cv=.3 later, I wanted to match(.3,cvseq), which gave me NA, hence my
question. I thought R would match .3 in cvseq within .Machine$double.eps,
but I can understand it if .3 and the second element of cvseq would not have
identical bits.
Besides the helpful suggestions below, I also tried
> cvseqf <- as.factor(cvseq)
> match(.3,cvseq)
[1] 2
which worked.

In general, would it be better to go the enumeration route via as.factor or
the approximation route?

Thanks for the help.

-Dan

On Mon, Mar 16, 2009 at 8:24 AM, Stavros Macrakis wrote:

> Well, first of all, seq(from=.2,to=.3) gives c(0.2), so I assume you
> really mean something like seq(from=.2,to=.3,by=.1), which gives
> c(0.2, 0.3).
>
> %in% tests for exact equality, which is almost never a good idea with
> floating-point numbers.
>
> You need to define what exactly you mean by "in" for floating-point
> numbers.  What sort of tolerance are you willing to allow?
>
> Some possibilities would be for example:
>
> approxin <- function(x,list,tol) any(abs(list-x) tolerance
>
> rapproxin <- function(x,list,tol) (x==0 && 0 %in% list) ||
> any(abs((list-x)/x)<=tol,na.rm=TRUE)
> # relative tolerance; only exact 0 will match 0
>
> Hope this helps,
>
>  -s
>
> On Mon, Mar 16, 2009 at 9:36 AM, Daniel Murphy 
> wrote:
> > Hello:I am trying to match the value 0.3 in the sequence seq(.2,.3). I
> get
> >> 0.3 %in% seq(from=.2,to=.3)
> > [1] FALSE
> > Yet
> >> 0.3 %in% c(.2,.3)
> > [1] TRUE
> > For arbitrary sequences, this "invisible .3" has been problematic. What
> is
> > the best way to work around this?
>

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] Match .3 in a sequence

2009-03-16 Thread Daniel Murphy
Got it. Thank you all.

On Mon, Mar 16, 2009 at 4:39 PM, Stavros Macrakis wrote:

> The factor approach is horrifically ugly and dangerous.
>
> Even if it didn't have the extraordinarily poor behavior documented
> below, it simply isn't well-defined what it should do.  The explicit
> approximation route is far far preferable in every way: more
> predictable, more controllable, and even (though it hardly matters
> usually) faster.
>
> Let's look at the extraordinarily poor behavior I was mentioning. Consider:
>
> nums <- (.3 + 2e-16 * c(-2,-1,1,2)); nums
> [1] 0.3 0.3 0.3 0.3
>
> Though they all print as .3 with the default precision (which is
> normal and expected), they are all different from .3:
>
> nums - .3 =>  -3.885781e-16 -2.220446e-16  2.220446e-16  3.885781e-16
>
> When we convert nums to a factor, we get:
>
> fact <- as.factor(nums); fact
> [1] 0.300 0.3   0.3   0.300
> Levels: 0.300 0.3 0.3 0.300
>
> Not clear what the difference between 0.300 and 0.3 is
> supposed to be, nor why some 0.300 are < .3 and others are
> > .3, but let's put that aside for the moment.
>
> Now let's look at the relations among the factor values:
>
> fact[1]==fact[2]
> [1] FALSE
> > fact[1]==fact[4]
> [1] TRUE
>
> So though nums[1] < nums[2] < nums[3] < nums[4], fact[1] compares
> *unequal* to fact[2] though it compares *equal* to fact[4].
> Apparently R is comparing the *names* of the levels rather than the
> indexes in the factor.  This would be weird even if it didn't lead to
> this very bad case.
>
> Hope this helps,
>
> -s
>
>
> On Mon, Mar 16, 2009 at 6:53 PM, Daniel Murphy 
> wrote:
> > I have a matrix whose columns were filled with values which were
> functions
> > of cvseq<-seq(.2,.3,by=.1) (and a row value of mode integer). To do a
> lookup
> > for cv=.3 later, I wanted to match(.3,cvseq), which gave me NA, hence my
> > question. I thought R would match .3 in cvseq within .Machine$double.eps,
> > but I can understand it if .3 and the second element of cvseq would not
> have
> > identical bits.
> > Besides the helpful suggestions below, I also tried
> >> cvseqf <- as.factor(cvseq)
> >> match(.3,cvseq)
> > [1] 2
> > which worked.
> > In general, would it be better to go the enumeration route via as.factor
> or
> > the approximation route?
> > Thanks for the help.
> > -Dan
> >
> > On Mon, Mar 16, 2009 at 8:24 AM, Stavros Macrakis  >
> > wrote:
> >>
> >> Well, first of all, seq(from=.2,to=.3) gives c(0.2), so I assume you
> >> really mean something like seq(from=.2,to=.3,by=.1), which gives
> >> c(0.2, 0.3).
> >>
> >> %in% tests for exact equality, which is almost never a good idea with
> >> floating-point numbers.
> >>
> >> You need to define what exactly you mean by "in" for floating-point
> >> numbers.  What sort of tolerance are you willing to allow?
> >>
> >> Some possibilities would be for example:
> >>
> >> approxin <- function(x,list,tol) any(abs(list-x) >> tolerance
> >>
> >> rapproxin <- function(x,list,tol) (x==0 && 0 %in% list) ||
> >> any(abs((list-x)/x)<=tol,na.rm=TRUE)
> >> # relative tolerance; only exact 0 will match 0
> >>
> >> Hope this helps,
> >>
> >>  -s
> >>
> >> On Mon, Mar 16, 2009 at 9:36 AM, Daniel Murphy 
> >> wrote:
> >> > Hello:I am trying to match the value 0.3 in the sequence seq(.2,.3). I
> >> > get
> >> >> 0.3 %in% seq(from=.2,to=.3)
> >> > [1] FALSE
> >> > Yet
> >> >> 0.3 %in% c(.2,.3)
> >> > [1] TRUE
> >> > For arbitrary sequences, this "invisible .3" has been problematic.
> What
> >> > is
> >> > the best way to work around this?
> >
> >
>

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] Match .3 in a sequence

2009-03-17 Thread Daniel Murphy
Is this a reasonably fast way to do an approximate match of a vector x to
values in a list?

match.approx  <- function(x,list,tol=.0001)
sapply(apply(abs(outer(list,x,"-"))wrote:

> Well, first of all, seq(from=.2,to=.3) gives c(0.2), so I assume you
> really mean something like seq(from=.2,to=.3,by=.1), which gives
> c(0.2, 0.3).
>
> %in% tests for exact equality, which is almost never a good idea with
> floating-point numbers.
>
> You need to define what exactly you mean by "in" for floating-point
> numbers.  What sort of tolerance are you willing to allow?
>
> Some possibilities would be for example:
>
> approxin <- function(x,list,tol) any(abs(list-x) tolerance
>
> rapproxin <- function(x,list,tol) (x==0 && 0 %in% list) ||
> any(abs((list-x)/x)<=tol,na.rm=TRUE)
> # relative tolerance; only exact 0 will match 0
>
> Hope this helps,
>
>  -s
>
> On Mon, Mar 16, 2009 at 9:36 AM, Daniel Murphy 
> wrote:
> > Hello:I am trying to match the value 0.3 in the sequence seq(.2,.3). I
> get
> >> 0.3 %in% seq(from=.2,to=.3)
> > [1] FALSE
> > Yet
> >> 0.3 %in% c(.2,.3)
> > [1] TRUE
> > For arbitrary sequences, this "invisible .3" has been problematic. What
> is
> > the best way to work around this?
>

[[alternative HTML version deleted]]

__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel