[Rd] S4 dispatch for .DollarNames (utils)

2010-05-29 Thread Romain Francois

Hello,

I'm trying to make .DollarNames generic and implement a method for it in 
a package. .DollarNames is the function that is now called to get 
completion possibilities.


My R code looks like this:

setGeneric( ".DollarNames" )

setClass("track",
 representation(x="numeric", y="numeric"))
## A class extending the previous, adding one more slot
setClass("trackCurve",
representation(smooth = "numeric"),
contains = "track")

setMethod( ".DollarNames", signature( x = "track", pattern = "character" 
), function(x, pattern){

grep( pattern, c("foo", "bar"), value = TRUE )  
} )


and the NAMESPACE :

import( utils )
exportMethods( .DollarNames )
exportClasses( track, trackCurve )


When I load the package, I can call .DollarNames explicitely :

> require( foo )
> x <- new( "trackCurve", x = 1:10, y = 1:10, smooth = 1:10 )
> .DollarNames( x, "f" )
[1] "foo"

but completion does not work :

> x$f
x$


What do I miss ?

I've uploaded foo here : http://addictedtor.free.fr/misc/rcpp/foo_1.0.tar.gz

Romain


--
Romain Francois
Professional R Enthusiast
+33(0) 6 28 91 30 30
http://romainfrancois.blog.free.fr
|- http://bit.ly/9CQ66r : RMetrics 2010
|- http://bit.ly/cork4b : highlight 0.1-8
`- http://bit.ly/bklUXt : RcppArmadillo 0.2.1


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


Re: [Rd] S4 dispatch for .DollarNames (utils)

2010-05-29 Thread Romain Francois

This seems to do the trick, but it does not feel right:

.onLoad <- function( libname, pkgname ){ 
utils <- asNamespace( "utils" )
unlockBinding( ".DollarNames", utils )
assignInNamespace( ".DollarNames", .DollarNames, utils )
lockBinding( ".DollarNames", utils )
}

Any better idea ?

Romain

Le 29/05/10 13:21, Romain Francois a écrit :


Hello,

I'm trying to make .DollarNames generic and implement a method for it in
a package. .DollarNames is the function that is now called to get
completion possibilities.

My R code looks like this:

setGeneric( ".DollarNames" )

setClass("track",
representation(x="numeric", y="numeric"))
## A class extending the previous, adding one more slot
setClass("trackCurve",
representation(smooth = "numeric"),
contains = "track")

setMethod( ".DollarNames", signature( x = "track", pattern = "character"
), function(x, pattern){
grep( pattern, c("foo", "bar"), value = TRUE )
} )


and the NAMESPACE :

import( utils )
exportMethods( .DollarNames )
exportClasses( track, trackCurve )


When I load the package, I can call .DollarNames explicitely :

 > require( foo )
 > x <- new( "trackCurve", x = 1:10, y = 1:10, smooth = 1:10 )
 > .DollarNames( x, "f" )
[1] "foo"

but completion does not work :

 > x$f
x$


What do I miss ?

I've uploaded foo here :
http://addictedtor.free.fr/misc/rcpp/foo_1.0.tar.gz

Romain





--
Romain Francois
Professional R Enthusiast
+33(0) 6 28 91 30 30
http://romainfrancois.blog.free.fr
|- http://bit.ly/9CQ66r : RMetrics 2010
|- http://bit.ly/cork4b : highlight 0.1-8
`- http://bit.ly/bklUXt : RcppArmadillo 0.2.1


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


Re: [Rd] S4 dispatch for .DollarNames (utils)

2010-05-29 Thread Deepayan Sarkar
On Sat, May 29, 2010 at 4:21 AM, Romain Francois
 wrote:
> Hello,
>
> I'm trying to make .DollarNames generic and implement a method for it in a
> package. .DollarNames is the function that is now called to get completion
> possibilities.
>
> My R code looks like this:
>
> setGeneric( ".DollarNames" )
>
> setClass("track",
>         representation(x="numeric", y="numeric"))
> ## A class extending the previous, adding one more slot
> setClass("trackCurve",
>    representation(smooth = "numeric"),
>    contains = "track")
>
> setMethod( ".DollarNames", signature( x = "track", pattern = "character" ),
> function(x, pattern){
>        grep( pattern, c("foo", "bar"), value = TRUE )
> } )
>
>
> and the NAMESPACE :
>
> import( utils )
> exportMethods( .DollarNames )
> exportClasses( track, trackCurve )
>
>
> When I load the package, I can call .DollarNames explicitely :
>
>> require( foo )
>> x <- new( "trackCurve", x = 1:10, y = 1:10, smooth = 1:10 )
>> .DollarNames( x, "f" )
> [1] "foo"
>
> but completion does not work :
>
>> x$f
> x$

I guess because

> utils:::.DollarNames(x, "f")
character(0)

so the S4 generic is not being seen within the utils namespace. I
don't know what the right fix is...

-Deepayan

> What do I miss ?
>
> I've uploaded foo here : http://addictedtor.free.fr/misc/rcpp/foo_1.0.tar.gz
>
> Romain
>
>
> --
> Romain Francois
> Professional R Enthusiast
> +33(0) 6 28 91 30 30
> http://romainfrancois.blog.free.fr
> |- http://bit.ly/9CQ66r : RMetrics 2010
> |- http://bit.ly/cork4b : highlight 0.1-8
> `- http://bit.ly/bklUXt : RcppArmadillo 0.2.1
>
>
> __
> 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


Re: [Rd] S4 dispatch for .DollarNames (utils)

2010-05-29 Thread Romain Francois

Le 29/05/10 20:23, Deepayan Sarkar a écrit :

On Sat, May 29, 2010 at 4:21 AM, Romain Francois
  wrote:

Hello,

I'm trying to make .DollarNames generic and implement a method for it in a
package. .DollarNames is the function that is now called to get completion
possibilities.

My R code looks like this:

setGeneric( ".DollarNames" )

setClass("track",
 representation(x="numeric", y="numeric"))
## A class extending the previous, adding one more slot
setClass("trackCurve",
representation(smooth = "numeric"),
contains = "track")

setMethod( ".DollarNames", signature( x = "track", pattern = "character" ),
function(x, pattern){
grep( pattern, c("foo", "bar"), value = TRUE )
} )


and the NAMESPACE :

import( utils )
exportMethods( .DollarNames )
exportClasses( track, trackCurve )


When I load the package, I can call .DollarNames explicitely :


require( foo )
x<- new( "trackCurve", x = 1:10, y = 1:10, smooth = 1:10 )
.DollarNames( x, "f" )

[1] "foo"

but completion does not work :


x$f

x$


I guess because


utils:::.DollarNames(x, "f")

character(0)


yes. hence the hack I used when replying which is probably not a good 
idea, specially if two packages want it.



so the S4 generic is not being seen within the utils namespace. I
don't know what the right fix is...

-Deepayan


Perhaps something like the attached ?

defining a generic in methods and use this one when methods dispatch is on.



What do I miss ?

I've uploaded foo here : http://addictedtor.free.fr/misc/rcpp/foo_1.0.tar.gz

Romain


--
Romain Francois
Professional R Enthusiast
+33(0) 6 28 91 30 30
http://romainfrancois.blog.free.fr
|- http://bit.ly/99bz5D : highlight 0.1-9
|- http://bit.ly/9CQ66r : RMetrics 2010
`- http://bit.ly/bklUXt : RcppArmadillo 0.2.1

Index: src/library/utils/R/completion.R
===
--- src/library/utils/R/completion.R(revision 52140)
+++ src/library/utils/R/completion.R(working copy)
@@ -351,7 +351,8 @@
else
{
## ## suffix must match names(object) (or 
ls(object) for environments)
-   .DollarNames(object, pattern = sprintf("^%s", 
makeRegexpSafe(suffix)))
+   dollarNames <- if( .isMethodsDispatchOn() ) 
methods:::.DollarNames else .DollarNames
+   dollarNames(object, pattern = sprintf("^%s", 
makeRegexpSafe(suffix)))   
## if (is.environment(object))
## {
## ls(object,
Index: src/library/methods/R/makeBasicFunsList.R
===
--- src/library/methods/R/makeBasicFunsList.R   (revision 52140)
+++ src/library/methods/R/makeBasicFunsList.R   (working copy)
@@ -222,7 +222,14 @@
base::sample(x, size, replace=replace, prob=prob, ...),
   signature = c("x", "size"), where = where)
 setGenericImplicit("sample", where, FALSE)
-
+
+setGeneric( ".DollarNames", 
+   function(x, pattern) standardGeneric(".DollarNames"), 
+   useAsDefault = function(x,pattern) utils:::.DollarNames(x,pattern), 
+   signature = "x", 
+   where = where )
+setGenericImplicit(".DollarNames", where, FALSE)
+
 ## not implicitGeneric() which is not yet available "here"
 registerImplicitGenerics(where = where)
 }
__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] S4 dispatch for .DollarNames (utils)

2010-05-29 Thread John Chambers
The idea of modifying .DollarNames to recognize S4 methods is OK, but 
the problem could arise again.

It would be better to have a general solution.  The general problem as 
it seems is that an S3 generic called from within its package's 
namespace (or from some other 3rd package) will not detect S4 methods.  
In a sense, this is a natural consequence of namespace semantics and 
therefore not a bug.  We don't really want to fix up each case when it 
arises.

I can see two general solutions, one a reasonable fix that could likely 
be implemented for 2.12.0, the other a slight hack added to make the 
solution work now.

Both solutions start with the idea that we continue to treat the S3 
generic as an S3 generic (at least when it's called from the owning 
package's namespace).  We then define an S3 method for the S4 class.

Right now, that fails to recognize S4 inheritance (that's the fix that 
should be doable for 2.12.0; most of the mechanism needed is already in 
the UseMethod implementation).

The workaround/hack that *does* work now, I believe, is to insert a 
dummy S3 class into the mix and define the S3 .DollarNames method for it.

Example:
 > setOldClass("foo3")
 > .DollarNames.foo3 <- function(x, pattern)"bar"
 >
 > setClass("foo", contains = "foo3", representation(x = "numeric"))
[1] "foo"
 >
 > ff = new("foo")
 >
 > setClass("fee", contains = "foo")
[1] "fee"
 >
 > fe = new("fee")

Both ff$ and fe$ complete with "bar", running 2.11.0 from the command line.

John





On 5/29/10 12:37 PM, Romain Francois wrote:
> Le 29/05/10 20:23, Deepayan Sarkar a écrit :
>> On Sat, May 29, 2010 at 4:21 AM, Romain Francois
>>   wrote:
>>> Hello,
>>>
>>> I'm trying to make .DollarNames generic and implement a method for 
>>> it in a
>>> package. .DollarNames is the function that is now called to get 
>>> completion
>>> possibilities.
>>>
>>> My R code looks like this:
>>>
>>> setGeneric( ".DollarNames" )
>>>
>>> setClass("track",
>>>  representation(x="numeric", y="numeric"))
>>> ## A class extending the previous, adding one more slot
>>> setClass("trackCurve",
>>> representation(smooth = "numeric"),
>>> contains = "track")
>>>
>>> setMethod( ".DollarNames", signature( x = "track", pattern = 
>>> "character" ),
>>> function(x, pattern){
>>> grep( pattern, c("foo", "bar"), value = TRUE )
>>> } )
>>>
>>>
>>> and the NAMESPACE :
>>>
>>> import( utils )
>>> exportMethods( .DollarNames )
>>> exportClasses( track, trackCurve )
>>>
>>>
>>> When I load the package, I can call .DollarNames explicitely :
>>>
 require( foo )
 x<- new( "trackCurve", x = 1:10, y = 1:10, smooth = 1:10 )
 .DollarNames( x, "f" )
>>> [1] "foo"
>>>
>>> but completion does not work :
>>>
 x$f
>>> x$
>>
>> I guess because
>>
>>> utils:::.DollarNames(x, "f")
>> character(0)
>
> yes. hence the hack I used when replying which is probably not a good 
> idea, specially if two packages want it.
>
>> so the S4 generic is not being seen within the utils namespace. I
>> don't know what the right fix is...
>>
>> -Deepayan
>
> Perhaps something like the attached ?
>
> defining a generic in methods and use this one when methods dispatch 
> is on.
>
>
>>> What do I miss ?
>>>
>>> I've uploaded foo here : 
>>> http://addictedtor.free.fr/misc/rcpp/foo_1.0.tar.gz
>>>
>>> Romain
>
>
> __
> 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 dispatch for .DollarNames (utils)

2010-05-29 Thread Romain Francois

Thanks. I'll apply the nice workaround for now.

Romain

Le 29/05/10 23:15, John Chambers a écrit :

The idea of modifying .DollarNames to recognize S4 methods is OK, but
the problem could arise again.

It would be better to have a general solution.  The general problem as
it seems is that an S3 generic called from within its package's
namespace (or from some other 3rd package) will not detect S4 methods.
In a sense, this is a natural consequence of namespace semantics and
therefore not a bug.  We don't really want to fix up each case when it
arises.

I can see two general solutions, one a reasonable fix that could likely
be implemented for 2.12.0, the other a slight hack added to make the
solution work now.

Both solutions start with the idea that we continue to treat the S3
generic as an S3 generic (at least when it's called from the owning
package's namespace).  We then define an S3 method for the S4 class.

Right now, that fails to recognize S4 inheritance (that's the fix that
should be doable for 2.12.0; most of the mechanism needed is already in
the UseMethod implementation).

The workaround/hack that *does* work now, I believe, is to insert a
dummy S3 class into the mix and define the S3 .DollarNames method for it.

Example:
 > setOldClass("foo3")
 > .DollarNames.foo3 <- function(x, pattern)"bar"
 >
 > setClass("foo", contains = "foo3", representation(x = "numeric"))
[1] "foo"
 >
 > ff = new("foo")
 >
 > setClass("fee", contains = "foo")
[1] "fee"
 >
 > fe = new("fee")

Both ff$ and fe$ complete with "bar", running 2.11.0 from the command line.

John





On 5/29/10 12:37 PM, Romain Francois wrote:

Le 29/05/10 20:23, Deepayan Sarkar a écrit :

On Sat, May 29, 2010 at 4:21 AM, Romain Francois
  wrote:

Hello,

I'm trying to make .DollarNames generic and implement a method for
it in a
package. .DollarNames is the function that is now called to get
completion
possibilities.

My R code looks like this:

setGeneric( ".DollarNames" )

setClass("track",
 representation(x="numeric", y="numeric"))
## A class extending the previous, adding one more slot
setClass("trackCurve",
representation(smooth = "numeric"),
contains = "track")

setMethod( ".DollarNames", signature( x = "track", pattern =
"character" ),
function(x, pattern){
grep( pattern, c("foo", "bar"), value = TRUE )
} )


and the NAMESPACE :

import( utils )
exportMethods( .DollarNames )
exportClasses( track, trackCurve )


When I load the package, I can call .DollarNames explicitely :


require( foo )
x<- new( "trackCurve", x = 1:10, y = 1:10, smooth = 1:10 )
.DollarNames( x, "f" )

[1] "foo"

but completion does not work :


x$f

x$


I guess because


utils:::.DollarNames(x, "f")

character(0)


yes. hence the hack I used when replying which is probably not a good
idea, specially if two packages want it.


so the S4 generic is not being seen within the utils namespace. I
don't know what the right fix is...

-Deepayan


Perhaps something like the attached ?

defining a generic in methods and use this one when methods dispatch
is on.



What do I miss ?

I've uploaded foo here :
http://addictedtor.free.fr/misc/rcpp/foo_1.0.tar.gz

Romain



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




--
Romain Francois
Professional R Enthusiast
+33(0) 6 28 91 30 30
http://romainfrancois.blog.free.fr
|- http://bit.ly/99bz5D : highlight 0.1-9
|- http://bit.ly/9CQ66r : RMetrics 2010
`- http://bit.ly/bklUXt : RcppArmadillo 0.2.1


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