Re: [Rd] S4 Dispatching

2005-07-20 Thread John Chambers
Paul Roebuck wrote:
> Is it possible for S4 to (continue) dispatch to a class
> created during dispatching? The code below doesn't work;
> is this not possible or have I ommitted something?

"doesn't work"?  This is not helpful.  Please show what you got and what 
you expected.  The result below is what I would expect (& get) from your 
code.

R> onthefly("testing")
generic onthefly
onthefly (character)
generic onthefly
onthefly (mydata)
List of 1
  $ name: chr "mydata"
  - attr(*, "class")= chr "mydata"

Since you used an undefined class "mydata" you can't expect very much 
else to work with these objects.  You did not in fact "create" the 
class, you just assigned a class attribute to an object corresponding to 
an undefined class.  There is a warning message to that effect from the 
second setMethod() call.


> 
> Concept was to create a SEXP with R_AllocatePtr, give it
> a class attribute, and continue dispatch. Example code
> below omits multiple parameters that can be different types.
> Essentially, any parameter would be converted to an
> internal type "class" and the final dispatch would be
> passing EXTPTRSXP objects.
> 
> 
> library(methods)
> 
> setGeneric("onthefly",
>function(mydata) {
> cat("generic", match.call()[[1]], "\n")
> standardGeneric("onthefly")
> })
> 
> setMethod("onthefly",
>   signature(mydata = "character"),
>   function(mydata) {
> cat(match.call()[[1]],
> "(character)\n")
> 
> # Simulating EXTPTRSXP
> mydata <- list(name = "mydata")
> class(mydata) <- "mydata"
> 
> callGeneric(mydata)
> })
> 
> setMethod("onthefly",
>   signature(mydata = "mydata"),
>   function(mydata) {
> cat(match.call()[[1]],
> "(mydata)\n")
> 
> str(mydata)
> })
> 
> 
> 
> 
>>version
> 
>  _
> platform powerpc-apple-darwin7.9.0
> arch powerpc
> os   darwin7.9.0
> system   powerpc, darwin7.9.0
> status
> major2
> minor1.1
> year 2005
> month06
> day  20
> language R
> 
> --
> SIGSIG -- signature too long (core dumped)
> 
> __
> 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] Default arguments for setMethod() (PR#8021)

2005-07-20 Thread John Chambers
Quite right.  There is code in the evaluator that copies default values 
from the method into the promise for a missing argument, when the method 
is being evalutated.

The catch seems to be that there is no promise unless SOME default was 
included for the argument in the generic.

So either we need to adjust the generic accordingly, perhaps when the 
setMethod() with a default is done (this could be tricky with multiple 
packages having methods for the same generic), or else admit the 
ugliness in the documentation.

Thanks.

[EMAIL PROTECTED] wrote:

> Full_Name: Bert Gunter
> Version: 2.1.1
> OS: Windows 2000
> Submission from: (NULL) (192.12.78.250)
> 
> 
> There appears to be either a bug or documentation problem in
> setMethod/setGeneric with how default arguments are handled. The setMethod 
> Help
> says:
> **
> Method definitions can have default expressions for arguments. If those
> arguments are then missing in the call to the generic function, the default
> expression in the method is used. If the method definition has no default for
> the argument, then the expression (if any) supplied in the definition of the
> generic function itself is used.
> **
> However:
> 
> 
>>setGeneric('foo',function(x,y)standardGeneric('foo'))
> 
> [1] "foo"
> 
>>setMethod('foo','numeric',function(x,y=3)x+y)
> 
> [1] "foo"
> 
>>foo(10)
> 
> Error in foo(10) : argument "y" is missing, with no default
> 
>  BUT adding a NULL default argument in the standardGeneric fixes this:
> 
> 
>>setGeneric('foo',function(x,y=NULL)standardGeneric('foo'))
> 
> [1] "foo"
> 
>>setMethod('foo','numeric',function(x,y=3)x+y)
> 
> [1] "foo"
> 
>>foo(10)
> 
> [1] 13
> 
> Cheers,
> Bert Gunter
> 
> __
> 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 Dispatching

2005-07-22 Thread John Chambers
Paul Roebuck wrote:
> On Wed, 20 Jul 2005, John Chambers wrote:
> 
> 
>>Paul Roebuck wrote:
>>
>>
>>>Is it possible for S4 to (continue) dispatch to a class
>>>created during dispatching? The code below doesn't work;
>>>is this not possible or have I ommitted something?
>>
>>"doesn't work"?  This is not helpful.  Please show what you got and what
>>you expected.  The result below is what I would expect (& get) from your
>>code.
>>
>>R> onthefly("testing")
>>generic onthefly
>>onthefly (character)
>>generic onthefly
>>onthefly (mydata)
>>List of 1
>>  $ name: chr "mydata"
>>  - attr(*, "class")= chr "mydata"
>>
>>Since you used an undefined class "mydata" you can't expect very much
>>else to work with these objects.  You did not in fact "create" the
>>class, you just assigned a class attribute to an object corresponding to
>>an undefined class.  There is a warning message to that effect from the
>>second setMethod() call.
> 
> 
> In retrospect, that should have been expressed as "doesn't
> work as I expected". I was using 'options(warn=2)' and didn't
> notice the warning conversion. I expected evaluation of the
> class existence would occur when callGeneric() was invoked,
> not during setMethod(). Also surprised at the return to
> generic prior to the final dispatch (instead of going
> straight there) along that same line of thought.
> 
> While it's true that all I did was add a class attribute to
> the object, I thought that was all that was required for a
> trivial S3 class to be "defined". In my case, it is solely
> for internal usage as an intermediate data object that
> allows R to handle its memory management. Not sure how to
> define an S4 class representation for an external pointer.

That is definitely a problem in the current R implementation.

Because external pointers (and environments and some other data types) 
are not duplicated in the way that ordinary vectors are, you cannot 
directly extend them as a class.  You can't for example set the class of 
such an object without affecting all the other code that uses the same 
pointer.

The usual workaround is to define a list of one element that contains 
the external pointer, and make that the object.  Or equivalently set up 
an S4 class with the external pointer as a slot.  That's not a really 
satisfactory workaround, though, since it's not what was intended.

It would be nice if the implementation duplicated the attributes, if 
any, of such objects.  But that appears not to be a simple fix---trying 
out that change causes problems that seem to be related to garbage 
collection or other internals of storage management.  A change for the 
future perhaps ...


> 
> Thanks for your patience and help.
> 
> --
> SIGSIG -- signature too long (core dumped)
>

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


Re: [Rd] S4 generating function

2005-08-05 Thread John Chambers
First, anyone planning to debug methods should consider the general form 
of the trace() function with signature= to say what method to trace, and 
some suitable interactive function such as "browser" or "recover" to 
examine the computations. See ?trace

In this example, something like:
   trace("initialize", sig="Superclass", browser)

Now, the specific example.  There are 3 special features used:
1. Nonstandard arguments for the initialize method (its official 
arguments are (.Object, ...))

2. callNextMethod

3. within callNextMethod, providing explicit arguments.  The simple case 
is callNextMethod(), which passes on the arguments to the current method.

Turns out that it's the third step that finds a bug in the heuristics 
used by callNextMethod to construct the actual call.

In your example, you don't need the explicit arguments since they just 
replicate the formal arguments to initialize().  If you omit them, the 
computation is simpler & works.

The bug can probably be fixed, but until 2.2 comes out at least, you 
need to stick to the simpler callNextMethod().


Removing the extraneous cat() and str() calls, the revised example is:

R> setClass("Superclass", representation(id = "character"),
 contains = "VIRTUAL")
[1] "Superclass"

R> setMethod("initialize", signature(.Object = "Superclass"),
 function(.Object, id = "") {
 if (length(id) > 0) {
 [EMAIL PROTECTED] <- i  [TRUNCATED]
[1] "initialize"

R> setClass("Subclass", contains = "Superclass")
[1] "Subclass"

R> setMethod("initialize", signature(.Object = "Subclass"),
 function(.Object, ...) {
 callNextMethod()
 })
[1] "initialize"

R> Subclass <- function(id = "") {
 new("Subclass", id = id)
}

R> new("Subclass", id = "test1")
An object of class “Subclass”
Slot "id":
[1] "test1"


R> Subclass(id = "test2")
An object of class “Subclass”
Slot "id":
[1] "test2"
---
Paul Roebuck wrote:

> Can someone explain what the problem is when I use the
> generating function? And how to get debug() to stop in
> the Superclass initialize method?
> 
> 
>  source -
> setClass("Superclass",
>  representation(id = "character"),
>  contains = "VIRTUAL")
> 
> setMethod("initialize",
>   signature(.Object = "Superclass"),
>   function(.Object, id = "") {
>   cat("initialize (Superclass)", "\n")
>   if (length(id) > 0) {
>   cat("\tid =", id, "\n")
>   [EMAIL PROTECTED] <- id
>   }
>   .Object
>   })
> 
> setClass("Subclass",
>  contains = "Superclass")
> 
> setMethod("initialize",
>   signature(.Object = "Subclass"),
>   function(.Object, ...) {
>   cat("initialize (Subclass)", "\n")
>   cat("\t... =");str(list(...));cat("\n")
>   callNextMethod(.Object, ...)
>   })
> 
> Subclass <- function(id = "") {
> new("Subclass", id = id)
> }
> 
> cat("*** Create class using new() ***\n")
> str(new("Subclass", id = "test1"))
> 
> cat("*** Create class using generating function ***\n")
> str(Subclass(id = "test2"))
> 
> 
>  output -
> *** Create class using new() ***
> initialize (Subclass)
> ... =List of 1
>  $ id: chr "test1"
> 
> initialize (Superclass)
> id = test1
> Formal class 'Subclass' [package ".GlobalEnv"] with 1 slots
>   ..@ id: chr "test1"
> *** Create class using generating function ***
> initialize (Subclass)
> ... =List of 1
>  $ id: chr "test2"
> 
> initialize (Superclass)
> Error in .local(.Object, ...) : Object "id" not found
> 
> 
> Thanks
> 
> --
> SIGSIG -- signature too long (core dumped)
> 
> __
> 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 setClass with prototypes " issues" (PR#8053)

2005-08-05 Thread John Chambers
Well, let's say R is currently picky when only a prototype is supplied.

The following is either a workaround or a revised, fussier requirement 
for the example mentioned, depending on your interpretation.

R> setClass("sequence", representation(.Data="numeric"), 
prototype=numeric(3))
[1] "sequence"
R> xx <- new('sequence',c(1,51,10))
R> xx
An object of class “sequence”
[1]  1 51 10
R> is(xx, "numeric")
[1] FALSE

So far, so good.  But there are a couple of catches.

The resolution of prototype and representation is currently somewhat of 
a mess in the R implementation.  There's been some discussion of 
cleaning it up, hopefully moving ahead from the Green Book description 
to a more coherent definition.  So whether eventually one could (or 
should) omit the representation() part remains to be seen.

The other relevant flaw currently is that S4 objects have no special 
internal representation in R, so there's effectively no way to keep 
primitive operations from working on them. (The general & notorious 
example is that xx[] always returns something on an S4 object, even when 
it shouldn't.)  In the current case, the problem is that, in spite of 
not extending "numeric", low-level arithmetic is still done.

R> xx+1
An object of class “sequence”
[1]  2 52 11

Something basic is needed here, in the code for primitives, but so far 
objections re efficiency have prevented doing anything.

Meanwhile, those more interested in getting something done than 
discussing, would need to implement explicit methods for the new class 
that either re-interpret or block the primitives that shouldn't happen 
in the standard way.


[EMAIL PROTECTED] wrote:

> To R-Developers:
> 
> I wish to report what I believe are inconsistencies between Green Book
> descriptions and R methods behaviors. I **realize** that R does not
> guarantee total consistency with the Green Book; therefore I leave it to you
> to decide whether any of this is a bug, design choice, or a need for
> additional documentation -- or whether I have simply misread or overlooked
> existing explanations. If the latter, I apologize for the error, but it was
> not for a want of effort.
> 
> The issues all revolve around the setClass('xxx',prototype=...) without any
> slots construction. All references are to the Green Book. R 2.1.1 (on
> Windows)
> 
> 1. Classes so defined (with protype, no slots) are not instantiated as
> described on the bottom of p.289. In particular, the following example from
> the book fails:
> 
> 
>>setClass('sequence',prototype=numeric(3))
> 
> [1] "sequence"
> 
>>new('sequence',c(1,51,10))
> 
> Error in initialize(value, ...) : cannot use object of class "numeric" in
> new():  class "sequence" does not extend that class
>  
> 2. I have been unable to find any Help documentation about the proper method
> to instantiate classes defined by prototypes without slots. Experimentation
> showed that only one of the two approaches on the bottom of p.289 worked:
> 
> 
>>setClass('foo',prototype=numeric())
> 
> [1] "foo"
> 
>>z<-new('foo')
> 
> ## new() works as it should
> 
>>z
> 
> An object of class "foo"
> numeric(0)
> 
> ## But now try this ...
> 
>>z<-1:3
>>is(z,'numeric')
> 
> [1] TRUE
> ## Hence, if R followed the book's statement that "For this to work,
> 'object' must either be suitable as a prototype for 'myClass or belong to a
> class that can be coerced to 'myClass.'" (Note, I interpret this to mean
> that either of these conditions are sufficient for either of the approaches
> shown).
> 
> 
>>as(z,'foo')
> 
> Error in as(z, "foo") : no method or default for coercing "integer" to "foo"
> 
> ## But
> 
>>class(z)<-'foo'
>>z
> 
> An object of class "foo"
> [1] 1 2 3
> 
> I was unable to find documentation for this behavior in R, assuming that
> this is not a bug. If it's a bug, it should be fixed, of course; if not, I
> think the behavior should be documented, perhaps in setClass.
> 
> 3. Finally, and most disconcertingly, The Green Book says (p.288):
> 
> "... We do NOT want a 'sequence' object to be interpreted as a numeric
> vector ... Doing arbitrary arithmetic on the object, for example would be
> disastrous...
> 
> The use of prototypes without representations allows the class designer to
> limit the legal computations on objects made up of numeric data..."
> 
> As I read this, this should mean that the following should fail, but it
> doesn't (continuing the above example):
> 
> 
>>z+1
> 
> An object of class "foo"
> [1] 2 3 4
> 
> Again, if this is not a bug, I think that this lack of adherence to the
> Green book should be documented in R. May I say, however, that I wish R had
> implemented the book's prescription.
> 
> 
> -- Bert Gunter
> Genentech Non-Clinical Statistics
> South San Francisco, CA
>  
> "The business of the statistician is to catalyze the scientific learning
> process."  - George E. P. Box
> 
> __
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinf

Re: [Rd] S4 generating function

2005-08-05 Thread John Chambers
Re:
 > If I understand your description correctly, the problem is
 > passing both named and unnamed arguments to callNextMethod().

No, as I said the distinction is a potential bug in callNextMethod 
_whenever_ it gets explicit arguments.  (At the moment, it seems to be a 
bug in substitute() or else a different interpretation of that function 
from the one in the Blue Book.  But I've only looked a little.)

So to work around it you have to be able to do callNextMethod() with no 
arguments.

Just at a guess, you may be able to do that if you avoid redefining the 
formal arguments for the initialize() method.  Leave them as .Object, 
... and extract the id= component.
   dotArgs <- list(...)
   id <- dotArgs$id

Or, wait for a fix.  There should at least be one in r-devel sometime 
fairly soon.


Paul Roebuck wrote:

> On Fri, 5 Aug 2005, John Chambers wrote:
> 
> 
>>Paul Roebuck wrote:
>>
>>
>>>Can someone explain what the problem is when I use the
>>>generating function? And how to get debug() to stop in
>>>the Superclass initialize method?
>>>[SNIP code & output]
>>
>>Now, the specific example.  There are 3 special features used:
>>1. Nonstandard arguments for the initialize method (its official
>>arguments are (.Object, ...))
>>
>>2. callNextMethod
>>
>>3. within callNextMethod, providing explicit arguments.  The simple case
>>is callNextMethod(), which passes on the arguments to the current method.
>>
>>Turns out that it's the third step that finds a bug in the heuristics
>>used by callNextMethod to construct the actual call.
>>
>>In your example, you don't need the explicit arguments since they just
>>replicate the formal arguments to initialize().  If you omit them, the
>>computation is simpler & works.
>>
>>The bug can probably be fixed, but until 2.2 comes out at least, you
>>need to stick to the simpler callNextMethod().
>>[SNIP modified code]
> 
> 
> Thank you for your help. Unfortunately, this is a case where
> posting the simplest code necessary to display the bug works
> against the poster. Actual code uses external pointers but
> this revision shows more of the general concept.
> 
> If I understand your description correctly, the problem is
> passing both named and unnamed arguments to callNextMethod().
> Can I [easily] do either of these things to avoid the bug?
> 
>   1) somehow add an argument to 'dots' and invoke callNextMethod()
>  without arguments?
>   2) parse 'dots' and invoke callNextMethod() with a completely
>  named argument list?
> 
> 
> -- revised source ---
> setClass("Superclass",
>  representation(.values = "integer",
> id  = "character"),
>  contains = "VIRTUAL")
> 
> setMethod("initialize",
>   signature(.Object = "Superclass"),
>   function(.Object, .values = NULL, id = "") {
>   cat("initialize (Superclass)", "\n")
>   if (!is.null(.values)) {
>   cat("\t.values =", .values, "\n")
>   [EMAIL PROTECTED] <- .values
>   }
>   if (length(id) > 0) {
>   cat("\tid =", id, "\n")
>   [EMAIL PROTECTED] <- id
>   }
>   .Object
>   })
> 
> setClass("Subclass",
>  contains = "Superclass")
> 
> setMethod("initialize",
>   signature(.Object = "Subclass"),
>   function(.Object, count = 1, ...) {
>   cat("initialize (Subclass)", "\n")
>   dots <- list(...)
>   cat("\t... =");str(dots);cat("\n")
>   .values = integer(count)
>   callNextMethod(.Object, .values = .values, ...)
>   })
> 
> Subclass <- function(count, id = "") {
> new("Subclass", count, id = id)
> }
> 
> cat("*** Create class using new() ***\n")
> str(new("Subclass", id = "test0"))
> str(new("Subclass", count = 3, id = "test1"))
> 
> cat("*** Create class using generating function ***\n")
> #trace("initialize", signature = "Subclass", browser)
> str(Subclass(count = 3, id = "test2"))
> 
> --
> SIGSIG -- signature too long (core dumped)
>

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


Re: [Rd] Registering S3 class from external package

2005-08-18 Thread John Chambers
Your description is a bit too vague to be sure, but it sounds as if 
you're trying to do something that breaks the basic namespace idea.

Paul Roebuck wrote:

> The package I'm working on can extract data from external
> packages but would otherwise have no dependency on them.
> However, I desire to be able to dispatch based on an
> external S3 class if its package is attached (.First.lib).

Dispatch from where?  If you mean from a generic function inside your 
package's namespace, then the corresponding class definitions need to be 
defined in or imported into that namespace when it's constructed.  One 
of the main virtues of the namespace mechanism is that the known classes 
(& therefore the dispatch behavior) are fixed by the package source + 
its imports.  This means that the behavior of the package is insulated 
against effects from attaching other packages.

OTOH, if you mean dispatch from a generic function in the global 
environment or another (non-NAMESPACE) package, then you need to ensure 
that the setOldClass() takes place in the appropriate environment; e.g. 
if the generic is in the global environment,
   setOldClass(c("foo", "bar"), where = .GlobalEnv)
If you're dispatching from a generic in "somepkg", the setOldClass call 
should just be a part of the source for that package.
But, again, these will not help if you're dispatching from the mypkg 
namespace; that's just what the mechanism is trying to avoid.

In case it's not clear, the setOldClass() call defines a special kind of 
  S4 class for each of the S3 classes.  Therefore it's subject to the 
same locking rules as setClass() or any other call that needs to do an 
assignment as a side effect.


> My code is S4-based and its package has NAMESPACE.
> 
> Registering the external class prior to the other
> package being attached doesn't seem to work so I am
> attempting to perform the registration once the other
> package has done so. But my namespace is locked by the
> time this occurs. Can someone either tell me how to do
> this, suggest a better alternative, or point me to
> another package that does something similar?
> 
> Current attempt is something like the following:
> 
>   setHook(packageEvent("somepkg", "attach"),
>   function(...) {
>   cat("* Register", sQuote("oldstyle"),
>   "as S3 class", "\n")
>   setOldClass(c("oldstyle", "data.frame"),
>   where = asNamespace("mypkg"))
>   })
> 
> 
> -
> 
>>require(mypkg)
> 
> Loading required package: mypkg
> ...
> 
>>require(somepkg)
> 
> Loading required package: somepkg
> * Register 'oldstyle' as S3 class
> Error in assign(classMetaName(Class), def, where) :
> cannot add bindings to a locked environment
> 
>>R.version.string
> 
> [1] "R version 2.1.1, 2005-06-20"
> 
> --
> SIGSIG -- signature too long (core dumped)
> 
> __
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
> 
> 
> !DSPAM:42fb68c222117714262142!
>

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


Re: [Rd] failure in `setClass' examples

2005-11-22 Thread John Chambers
There's nothing bad happening, and we should remove the setIs() example 
from the setClass() documentation.

If you run example(setIs), you will see a slightly different version of 
the same call to setIs(), but one that does not generate the warning 
(because it includes the argument replace= to setIs()). Comparing the 
two calls and looking at the documentation for setIs should explain 
where the warning comes from.  But in any case, nothing to worry about.

John Chambers.

Sebastian Luque wrote:
> Hello,
> 
> Below is what I got running the examples from `setClass'.  Could somebody
> please help explain why the last `setIs' call is returning the warning and
> whether this is expected?
> 
> 
> R>  setClass("track",
> +   representation(x="numeric", y="numeric"))
> [1] "track"
> R>  setClass("trackCurve",
> +   representation("track", smooth = "numeric"))
> [1] "trackCurve"
> R>  setClass("trackMultiCurve",
> +   representation(x="numeric", y="matrix", smooth="matrix"),
> +   prototype = list(x=numeric(), y=matrix(0,0,0),
> +smooth= matrix(0,0,0)))
> [1] "trackMultiCurve"
> R>  try(setIs("trackMultiCurve", "trackCurve",
> +  test = function(obj) {ncol(slot(obj, "y")) == 1}))
> Warning message:
> there is no automatic definition for as(object, "trackCurve") <- value when 
> object has class "trackMultiCurve" and no 'replace' argument was supplied; 
> replacement will be an error in: makeExtends(class1, class2, coerce, test, 
> replace, by, classDef1 = classDef,  
> R>  setIs("trackMultiCurve", "trackCurve",
> +test = function(obj) {ncol(slot(obj, "y")) == 1},
> +coerce = function(obj) {
> +   new("trackCurve",
> +   x = slot(obj, "x"),
> +   y = as.numeric(slot(obj,"y")),
> +   smooth = as.numeric(slot(obj, "smooth")))
> +})
> Warning message:
> there is no automatic definition for as(object, "trackCurve") <- value when 
> object has class "trackMultiCurve" and no 'replace' argument was supplied; 
> replacement will be an error in: makeExtends(class1, class2, coerce, test, 
> replace, by, classDef1 = classDef,  
> R> version
>  _
> platform i486-pc-linux-gnu
> arch i486 
> os   linux-gnu
> system   i486, linux-gnu  
> status
> major2
> minor2.0  
> year 2005 
> month10   
> day  06   
> svn rev  35749
> language R
> 
> 
> Thanks in advance,
>

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


Re: [Rd] Wish list

2006-01-02 Thread John Chambers

I very much share Duncan's concern that research in statistical software 
should move ahead, and contribute to some of the exciting new uses of 
data we see.

R is the most striking success in statistical software over the last 
decade, in terms of the variety and quantity of statistical technology 
it's made available.  The R mechanism for managing the system and making 
packages available is very effective for sharing statistical 
techniques.  I think the community owes a big debt to the people in R 
core and others who've made this happen.

But the most striking current developments in how data & information are 
collected and used are taking place largely outside our context.  The 
software implemented in R and the people involved could add some 
important abilities that won't be available otherwise.  How do we get 
from here to there, though?  The very success of R tends to push against 
major changes, as opposed to incremental additions.

Thinking about the situation now versus the way S developed starting 
about 30 years ago, I see differences in the context, technical and 
human, that challenge us.

Technical challenges: 
Mainly, the obvious difference is the scale of current hardware and 
software, and the speed with which new technology arises.  I think this 
means our response has to emphasize components, and interfaces that work 
_with_ other systems, including R.

Human challenges:
As S grew, we had a group of about 2-6 people working together with  
support for risk-taking research aimed at major changes.   How do we get 
a critical mass going for the next breakthrough?  We need people working 
closely together, we need support, and we need to include teaching and 
graduate research, all required to keep good research going in this area.


Duncan Temple Lang wrote:

> ...
>
>
>And while we are on the topic of wishlists...
>Generally (i.e. not directed specifically to Gabor),
>the suggestions are very welcome, but so are contributions.
>And for issues such as making the existing R available on handhelds,
>that is a programming task. And I draw a large distinction between
>programming and creative research which is based on new concepts and
>paradigms.  The pool of people working in statistical computing research
>is very small. And to a large extent, their time is consumed with
>programming - making the same thing work on multiple platforms,
>correcting documentation, etc. which are good things, but
>not obviously the best use of available research ability and time.
>There are many more topics that are in progress that represent
>changes to what we can do  rather than just to how we do the same thing.
>
>One of the reasons S (R and S-Plus) is where it is now
>is because in Bell Labs, the idea was to be thinking
>5 years ahead and both meeting and directing the needs for the future.
>Because of R's popularity (somewhat related to it being free), there is
>an aspect of development that focuses more on software for statisticians
>to use "right now".
>Obviously, th development is a mixture of both the current and the
>future, but there is less of the future and certainly less of the
>longer term directions that is sacrificed by the need to maintain an
>existing system and be backward-compatible.
>If statistics is to fulfill its potential in this modern IT, we need new
>ideas and research into those new ideas. If we focus on basic
>programming tasks (however complex) and demand usability above concepts,
>we risk losing those whose primary focus is in statistical computing
>research from the field.
>
>While R provides statisticians and stat. comp. researchers with a
>terrific vehicle for doing their respective work, it also acts as
>a constraint for doing anything even moderately new. But much (not all)
>of R is based on innovations from the 1970's, 80's and 90's.   And
>as IT evolves at a terrific pace, to keep up with it, we need to be
>forward looking.
>
>
>I'll leave it there - for the moment - and go fight off the ants
>that are invading my desk!  While I wrote this down relatively
>rapidly, the ideas have been brewing for a long time. If anyone
>wishes to comment on the theme, I hope they will take a few minutes
>to think about the broad set of issues and tradeoffs.
>
>
>  D.
>
>
>  
>
>>__
>>R-devel@r-project.org mailing list
>>https://stat.ethz.ch/mailman/listinfo/r-devel
>>
>>
>
>- --
>Duncan Temple Lang[EMAIL PROTECTED]
>Department of Statistics  work:  (530) 752-4782
>4210 Mathematical Sciences Building   fax:   (530) 752-7099
>One Shields Ave.
>University of California at Davis
>Davis,
>CA 95616,
>USA
>-BEGIN PGP SIGNATURE-
>Version: GnuPG v1.4.2 (Darwin)
>
>iD8DBQFDt/by9p/Jzwa2QP4RAr6UAJ4mT9C1JcGwlFFJRFVDteyetDrAjACfax7B
>0MpswqQE442j23WzJjqUADA=
>=Aq8t
>-END PGP SIGNATURE-
>
>__
>R-devel@r-project.org mailing list
>

Re: [Rd] S4 default initialization: unwanted NULL

2006-01-03 Thread John Chambers
S3 classes are treated as virtual classes, with or without a call to 
setOldClass()--the purpose of setOldClass() is to make method dispatch 
with S3 inheritance work.

It's legal to have virtual classes as slots, but yes, the slot is NULL 
in the prototype for the new class, unless the user specifies a value.  
In your case, providing a non-null prototype for the data.frame slot 
might be the desired solution.

There is no S4 "initialization" for S3 classes; in fact, it's generally 
an error to use new() on them (or on other virtual classes).

 > getClass("data.frame")
Virtual Class

No Slots, prototype of class "NULL"

Extends: "oldClass"

Known Subclasses: "anova"

 > new("data.frame")
Error in new("data.frame") : trying to use new() on a virtual class


John

PS: it's possible to imagine an extended version of setOldClass() that 
made S3 classes into non-virtual S4 classes.  Worth discussion, but a 
definite change to current design.


Matthias Kohl wrote:

>you might need a call to "setOldClass"; see Section "Register or 
>Convert?" of the corresponding help page.
>
>Matthias
>
>Seth Falcon schrieb:
>
>  
>
>>The default initialization for slots of class "factor" and
>>"data.frame" gives NULL.  This seems odd, since those slots can't ever
>>be set to NULL by the user.  I would expect zero-length instances of
>>factor and data.frame.
>>
>>Here is an example:
>>
>>setClass("FOO", representation(a="factor", b="data.frame", c="numeric"))
>>[1] "FOO"
>> 
>>
>>
>>
>>>ff <- new("FOO")
>>>ff
>>>   
>>>
>>>  
>>>
>>An object of class "FOO"
>>Slot "a":
>>NULL
>>
>>Slot "b":
>>NULL
>>
>>Slot "c":
>>numeric(0)
>>
>>
>>sessionInfo()
>>R version 2.3.0, 2005-12-26, powerpc-apple-darwin8.3.0 
>>
>>attached base packages:
>>[1] "tools" "methods"   "stats" "graphics"  "grDevices" "utils"
>>[7] "datasets"  "base" 
>>
>>
>>Slot c is initialized as I was expecting.
>>
>>+ seth
>>
>>__
>>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 default initialization: unwanted NULL

2006-01-03 Thread John Chambers
Seth Falcon wrote:

>On  3 Jan 2006, [EMAIL PROTECTED] wrote:
>  
>
>>It's legal to have virtual classes as slots, but yes, the slot is
>>NULL in the prototype for the new class, unless the user specifies a
>>value.  In your case, providing a non-null prototype for the
>>data.frame slot might be the desired solution.
>>
>>
>
>Yes, that's a workaround.  
>
>  
>
>>There is no S4 "initialization" for S3 classes; in fact, it's
>>generally an error to use new() on them (or on other virtual
>>classes).
>>
>>
>
>The "basic vector classes" (see man page for new) can be created
>with new().  From my perspective it would be more consistent if
>data.frame and factor behaved similarly.  
>  
>
The basic classes are set up specially, as "real" S4 classes.  In a 
sense, it would be more consistent NOT to do this & have them be S3 
classes as well, but I assume you're not suggesting that ;-)

The reason that S3 classes are generally virtual is simple:  there is no 
metadata information to tell the system anything at all about the 
objects from the class, and in particular what a prototype object would 
be.  Therefore, new() doesn't know what to return.

In a future version, we could augment setOldClass() to provide such 
information, but it remains true that some S3 classes don't behave like 
legal S4 classes (e.g., different objects from the class can have 
different "slots").

>I admit that I don't understand why data.frame and factor are virtual
>classes and don't know what would be involved to have new() work for
>data.frame and factor.
>
>+ seth
>
>__
>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] match gets confused by S4 objects

2006-02-07 Thread John Chambers
In fact there is a heuristic test that is cheap and reasonably 
reliable.  The class attribute generated for S4 objects itself has an 
attribute, "package".  A C-level test for the existence of that 
attribute is cheap enough, I would think, that most anti-S4 users 
wouldn't notice it in match(), c(), etc.  Of course, nothing prevents 
someone from putting a package attribute on an S3 class, but it seems 
unlikely.

This is _not_ the right solution, which most everyone agrees is to have 
an explicit SEXP.  But it should bridge the gap until someone with 
sufficient knowledge of R internals implements that solution.

There is one catch, but it doesn't seriously affect tests for match(), 
etc.  Two of the built-in S4 classes don't currently have a "package" 
attribute; it's just a slipup in the bootstrapping of S4 classes.  Easy 
to fix, but it means that the test won't work for code designed _for_ S4 
classes unless all packages are re-installed with the fixed version.  
For this reason, I haven't committed the change.

The catch is not a serious problem if the code in question was not meant 
to work for S4 objects in the first place: weird things will happen if 
someone applies match() to a class representation object, for example, 
which presumably no one would do just for the sake of generating an error.

I'll try to commit the new test sometime soon & if there are no serious 
problems,  we can start including it in some of the relevant functions.



Seth Falcon wrote:

>On  7 Feb 2006, [EMAIL PROTECTED] wrote:
>  
>
>>The solution has been agreed to be changing the internal
>>representation of S4 objects making them a new SEXP (basic R
>>"type"); and as Brian alludes to, the problem is that those in
>>R-core that want to and are able to do this didn't have the time
>>for that till now.
>>
>>
>
>The explanations from you are Brian are helpful, thanks.  I was aware
>that the issue is the internal representation of S4 objects and was
>hoping there might be a cheap work around until a new SEXP comes
>around.
>
>It seems that S4 instances are less trivial to detect than one might
>expect before actually trying it.  
>
>I suppose one work around is to have an S4Basic class that defines
>methods for match(), c(), etc and raises an error.  Then extending
>this class gives you some protection.
>
>+ seth
>
>__
>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 John Chambers

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



__
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 John Chambers


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




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


Re: [Rd] Creating an environment with attributes in a package

2010-07-16 Thread John Chambers
Note that S4 classes extend "environment" and other reference types, by 
using a hidden slot.  You can then add other slots.  So, with some extra 
work:


> setClass("myEnv", contains = "environment",
+ representation(myName = "character"))
[1] "myEnv"
> Foo <- new("myEnv", myName = "Foo")
> Foo
An object of class "myEnv"

Slot "myName":
[1] "Foo"

There are a few holes in the implementation as of R 2.11.1, which are 
being filled in r-devel.  Partly to support some new applications for 
extensions of environments, which I hope to commit today (stay tuned to 
this list).



On 7/16/10 5:51 AM, Jon Clayden wrote:

On 16 July 2010 13:32, Hadley Wickham  wrote:

On Fri, Jul 16, 2010 at 2:08 PM, Jon Clayden  wrote:

Dear all,

I am trying to create an environment object with additional attributes, viz.

Foo<- structure(new.env(), name="Foo")

Doing this in a standard session works fine: I get the environment
with attr(,"name") set as expected. But if the same code appears
inside a package source file, I get just the plain environment with no
attributes set. Using a non-environment object works as I would expect
within the package (i.e. the attributes remain).

I've looked through the documentation for reasons for this, and the
only thing I've found is the mention in the language definition that
"assigning attributes to an environment can lead to surprises". I'm
not sure if this is one of the surprises that the author(s) had in
mind! Could someone tell me whether this is expected, please?


You'll be much less surprised if you do:

Foo<- structure(list(new.env()), name="Foo")

Attributes on reference objects are also passed by reference, and
surprises will result.


Ah, it's good to know the core reason for the "surprises"! Sounds like
the best thing is to refactor things as you suggest.

Many thanks for all the responses.

Regards,
Jon

__
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


[Rd] Inserting and testing revised functions in a package

2010-07-16 Thread John Chambers
A new facility has been added to r-devel for experimenting by authors of 
packages.

The idea is to insert modified code from the package source into the 
running package without re-installing.  So one can change, test, change, 
etc in a quick loop.

The mechanism is to evaluate some files of source code, returning an 
environment object which is a snapshot of the code.  From this 
environment, functions and methods can be inserted into the environment 
of the package in the current session.  The insertion uses the trace() 
mechanism, so the original code can be restored.

The one-step version is:
   insertSource("mySourceFile.R", package = "myPackage", functions = "foo")

This is intended specially for those of us who own largish packages. (It 
proved useful in debugging itself, e.g.)  You can use the other trace() 
mechanisms with it, with a little care, as well as debug() etc.

For the moment it only works on functions and S4 methods, via trace().  
There are a number of possible future applications, both for 
insertSource and for the underlying snapshot environments as records of 
the state of the code.

The code was added today (revision 52545)  See ?insertSource for 
details, a piece of the documentation is at the end of this mail.

Cheers,
   John


  Usage

evalSource(source, package = "", lock = TRUE, cache = FALSE)

insertSource(source, package = "", functions = , methods = )



  Details

The |source| file is parsed and evaluated, suppressing by default the 
actual caching of method and class definitions contained in it, so that 
functions and methods can be tested out in a reversible way. The result, 
if all goes well, is an environment containing the assigned objects and 
metadata corresponding to method and class definitions in the source file.

 >From this environment, the objects are inserted into the package, into 
its namespace if it has one, for use during the current session or until 
reverting to the original version by a call to untrace(). The insertion 
is done by calls to the internal version of |trace()|, to make reversion 
possible.

Because the trace mechanism is used, only function-type objects will be 
inserted, functions themselves or S4 methods.

When the |functions| and |methods| arguments are both omitted, 
|insertSource| selects all suitable objects from the result of 
evaluating the |source| file.

In all cases, only objects in the source file that differ from the 
corresponding objects in the package are inserted. The definition of 
"differ" is that either the argument list (including default 
expressions) or the body of the function is not identical. Note that in 
the case of a method, there need be no specific method for the 
corresponding signature in the package: the comparison is made to the 
method that would be selected for that signature.


[[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 John Chambers
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



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


Re: [Rd] Bug: broken exception handling in S4 methods

2010-07-21 Thread John Chambers
The problem in this example is (plausibly) that the argument evaluation 
code in method selection itself uses an internal C-level version of 
try(), overriding the user's setting.


If this is the bug, I'll have to defer to more expert advice on whether, 
and if so how, the code can adjust for the current exception handling. 
(There don't seem to be many uses of this R_try() mechanism.)



On 7/21/10 2:36 AM, Sklyar, Oleg (London) wrote:

Hi all:

we have noticed for quite a while that certain errors cannot be handled
by R try, tryCatch etc blocks, but it was fairly difficult to understand
what were the conditions for this incorrect behaviour. Finally I stabbed
across a very understandable case, which is outlined in the (runnable)
example below.

The main message is: wrapping an S4 method call in a try block will not
help if an error occurs in evaluating an argument to such a call; this
works just fine for function calls (as opposed to S4 methods)

The particular example is a result of trying to write a unit test for a
constructor of a class object which should fail under certain
conditions. This failure obviously need to be caught for the unit test
to proceed. However, it is a general problem with handling some
exceptions in R.

# Consider a simple class MyClassA, which is derived from numeric and
for which
# we define a constructor (in form of a method). On its own this class
works nicely
# and so does exception handling of it:

setClass("MyClassA",
 contains = "numeric",
 validity = function(object)
 {
 stopifnot(object[1] == object[2])
 TRUE
 }
)


setGeneric("MyClassA", function(x) standardGeneric("MyClassA"))

setMethod("MyClassA",
 signature(x = "numeric"),
 function(x)
 {
 new("MyClassA", x)
 }
)

## OK
er = try({ MyClassA(c(1,2)) })

## OK (error in constructor)
er = try({ MyClassA(c(1,2)) })

## OK (error evaluating argument to a function)
er = try({ sin(MyClassA(c(1,2))) })


# Now consider we define MyClassB that has MyClassA in a slot
# and we define a constructor that takes such objects:


setClassUnion("MyClassAOrNULL", c("MyClassA", "NULL"))

setClass("MyClassB",
 representation(
 ca = "MyClassAOrNULL"
 ),
 prototype(ca = NULL)
)

setGeneric("MyClassB", function(x) standardGeneric("MyClassB"))

setMethod("MyClassB",
 signature(x = "MyClassA"),
 function(x)
 {
 new("MyClassB", ca = x)
 }
)

## OK
b = MyClassB(MyClassA(c(1,1)))

## FAILS (error evaluating argument to a method)
er = try({ MyClassB(MyClassA(c(1,2))) })

# As you see the last error cannot be handled


# Moreover. If we define a function and a method as function(x) x then
# the function can be handled by try, yet the method cannot:

f = function(x) x

setGeneric("g", function(x) standardGeneric("g"))
setMethod("g", "MyClassA", function(x) x)

## OK (error evaluating argument to a function)
er = try({ f(MyClassA(c(1,2))) })

## FAILS (error evaluating argument to a method)
er = try({ g(MyClassA(c(1,2))) })




sessionInfo()

R version 2.11.0 Patched (2010-05-05 r51914)
x86_64-unknown-linux-gnu

locale:
  [1] LC_CTYPE=en_GB   LC_NUMERIC=C LC_TIME=en_GB
LC_COLLATE=en_GB
  [5] LC_MONETARY=CLC_MESSAGES=en_GBLC_PAPER=en_GB
LC_NAME=C
  [9] LC_ADDRESS=C LC_TELEPHONE=C   LC_MEASUREMENT=en_GB
LC_IDENTIFICATION=C

attached base packages:
[1] splines   stats graphics  utils datasets  grDevices methods
base


Dr Oleg Sklyar
Research Technologist
AHL / Man Investments Ltd
+44 (0)20 7144 3803
oskl...@ahl.com

**
  Please consider the environment before printing this email or its attachments.
The contents of this email are for the named addressees ...{{dropped:19}}

__
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] new.env does not recognize parents from subclasses of "environment"

2010-10-20 Thread John Chambers
 Thanks for the report.  Should now be fixed in r-devel and 2.12 
patched (rev 53383).


Please do report any cases where a subclass of environment doesn't 
work.  There are some known cases in locking and active binding, that 
will be fixed in due course.


The workaround for any such problem is usually as.environment().

On 10/20/10 3:17 AM, Vitaly S. wrote:

Dear Developers,

A lot has been changed in the R12.0 with respect to behavior of "environment"
subclasses.  Many thanks for that.

One small irregularity, though; new.env does not allow the parent to be from S4
subclass.



setClass("myenv", contains="environment")

[1] "myenv"

new.env(parent=new("myenv"))

Error in new.env(parent = new("myenv")) : 'enclos' must be an environment

I wonder if this is a "planed" behavior.

The use of .xData  slot obviously works:

new.env(parent=new("myenv")@.xData)


Thanks,
Vitaly.

__
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] new.env does not recognize parents from subclassesof "environment"

2010-10-21 Thread John Chambers
 This is a problem related to the introduction of exact= into the [[ 
and [[<- functions. As Bill says, the current method misuses 
eval.parent() when that argument is added.


However, a simpler and more efficient solution is to migrate the checks 
for subclasses of "environment" used in other base code into the code 
for [[<- (and for $<-), at which point the methods for these functions 
are no longer needed.


A solution on these lines is being tested now and will find its way into 
r-devel and 2.12 patched.


One other point about the original posting:

Please don't use constructions like e...@.xdata. This depends on the 
current implementation and is not part of the user-level definition. Use 
as(env, "environment") or equivalent. (In this case, the assignment of 
the object's own environment was irrelevant to the error.)


John Chambers

On 10/21/10 9:21 AM, William Dunlap wrote:

The traceback looks very similar to a problem
in R 2.11.1 reported earlier this month by Troy Robertson.
   >  From: r-devel-boun...@r-project.org
   >  [mailto:r-devel-boun...@r-project.org] On Behalf Of Troy Robertson
   >  Sent: Wednesday, October 06, 2010 6:13 PM
   >  To: 'r-devel@R-project.org'
   >  Subject: Re: [Rd] Recursion error after upgrade to
   >  R_2.11.1[Sec=Unclassified]
It was due to a miscount of how many frames to go
up before evaluating an expression in
getMethod("[[<-",".environment") because setMethod()
introduced a local function in the new method.

Bill Dunlap
Spotfire, TIBCO Software
wdunlap tibco.com


-Original Message-
From: r-devel-boun...@r-project.org
[mailto:r-devel-boun...@r-project.org] On Behalf Of Vitally S.
Sent: Thursday, October 21, 2010 9:00 AM
To: John Chambers
Cc: r-devel@r-project.org
Subject: Re: [Rd] new.env does not recognize parents from
subclassesof "environment"



Here is an infinite recursion error  which occurs only with S4
subclasses assignment.

  setClass("myenv", contains = "environment")
#[1] "myenv"
  env<- new("myenv")
  env[[".me"]]<- ∑
#Error: evaluation nested too deeply: infinite recursion /
options(expressions=)?


With basic types it works as expected:

env1<- new.env()
env1[[".me"]]<- env1

May be this is related to active bindings that you mentioned,
  but I am still
reporting it here.

Vitally.



  Thanks for the report.  Should now be fixed in r-devel and

2.12 patched (rev 53383).

Please do report any cases where a subclass of environment

doesn't work.  There are some known cases in locking and

active binding, that will be fixed in due course.

The workaround for any such problem is usually as.environment().

On 10/20/10 3:17 AM, Vitaly S. wrote:

Dear Developers,

A lot has been changed in the R12.0 with respect to

behavior of "environment"

subclasses.  Many thanks for that.

One small irregularity, though; new.env does not allow the

parent to be from S4

subclass.



setClass("myenv", contains="environment")

[1] "myenv"

new.env(parent=new("myenv"))

Error in new.env(parent = new("myenv")) : 'enclos' must be

an environment

I wonder if this is a "planed" behavior.

The use of .xData  slot obviously works:

new.env(parent=new("myenv")@.xData)


Thanks,
Vitaly.

__
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



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


Re: [Rd] Reference classes

2010-10-22 Thread John Chambers

Last question first:

>
> More generally, I was wondering how firm the commitment is to
> providing this kind of programming mechanism. I know it's likely to
> change in some ways in future releases, but can I use it in packages,
> trusting that only a few tweaks will be needed for compatibility with
> future versions of R, or is it possible that the whole infrastructure
> will be removed in future?
>

Speaking just for myself, I'd say it's pretty solid.  Reasons:

 - it's essentially an add-on and essentially all R code, so as long as 
there is some interest, it's not hurting other code--it builds directly 
on some valuable existing tools for environments, such as active bindings;


 - this is something I've wanted to do for a while.  The essential step 
was being able to subclass environments, and that has been in place for 
some time now;


 - initial experience has been largely positive.  The Rcpp package in 
its newest version depends on reference classes.


Now as to what "tweaks" will be needed, that remains to be seen.  But my 
guess is that most will be issues of implementation.  The user interface 
is sufficiently standardized among languages that it has a reasonable 
chance to stay compatible.


Other comments below.

John


On 10/22/10 7:21 AM, Jon Clayden wrote:

Dear all,

First, many thanks to John Chambers, and anyone else who was involved,
for the new support for "reference classes" in R 2.12.0. It's nice to
see this kind of functionality appear in a relatively R-like form, and
with the blessing of the core team. In some contexts it is undoubtedly
appealing to associate a set of methods with a class directly, rather
than defining a load of generics which are only ever likely to be
implemented for a single class, or some other such arrangement. (I was
actually in the process of writing a package which did something
similar to the reference class idea, although it is less fully
realised.)

My initial experiences with this functionality have been very
positive. I've stumbled over one minor issue so far: default values of
method parameters are not displayed by the help() method, viz.


library(methods)
Regex<- setRefClass("Regex", fields="string", methods=list(

+ isMatch = function (text, ignoreCase = FALSE)
+ {
+ 'Returns a logical vector of the same length as "text",
indicating whether or not each element is a match to the regular
expression.'
+ grepl(string, text, ignore.case=ignoreCase, perl=TRUE)
+ }
+ ))

Regex$help("isMatch")

Call: $isMatch(text, ignoreCase = )

Returns a logical vector of the same length as "text", indicating
whether or not each element is a match to the regular expression.

It seems unlikely that this is intentional, but correct me if I'm
wrong. It still seems to happen with the latest R-patched (Mac OS X
10.5.8).


It's a bug.


As a suggestion, it would be nice if the accessors() method could be
used to create just "getters" or just "setters" for particular fields,
although I realise this can be worked around by removing the unwanted
methods afterwards.


In other words, read-only fields.  There is a facility for that 
implemented already, but it didn't yet make it into the documentation, 
and it could use some more testing.  The generator object has a $lock() 
method that inserts a write-once type of method for one or more fields. 
 Example:


> fg <- setRefClass("foo", list(bar = "numeric", flag = "character"),
+ methods = list(
+ addToBar = function(incr) {
+ b = bar + incr
+ bar <<- b
+ b
+ }
+ ))
> fg$lock("bar")
> ff = new("foo", bar = 1.5)
> ff$bar <- 2
Error in function (value)  : Field "bar" is read-only

A revision will document this soon.

(And no, the workaround is not to remove methods.  To customize access 
to a field, the technique is to write an accessor function for the field 
that, in this case, throws an error if it gets an argument.  See the 
documentation for the fields argument.  The convention here and the 
underlying mechanism are taken from active bindings for environments.)




More generally, I was wondering how firm the commitment is to
providing this kind of programming mechanism. I know it's likely to
change in some ways in future releases, but can I use it in packages,
trusting that only a few tweaks will be needed for compatibility with
future versions of R, or is it possible that the whole infrastructure
will be removed in future?

All the best,
Jon

__
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] new.env does not recognize parents from subclassesof "environment"

2010-10-22 Thread John Chambers
 You need to update your version of R (r-devel or 2.12 patched) to rev
53385 or later, and read NEWS, particularly the line:


- Assignment of an environment to functions or as an attribute to other
objects now works for subclasses of "environment".



On 10/22/10 10:20 AM, Vitally S. wrote:
> Yet another inconsistency. environment<- does not work with S4:
>
>
>> setClass("myenv", contains = "environment")
> [1] "myenv"
>> env <- new("myenv")
>> tf <- function(x){x}
>> environment(tf) <- env
> Error in environment(tf) <- env : 
>   replacement object is not an environment
>
>
> Vitally.
>
>
> John Chambers  writes:
>>  This is a problem related to the introduction of exact= into the [[ and 
>> [[<- functions. As Bill says, the current
>> method misuses eval.parent() when that argument is added.
>>
>> However, a simpler and more efficient solution is to migrate the checks for 
>> subclasses of "environment" used in
>> other base code into the code for [[<- (and for $<-), at which point the 
>> methods for these functions are no longer
>> needed.
>>
>> A solution on these lines is being tested now and will find its way into 
>> r-devel and 2.12 patched.
>>
>> One other point about the original posting:
>>
>> Please don't use constructions like e...@.xdata. This depends on the current 
>> implementation and is not part of the
>> user-level definition. Use as(env, "environment") or equivalent. (In this 
>> case, the assignment of the object's own
>> environment was irrelevant to the error.)
>>
>> John Chambers
>>
>> On 10/21/10 9:21 AM, William Dunlap wrote:
>>> The traceback looks very similar to a problem
>>> in R 2.11.1 reported earlier this month by Troy Robertson.
>>>>  From: r-devel-boun...@r-project.org
>>>>  [mailto:r-devel-boun...@r-project.org] On Behalf Of Troy Robertson
>>>>  Sent: Wednesday, October 06, 2010 6:13 PM
>>>>  To: 'r-devel@R-project.org'
>>>>  Subject: Re: [Rd] Recursion error after upgrade to
>>>>  R_2.11.1[Sec=Unclassified]
>>> It was due to a miscount of how many frames to go
>>> up before evaluating an expression in
>>> getMethod("[[<-",".environment") because setMethod()
>>> introduced a local function in the new method.
>>>
>>> Bill Dunlap
>>> Spotfire, TIBCO Software
>>> wdunlap tibco.com
>>>
>>>> -Original Message-
>>>> From: r-devel-boun...@r-project.org
>>>> [mailto:r-devel-boun...@r-project.org] On Behalf Of Vitally S.
>>>> Sent: Thursday, October 21, 2010 9:00 AM
>>>> To: John Chambers
>>>> Cc: r-devel@r-project.org
>>>> Subject: Re: [Rd] new.env does not recognize parents from
>>>> subclassesof "environment"
>>>>
>>>>
>>>>
>>>> Here is an infinite recursion error  which occurs only with S4
>>>> subclasses assignment.
>>>>
>>>>   setClass("myenv", contains = "environment")
>>>> #[1] "myenv"
>>>>   env<- new("myenv")
>>>>   env[[".me"]]<- ∑
>>>> #Error: evaluation nested too deeply: infinite recursion /
>>>> options(expressions=)?
>>>>
>>>>
>>>> With basic types it works as expected:
>>>>
>>>> env1<- new.env()
>>>> env1[[".me"]]<- env1
>>>>
>>>> May be this is related to active bindings that you mentioned,
>>>>   but I am still
>>>> reporting it here.
>>>>
>>>> Vitally.
>>>>
>>>>
>>>>>   Thanks for the report.  Should now be fixed in r-devel and
>>>> 2.12 patched (rev 53383).
>>>>> Please do report any cases where a subclass of environment
>>>> doesn't work.  There are some known cases in locking and
>>>>> active binding, that will be fixed in due course.
>>>>>
>>>>> The workaround for any such problem is usually as.environment().
>>>>>
>>>>> On 10/20/10 3:17 AM, Vitaly S. wrote:
>>>>>> Dear Developers,
>>>>>>
>>>>>> A lot has been changed in the R12.0 with respect to
>>>> behavior of "environment"
>>>>>> subclasses.  Many thanks for that.
>>>>>>
>>>>>> One small irregularity, though; new.env does not allow the
>>>> parent to be from S4
>>>>>> subclass.
>>>>>>
>>>>>>
>>>>>>> setClass("myenv", contains="environment")
>>>>>> [1] "myenv"
>>>>>>> new.env(parent=new("myenv"))
>>>>>> Error in new.env(parent = new("myenv")) : 'enclos' must be
>>>> an environment
>>>>>> I wonder if this is a "planed" behavior.
>>>>>>
>>>>>> The use of .xData  slot obviously works:
>>>>>>> new.env(parent=new("myenv")@.xData)
>>>>>> 
>>>>>> Thanks,
>>>>>> Vitaly.
>>>>>>
>>>>>> __
>>>>>> 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>>
>> __
>> 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

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


Re: [Rd] Reference classes

2010-10-22 Thread John Chambers

One correction:

On 10/22/10 10:55 AM, John Chambers wrote:
.


As a suggestion, it would be nice if the accessors() method could be
used to create just "getters" or just "setters" for particular fields,
although I realise this can be worked around by removing the unwanted
methods afterwards.


In other words, read-only fields. There is a facility for that
implemented already, but it didn't yet make it into the documentation,
and it could use some more testing. The generator object has a $lock()
method that inserts a write-once type of method for one or more fields.
Example:

 > fg <- setRefClass("foo", list(bar = "numeric", flag = "character"),
+ methods = list(
+ addToBar = function(incr) {
+ b = bar + incr
+ bar <<- b
+ b
+ }
+ ))
 > fg$lock("bar")
 > ff = new("foo", bar = 1.5)
 > ff$bar <- 2
Error in function (value) : Field "bar" is read-only




Actually it is documented in the section on generator objects.  But 
since I also didn't see it, maybe it needs an example.  ;-)


John

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


Re: [Rd] Plans for tighter integration of reference classes in R.

2010-10-23 Thread John Chambers
  For reference classes (and other R code) it's important to distinguish 
the application program interface from the implementation.  Anyone is 
welcome to explore the implementation, but we reserve the right to 
change that, particularly with a new feature in the language.

The draft API for reference classes is the ?ReferenceClasses 
documentation page at this stage.

Second point first:  The actual environment of a function is tightly 
bound to low-level implementation at the C level.  Only a _really_ 
strong practical argument would even tempt us to change that, such as by 
going away from the requirement that the type of the environment be 
ENVSXP.   (As mentioned in another thread, one point in favor of 
reference classes is that they have not messed with internals of R 
evaluation, just used existing techniques.)

The API  says nothing about what the environment of a reference method 
is, only that you aren't allowed to use any of the other R tricks that 
depend on the environment, such as generic functions.

Assigning attributes directly to an environment is a bad idea, as 
discussed in the past on this list.  That's why we went to the S4 
mechanism for subclasses of environments.

As for .self, the documentation says that the "entire object can be 
referred to in a method by the reserved name .self|"|.  That's a bit 
vague, and it's possible that one could update the slots of .self as 
part of slot assignment, but absent a serious example, it may be better 
to just clarify the documentation.


On 10/23/10 5:43 AM, Vitalie S. wrote:
> Hello Everyone!  Here are a couple of thought/questions on refClasses
> integration in R core functionality.
>
> First, coexistence with S4:
>
>> X<- setRefClass("classX", fields = c("a", "b"),
> +  representation = list(c = "character"))
>> x<- X$new()
>> x...@c<- "sss"
>> x
> An object of class "classX"
> 
> Slot "c":
> [1] "sss"
>
> The above is cool, S4 and refClasses apparently live happily together.
> But,
>
>> x$.self
> An object of class "classX"
> 
> Slot "c":
> character(0)
>
> This is not a surprise, taking into account the copping paradigm of R.
> Are there any plans to tighten S4<>refClasses integration? Or it's just not a
> good idea to mix them as in the above example?
>
>
> Second, R core integration (this bothers me much more):
>
>> X$methods(m = function(t) a*t)
>> environment(x$m)
> 
>
> environment(..) does not return the refObject but the basic type. I assume 
> that
> it is the same with other core functionality. Usage of refObjects as 
> parent.env
> is also probably precluded in the similar way (don't have a patched R, so can
> not test yet).
>
> Would it be possible, some day, to use refObjects as parent.env or function's
> environment  without "loosing the class"?
>
> Parenthetically, the attributes of an object (including S3 classes) are not 
> lost:
>
>> env<- structure(new.env(), a1 = "fdsf", class = "old_class")
>> tf<- function(x)x
>> environment(tf)<- env
>> environment(tf)
> 
> attr(,"a1")
> [1] "fdsf"
> attr(,"class")
> [1] "old_class"
>> class(environment(tf))
> [1] "old_class"
> Thanks,
> Vitalie.
>
> __
> 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] Plans for tighter integration of reference classes in R.

2010-10-24 Thread John Chambers

On 10/24/10 2:53 AM, Vitalie S. wrote:


Thank you for the answer, John.

John Chambers  writes:

Second point first:  The actual environment of a function is tightly
bound to low-level implementation at the C level.  Only a _really_
strong practical argument would even tempt us to change that, such as by
going away from the requirement that the type of the environment be
ENVSXP.


But, how about parent.env() functionality? The "S4" envelope is lost:


setClass("myenv", contains = "environment")

[1] "myenv"

env<- new("myenv")
envp<- new("myenv")
parent.env(env)<- envp
parent.env(env)




If you're talking about new R code, consider writing methods for 
parent.env() or for environment().


If you mean reprogramming the internals of the evaluator, not a chance 
in the foreseeable future.




Here I have in mind, as an application, the "prototype" programing paradigm
(akin to JavaScript, also implemented in R's proto package).

If environment manipulation functions would not strip the "S4" envelope from
environments, a considerably wider scope for implementation of "foreign"
programing paradigms would open up. All, by using the "existing techniques"
already available in S4 system.

Proto package makes it possible by using S3 classes, because they are not
striped away. Currently I am struggling to build a prototype based system, 
similar to
proto,  but in S4 framework. With all the advantages of S4, I am still doubting
that I made a right decision.

Thanks,
Vitalie.


... (As mentioned in another thread, one point in favor of
reference classes is that they have not messed with internals of R
evaluation, just used existing techniques.)

The API  says nothing about what the environment of a reference method
is, only that you aren't allowed to use any of the other R tricks that
depend on the environment, such as generic functions.

Assigning attributes directly to an environment is a bad idea, as
discussed in the past on this list.  That's why we went to the S4
mechanism for subclasses of environments.

As for .self, the documentation says that the "entire object can be
referred to in a method by the reserved name .self|"|.  That's a bit
vague, and it's possible that one could update the slots of .self as
part of slot assignment, but absent a serious example, it may be better
to just clarify the documentation.

On 10/23/10 5:43 AM, Vitalie S. wrote:

Hello Everyone!  Here are a couple of thought/questions on refClasses
integration in R core functionality.

First, coexistence with S4:


X<- setRefClass("classX", fields = c("a", "b"),

+  representation = list(c = "character"))

x<- X$new()
x...@c<- "sss"
x

An object of class "classX"

Slot "c":
[1] "sss"

The above is cool, S4 and refClasses apparently live happily together.
But,


x$.self

An object of class "classX"

Slot "c":
character(0)

This is not a surprise, taking into account the copping paradigm of R.
Are there any plans to tighten S4<>refClasses integration? Or it's just not a
good idea to mix them as in the above example?


Second, R core integration (this bothers me much more):


X$methods(m = function(t) a*t)
environment(x$m)



environment(..) does not return the refObject but the basic type. I assume that
it is the same with other core functionality. Usage of refObjects as parent.env
is also probably precluded in the similar way (don't have a patched R, so can
not test yet).

Would it be possible, some day, to use refObjects as parent.env or function's
environment  without "loosing the class"?

Parenthetically, the attributes of an object (including S3 classes) are not 
lost:


env<- structure(new.env(), a1 = "fdsf", class = "old_class")
tf<- function(x)x
environment(tf)<- env
environment(tf)


attr(,"a1")
[1] "fdsf"
attr(,"class")
[1] "old_class"

class(environment(tf))

[1] "old_class"
Thanks,
Vitalie.

__
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



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


Re: [Rd] Plans for tighter integration of reference classes in R.

2010-10-24 Thread John Chambers



On 10/24/10 1:43 PM, Vitalie S. wrote:

John Chambers  writes:


On 10/24/10 2:53 AM, Vitalie S. wrote:


Thank you for the answer, John.

John Chambers   writes:

Second point first:  The actual environment of a function is tightly
bound to low-level implementation at the C level.  Only a _really_
strong practical argument would even tempt us to change that, such as by
going away from the requirement that the type of the environment be
ENVSXP.


But, how about parent.env() functionality? The "S4" envelope is lost:


setClass("myenv", contains = "environment")

[1] "myenv"

env<- new("myenv")
envp<- new("myenv")
parent.env(env)<- envp
parent.env(env)




If you're talking about new R code, consider writing methods for parent.env() 
or for environment().

If you mean reprogramming the internals of the evaluator, not a chance in the
foreseeable future.


Not internals of the  evaluator, the .environment class.
Something like:
   - move the .self into a  super-class of envRefClass (in this case 
.environment),
   - make the method for `...@` for .environment, such that any update of the
   slots of the object will update the .self, making it virtually a mirror of 
the
   object.
   - make functions like parent.env and environment recognize the .self and
   return it instead of the internal environment object (writing methods would 
be probably
   quite an overhead).


I'm sorry, this is not likely to happen soon, if you expect the core 
developers to do it for you.  If you want to implement something like 
you suggest via methods for your classes and find it works well, we can 
consider implementing related code for the core .environment class.


Whether you think the overhead of _writing_ the methods is large or not, 
the way such development in R works best is that those interested in new 
features implement them; particularly useful or attractive features may 
be absorbed into the core later if that makes sense.


Meanwhile, the overhead of _using_ methods for these functions (i.e., 
the need to dispatch methods for the newly generic functions) will not 
be passed on to other applications that subclass environment.






This way, envRefClass is not affected, and people will have much nicer time in
programming with subclasses of .environment. Particularly I will be writing my
protoRefClasses happily, and not bother to overwrite core functions:)





Here I have in mind, as an application, the "prototype" programing paradigm
(akin to JavaScript, also implemented in R's proto package).

If environment manipulation functions would not strip the "S4" envelope from
environments, a considerably wider scope for implementation of "foreign"
programing paradigms would open up. All, by using the "existing techniques"
already available in S4 system.

Proto package makes it possible by using S3 classes, because they are not
striped away. Currently I am struggling to build a prototype based system, 
similar to
proto,  but in S4 framework. With all the advantages of S4, I am still doubting
that I made a right decision.

Thanks,
Vitalie.


... (As mentioned in another thread, one point in favor of
reference classes is that they have not messed with internals of R
evaluation, just used existing techniques.)

The API  says nothing about what the environment of a reference method
is, only that you aren't allowed to use any of the other R tricks that
depend on the environment, such as generic functions.

Assigning attributes directly to an environment is a bad idea, as
discussed in the past on this list.  That's why we went to the S4
mechanism for subclasses of environments.

As for .self, the documentation says that the "entire object can be
referred to in a method by the reserved name .self|"|.  That's a bit
vague, and it's possible that one could update the slots of .self as
part of slot assignment, but absent a serious example, it may be better
to just clarify the documentation.

On 10/23/10 5:43 AM, Vitalie S. wrote:

Hello Everyone!  Here are a couple of thought/questions on refClasses
integration in R core functionality.

First, coexistence with S4:


X<- setRefClass("classX", fields = c("a", "b"),

+  representation = list(c = "character"))

x<- X$new()
x...@c<- "sss"
x

An object of class "classX"

Slot "c":
[1] "sss"

The above is cool, S4 and refClasses apparently live happily together.
But,


x$.self

An object of class "classX"

Slot "c":
character(0)

This is not a surprise, taking into account the copping paradigm of R.
Are there any plans to tighten S4<>refClasses integration? Or it's just not a
good idea to mix them as in the above example?


Second, R core integration (this bothers me much more):


X$methods(m = func

Re: [Rd] Reference classes

2010-10-26 Thread John Chambers
What you've written will certainly generate an infinite recursion.  How 
could it not?


Specifying an accessor function says to the system "Any reference to 
this field should be evaluated by calling this function."  But then you 
refer to the field in the function itself, which will result in a call 
to the function, which 


Accessor functions are typically used when the field is a proxy for some 
data stored in a less convenient form (in a C++ object in the case of 
Rcpp).  As a self-contained example:


> ss <- setRefClass("silly", fields = list(now = function(value) {
+ if(missing(value)) Sys.time()
+ else stop("You can't change the time, dummy!")
+ }))
> s1 <- ss$new()
> s1$now
[1] "2010-10-26 08:50:36 PDT"
> s1$now <- "Never"
Error in function (value)  : You can't change the time, dummy!



On 10/26/10 4:57 AM, Jon Clayden wrote:

On 23 October 2010 00:52, Jon Clayden  wrote:

On 22 October 2010 18:55, John Chambers  wrote:


As a suggestion, it would be nice if the accessors() method could be
used to create just "getters" or just "setters" for particular fields,
although I realise this can be worked around by removing the unwanted
methods afterwards.


In other words, read-only fields.  There is a facility for that implemented
already, but it didn't yet make it into the documentation, and it could use
some more testing.  The generator object has a $lock() method that inserts a
write-once type of method for one or more fields.  Example:


fg<- setRefClass("foo", list(bar = "numeric", flag = "character"),

+ methods = list(
+ addToBar = function(incr) {
+ b = bar + incr
+ bar<<- b
+ b
+ }
+ ))

fg$lock("bar")
ff = new("foo", bar = 1.5)
ff$bar<- 2

Error in function (value)  : Field "bar" is read-only

A revision will document this soon.

(And no, the workaround is not to remove methods.  To customize access to a
field, the technique is to write an accessor function for the field that, in
this case, throws an error if it gets an argument.  See the documentation
for the fields argument.  The convention here and the underlying mechanism
are taken from active bindings for environments.)


OK, yes - I see. This is clearly much less superficial than removing
the setter method for a field which can be directly set anyway. I'll
have to try out field accessor functions and get a feel for the
semantics.


Unfortunately, I'm having difficulty working out the accessor function
approach. I've looked in the Rcpp package for examples, but it doesn't
seem to use this feature. If I define

Foo<- setRefClass("Foo", fields=list(bar=function (newBar) {
 if (missing(newBar)) bar
 else stop("bar is read-only") }),
   methods=list(barExists=function ()
print(exists("bar"

then I can't access the value of "bar" due to infinite recursion.
Using ".self$bar" in the accessor produces the same effect.


f<- Foo$new()
f$barExists()

[1] TRUE

f$bar

Error: evaluation nested too deeply: infinite recursion / options(expressions=)?

f$bar()

Error: evaluation nested too deeply: infinite recursion / options(expressions=)?

I can guess why this is happening (accessing "bar" within the accessor
calls itself), but how can I get at the value of "bar" within the
accessor without this occurring?

The other problem is that I can't even set a value at the time of
creation of the object, viz.


f<- Foo$new(bar=2)

Error in function (newBar)  : bar is read-only

Is there a way to test whether "bar" has already been set in the
accessor, so that I can allow it to be set once? (I know lock() allows
this, but it would be useful to be able to replicate the effect using
accessors, so that it can be generalised further where needed.)
Clearly, exists("bar") doesn't do this, as seen above -- presumably
because it sees the method rather than the field, or there is some
default value.

Thanks in advance,
Jon



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


Re: [Rd] Reference Classes: Generalizing Reference Class Generator objects?

2010-10-29 Thread John Chambers

Good diagnoses.

This thread brought up a point or two that needed some fixes to the 
documentation and code.  They should be in r-devel and 2.12 patched 
(from rev. 53471).


Briefly:

- Initialization methods should take account of future subclasses to 
your class by including and passing on the ... argument, so that 
additional fields can be specified.  Discussed briefly now in the 
$new(...) section of ?ReferenceClasses.


- The InitFields() method is fine but was an early kludge when 
callSuper() didn't work for initialize().  To allow for the case that 
your class has a superclass with an initialize() method, use the 
callSuper() approach.  There is an example now in the documentation.


John

On 10/28/10 10:55 AM, Jon Clayden wrote:

?ReferenceClasses says "Reference methods can not themselves be
generic functions; if you want additional function-based method
dispatch, write a separate generic function and call that from the
method". So I think you'd need to take that approach in your
"initialize" method.

Hope this helps,
Jon


On 28 October 2010 18:25, Daniel Lee  wrote:

Thank you. Your example really clarifies what the $initialize(...) function
is supposed to do.

Do you know if there is a straightforward way to dispatch the $new(...)
method based on the signature of the arguments? I am thinking along the
lines of S4 methods with valid signatures.

Thanks again for the example.


On 10/28/2010 12:12 PM, Jon Clayden wrote:


Sorry - you don't need to assign the value of initFields(). I was
going to do it in two lines but then realised one was enough... :)

TestClass<- setRefClass ("TestClass",
fields = list (text = "character"),
methods = list (
initialize = function (text) {
initFields(text=paste(text,"\n")) },
print = function ()  { cat(text) } )
)

All the best,
Jon


On 28 October 2010 15:13, Daniel Leewrote:


Is it possible to override the $new(...) in the reference class
generator? I
have tried adding a "new" method to the methods of the class, but that is
obviously not correct. I have also tried adding it to the class
generator,
but the class generator still uses the default constructor.

As a simple example, this is the current interface:
TestClass<- setRefClass ("TestClass",
fields = list (text = "character"),
methods = list (
print = function ()  {cat(text)})
)
test<- TestClass$new (text="Hello World")
test$print()

I would like to override $new(...) to be something like (add a "\n" to
the
end of the input, no need to specify input fields):
TestClass$methods (new = function (text) {
text<- paste (text, "\n")
methods:::new (def, text=text)
})

The constructor would then be:
test<- TestClass$new ("Hello World")

This is a subtle, but useful change. I have also tried adding to
TestClass a
method $newInstance(text), but that was not successful. If this is not
possible, could we consider augmenting the Reference Class interface to
include constructors?

__
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



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


Re: [Rd] "[[" strips the S4 class for classes extending environment

2010-11-10 Thread John Chambers
`[[<-`, that is.  Right, the primitive code is not retaining the 
subclass information.


Should be fixed in r-devel and 2.12 patched from revision 53547.

Thanks for the catch.

On 11/10/10 3:32 AM, Vitalie S. wrote:

Dear Developers,

A recently patched [[ for environment class returns a blank environment for a
children class:

setClass("myenv", contains = "environment")
#[1] "myenv"
env<- new("myenv")
class(env)
#[1] "myenv"
#attr(,"package")
#[1] ".GlobalEnv"
env[["a"]]<- 343
class(env)
[1] "environment"

It looks like not being an intended behavior.

Best,
Vitalie.

__
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] callNextMethod fails with "$" generic

2010-11-10 Thread John Chambers
The problem here is that the primitive for `$` does not use standard R 
evaluation on its second argument, so when it is selected as the next 
method the call is effectively x$name regardless of the original call.


If possible, I would avoid such cascaded calls of methods for `$`, 
precisely because of the nonstandard evaluation, which makes the 
interpretation of each level of the call ambiguous.


If this kind of code is needed, then the primitive method  should get a 
call in which the literal name is in place and the object has been 
coerced suitably.


In this example, something like

> setMethod("$", "mylist", function(x, name) {
+ theName <- substitute(name)
+ expr <- substitute(xx$NAME, list(NAME = theName))
+ xx <- unclass(x)
+ eval(expr)
+ })
[1] "$"
> tl <- new("mylist")
> tl[["z"]] <- 1
> tl$z
[1] 1

On 11/10/10 4:49 AM, Vitalie S. wrote:

Dear Developers,

callNextMethods does not work with "$"

setClass("mylist", contains = "list"):
setMethod("$",
   signature(x = "mylist"),
   function (x, name){
   cat("here:\n")
   callNextMethod()
   })

tl<- new("mylist")
tl[["x"]]<- 343

tl$x
#here:
#NULL


If I use callNextMethod(x=x, name=name)

this error is issued:

Error in function (classes, fdef, mtable)  :
   unable to find an inherited method for function "addNextMethod", for signature 
"function"

It must be something "$" specific. If the above is an expected behavior , how
should I call next method for "$" generic?

My info:
R version 2.12.0 Patched (2010-11-01 r53513)
Platform: i386-pc-mingw32/i386 (32-bit)

Same behavior for official R 2.12.0.

Thanks,
Vitalie.

__
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] R5 reference classes: how to initialize exactly?

2010-11-17 Thread John Chambers
On the subject of clarification, Reference Classes are not really an 
"addition" to S4.  They are a programming interface to allow OOP (i.e., 
C++ or Java-style) programming in R.


They do use some S4 tools but rely more on some valuable existing 
techniques for dealing with environments, such as active bindings.  They 
use a thin layer on top of existing R with the goal of simpler and 
clearer programming where object references and class-based methods are 
useful.


John

On 11/17/10 2:34 AM, Simon Urbanek wrote:

Just a clarification for posterity - R5 has nothing to do with the new 
reference classes. It's not even an official name, but informally it's a 
collection of ideas for an entirely new object system that can replace both S3 
and S4 (not that it will but it should be seen as having the capability to do 
so technically). Reference classes are just an addition to S4.




Cheers,
Simon


On Nov 16, 2010, at 12:30 AM, Janko Thyson wrote:


Sorry, I was stupid:



MyRefObj<- setRefClass("Blabla", .)



One can always get the generator object of an defined class with
'getRefClass()'. So:



g<- getRefClass("Blabla")

x<- g$new(.)



Regards,

Janko





Von: Janko Thyson [mailto:janko.thy...@ku-eichstaett.de]
Gesendet: Dienstag, 16. November 2010 00:27
An: 'r-de...@r-project. org'
Betreff: R5 reference classes: how to initialize exactly?



Dear List,



So far, I really like those new R5 classes. But what kind of puzzles me is
that it's not just enough to define the actual reference class, I also have
to assign it to an object (e.g. 'MyRefObj') in order to fire
'MyRefObj$new(.)'.



S4:

setClass("Blabla", .)

x<- new("Blabla")



R5:

MyRefObj<- setRefClass("Blabla", .)

x<- MyRefObj$new(.)



But then how do I define a reference class in a package that should be
available after the package is loaded via 'library(my_pkg)' as there is no
'MyRefObj' at startup yet? Do I have to call the script where the definition
lives?



Thanks for any comments,

Janko




[[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



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


Re: [Rd] R5 reference classes: how to initialize exactly?

2010-11-22 Thread John Chambers
As I posted previously in this same thread, reference classes are _not_ 
an addition to S4, but provide an interface to the "classical" OOP 
programming model in R, via environments and tools for those (and, also, 
via some S4 techniques).  The current version of the Rcpp package 
illustrates how they can be used in an interface, to C++.


There has been more than enough confusion already between the S and R 
version of OOP (which I'm calling "functional classes and methods" these 
days) and the C++/Java/... version.


Please just refer to "R reference classes" or words to that effect.

John

On 11/22/10 8:54 AM, Davor Cubranic wrote:

Just a clarification for posterity - R5 has nothing to do with the new
reference classes. It's not even an official name, but informally it's a
collection of ideas for an entirely new object system that can replace
both S3 and S4 (not that it will but it should be seen as having the
capability to do so technically). Reference classes are just an addition
to S4.

Cheers,
Simon


Thanks for that clarification. I picked that name up from the Google
TechTalks presentation of Dirk and Romain. So I refer to them as S4
reference classes in future posts?



Or just R15S for brevity. :-)

Davor

__
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] Ref classes: can I register fields as I register methods?

2010-11-22 Thread John Chambers
Well, it's an interesting idea, and the current implementation would fit 
with it.


One catch is that it goes against any obvious notion of checking for 
valid objects (admittedly, there are some difficulties in that already 
with active bindings being used).


Another issue is that in normal R programming practice, your "template" 
class would be in a package, in a namespace, and therefore locked. 
Conceptually at least, one would not be allowed to modify that definition.


Both these issues would be solved by using subclasses for the 
extensions, which seems more in the spirit of R.  Seems like you could 
hide the subclass details from your users if you wanted to.


So, something to think about, but the use case isn't convincing yet.

John

On 11/21/10 2:18 PM, Janko Thyson wrote:

Hi there,



is it possible to register fields as you can register methods with
getRefClass("Classname")$methods(.)?



I know that you should usually give some thought on which fields you need
and hardcode them in the class def. But I'm playing around with dynamically
creating/extending sort of a template class that already offers basic
functionality shared by all objects that "inherit" from that class. If I
follow the usual inheritance paradigm I would have to actually define those
new "subclasses" and let them inherit from the superclass (contains
argument(, right? But can I get around that by sort of registering new
fields? Maybe with 'initFields(.)'?



Thanks for any info on that,

Janko



# SYSTEM INFO #

Windows XP SP3

R 2.12.0

Eclipse 3.6.1 (Helios)

StatET 0.9.1

#






[[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


Re: [Rd] reference classes: question on inheritance

2010-11-22 Thread John Chambers

>>
>> What am I doing wrong here?

Not using a recent enough version of R probably (and not telling us what 
version you are using).


The warning (not an error) should not appear in current r-devel or 
2.12-patched. In other words, works fine for me.


John

On 11/21/10 3:40 PM, Janko Thyson wrote:

Hmm, interesting: it's the virtual class that causes the trouble. If a
virtual class is a ref class, everything works fine. If it's a standard S4
class, it results in the error below.

Regards,
Janko


-Ursprüngliche Nachricht-
Von: Janko Thyson [mailto:janko.thy...@ku-eichstaett.de]
Gesendet: Montag, 22. November 2010 00:31
An: 'r-de...@r-project. org'
Betreff: reference classes: question on inheritance

Dear list,

I have a reference class which should act as a “generic” superclass for
other classes. I’ve read the respective section at ?setRefClass and put
the name of the superclass to the ‘contains’ argument of an example
subclass (see class defs below). Classnames are set in a way that
shouldn’t result in collation issues (virtual def sourced before
superclass def sourced before subclass). Yet, this  results in the
following error:

Warnmeldung:
unable to find a consistent ordering of superclasses for class
"Shabubu": order chosen is inconsistent with the superclasses of
"JObject"

## CLASS DEFS #
setClass("JObjectVirtual")
setRefClass(
Class="JObject",
fields=list(
# GENERIC FIELDS (DON'T CHANGE !!!)
.BUFFER="environment",
.GENESIS="environment",
.HISTORY="environment",
.IMAGES="environment",
.LOGS="environment",
.OPTS="environment",
.PLUGINS="environment",
.TMP="environment",
.UID="character",
DATA="data.frame"
# /
),
contains=c("JObjectVirtual"),
methods=list(
...
)
)
setRefClass(
Class="Shabubu",
fields=list(
# CUSTOM FIELDS (ADAPT TO YOUR NEEDS)
a="numeric",
b="character",
c="logical",
d="data.frame",
e="matrix",
f="list",
derived.field="function"
# /
),
contains=c("JObject")
)

Thanks,
Janko


__
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] Reference Classes: how to clone/copy instances?

2010-11-25 Thread John Chambers
No reference class method explicitly does this, but it's a natural 
utility. Some form of $copy() will be added.  It needs a shallow/deep 
option; i.e., if a field is itself a reference class object, should that 
field be cloned as well.  The full reflectance available should make a 
single method (for the "envRefClass") work generally, although classes 
with non-standard accessor functions may need to have their own method.


Any contributions or suggestions are welcome, particularly with respect 
to features from other OOP languages that should be accommodated.  Lazy 
copy would be attractive, but harder to implement.



John

On 11/24/10 1:47 AM, Janko Thyson wrote:

Dear list,

I don't know what's the correct term for this in the OOP context, but is it
possible to "clone"/copy an instance of a reference class (say 'a') so that
I get an *autonomous* second instance 'b'? Autonomous in the sense that
changes to 'a' do not affect 'b'.

I know that this is somewhat against the pass-by-reference paradigm, but the
motive behind this is to generalize the 'undo()' functionality described in
the example of 'setRefClass()' to entire objects: I'd like to generate
"images" of my object via a '$imageAdd()" method in order to generate a
change history of the object (images are assigned to a field '.IMAGES' of
class 'environment') that I can "load()" on demand to undo changes to my
object.

Obviously, simply assigning 'b<- a' does not work with respect to autonomy.
Nor does exporting the object via 'b<- a$export(Class="A")'.
I thought about creating a new instance b and then defining a function that
maps the field values from a to b:

b<- getRefClass("A")$new()
fieldsMap(src=a, tgt=b)

Is there already some functionality I can use?

Thanks,
Janko

## SYSTEM INFO ##
Windows XP SP3
R 2.12.0 (patched as of 2010-11-22)
Eclipse 3.6.1 (Helios)
StatET 0.9.x
###

__
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] ReferenceClasses examples {method}

2011-01-28 Thread John Chambers

Hi Marc,

Sort of one out of two, but very helpful.

On 1/28/11 11:01 AM, Marc Carpentier wrote:

Dear r-devel-list, dear John Chambers,

I'm trying to learn OOP-possibilities in R and I was going through the
documentation 'ReferenceClasses {methods}' (great work, by the way...).
Reading associated Examples, something bothers me : it seems to me that there
are errors in 'edit' and 'undo' methods. I think that :
- 'undo' should update 'edits' field with :
length(edits)<<- length(edits) - 1 #(and not - 2)


Nope.  There are actually two logical choices here, but that is not 
either of them.


Notice that the line before that is:
  edit(prev[[1]], prev[[2]], prev[[3]])
which invokes the $edit() method to effect the undo, _and_ which adds 
that edit to the $edits list.


One could just leave things that way, but we decide to hide our undo 
from Wikileaks by removing both the edits.



- and for coherence, 'edit' should store modifications in an 'append'-style :
edits<<- c(edits,list(backup)) #as opposed to c(list(backup),edits)


Well, that's a bit debatable, but it does expose a bug, for sure.  The 
current order might be acceptable, but $undo() is then removing the 
wrong end of the $edits list, as would have been obvious if the example 
had done two edits and then removed one.  In the current version the 
first backup is the most recent edit (and indeed is used to reset the 
data), but then the wrong elements of $edits are removed.


Given that, I agree that the opposite order of keeping the backup list 
is better.  Less copying, for one thing.


Attached is a corrected and slightly expanded version of that part of 
the example.  Anyone is encouraged to try it out; if no further problems 
arise, I'll commit its essentials.




I hope I'm not wrong and this hasn't been previously reported (I didn't find
anything about it)
Best regards.

PS: I first posted this message on help-list. David Winsemius suggested  me
devel-list would probably be more appropriate and was right about that. Sorry if
you read it  again.


And indeed r-devel was the right place.  Thanks

John


PPS: please associate my address when responding because I didn't subscribe to
r-devel-list (I'm still far from being able to follow all its discussions...)







mEditor <- setRefClass("matrixEditor",
  fields = list( data = "matrix",
edits = "list"),
  methods = list(
 edit = function(i, j, value) {
   ## the following string documents the edit method
   'Replaces the range [i, j] of the
object by value.
'
 backup <-
 list(i, j, data[i,j])
 data[i,j] <<- value
 edits <<- c(edits, list(backup))
 invisible(value)
 },
 undo = function() {
   'Undoes the last edit() operation
and update the edits field accordingly.
'
 prev <- edits
 if(length(prev)) prev <- prev[[length(prev)]]
 else stop("No more edits to undo")
 edit(prev[[1]], prev[[2]], prev[[3]])
 ## trim the edits list
 length(edits) <<- length(edits) - 2
 invisible(prev)
 }
 ))

xMat <- matrix(1:12,4,3)
xx <- mEditor$new(data = xMat)
xx$edit(2, 2, 0)
xx$data
xx$edit(1,3, -1)
xx$data
xx$edits
xx$undo()
xx$edits
xx$data
xx$undo()
xx$data

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


Re: [Rd] Creating a reference class object from a class definition in a package fails

2011-02-03 Thread John Chambers

You don't say, but my guess is you created the package without a namespace.

For reasons that are not too clear at the moment, the namespace seems to 
be needed.  At any rate, replicating your experiment with the argument 
namespace=TRUE to package.skeleton() worked:


> require(TestClass2)
Loading required package: TestClass2
> TestClass$new()
An object of class "TestClass"


Without that I replicated your result.

Namespaces are a good idea anyway, though other things being equal it 
would be nice not to require them.  For the moment, though, we do.


John


On 2/2/11 7:25 PM, Jeffrey Horner wrote:

Hi,

I'm trying to create a package that contains reference class
definitions from which users can create reference objects, but there
seems to be something awry.

My toy example creates an empty package via
package.skeleton('TestClass') to which I add the following R code:

TestClass<- setRefClass('TestClass',fields=c('name'))

Unfortunately my R console output bears this:


library(TestClass)
TestClass$new(name='foo')

Error: attempt to apply non-function

getRefClass('TestClass')$new(name='foo')

Error: attempt to apply non-function

Creating the same reference class in the global environment works though:


x<- setRefClass('TestClass',fields='name')
x$new(name='foo')

An object of class "TestClass"


I'm new to S4 and reference classes, so maybe I'm missing something fundamental?

Jeff


sessionInfo()

R version 2.13.0 Under development (unstable) (2011-02-02 r54197)
Platform: i686-pc-linux-gnu (32-bit)

locale:
  [1] LC_CTYPE=en_US.UTF-8   LC_NUMERIC=C
  [3] LC_TIME=en_US.UTF-8LC_COLLATE=en_US.UTF-8
  [5] LC_MONETARY=C  LC_MESSAGES=en_US.UTF-8
  [7] LC_PAPER=en_US.UTF-8   LC_NAME=C
  [9] LC_ADDRESS=C   LC_TELEPHONE=C
[11] LC_MEASUREMENT=en_US.UTF-8 LC_IDENTIFICATION=C

attached base packages:
[1] stats graphics  grDevices datasets  utils methods   base

other attached packages:
[1] TestClass_1.0

loaded via a namespace (and not attached):
[1] tools_2.13.0

__
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] Creating a reference class object from a class definition in a package fails

2011-02-03 Thread John Chambers
Yes, as noted in my previous mail, which crossed yours.  If you included 
the TestClass  in a code_file= in the package skeleton, the default 
NAMESPACE file from package.skeleton() will do that for you:


exportPattern("^[[:alpha:]]+")
exportClasses(
"TestClass"

It's certainly true that _if_ you have a namespace file, reference 
classes (and all other classes) and generator objects have to be 
exported to be used outside the package.  Still not quite clear, though, 
why _any_ namespace file is needed.


Thanks for the catch.

John


On 2/3/11 1:46 PM, Jeffrey Horner wrote:

Apparently reference classes must be declared in the NAMESPACE file
via an S4 declaration. If I place the following in the NAMESPACE file
all is well:

exportClasses(TestClass)
export(TestClass)


Jeff

On Wed, Feb 2, 2011 at 9:25 PM, Jeffrey Horner  wrote:

Hi,

I'm trying to create a package that contains reference class
definitions from which users can create reference objects, but there
seems to be something awry.

My toy example creates an empty package via
package.skeleton('TestClass') to which I add the following R code:

TestClass<- setRefClass('TestClass',fields=c('name'))

Unfortunately my R console output bears this:


library(TestClass)
TestClass$new(name='foo')

Error: attempt to apply non-function

getRefClass('TestClass')$new(name='foo')

Error: attempt to apply non-function

Creating the same reference class in the global environment works though:


x<- setRefClass('TestClass',fields='name')
x$new(name='foo')

An object of class "TestClass"


I'm new to S4 and reference classes, so maybe I'm missing something fundamental?

Jeff


sessionInfo()

R version 2.13.0 Under development (unstable) (2011-02-02 r54197)
Platform: i686-pc-linux-gnu (32-bit)

locale:
  [1] LC_CTYPE=en_US.UTF-8   LC_NUMERIC=C
  [3] LC_TIME=en_US.UTF-8LC_COLLATE=en_US.UTF-8
  [5] LC_MONETARY=C  LC_MESSAGES=en_US.UTF-8
  [7] LC_PAPER=en_US.UTF-8   LC_NAME=C
  [9] LC_ADDRESS=C   LC_TELEPHONE=C
[11] LC_MEASUREMENT=en_US.UTF-8 LC_IDENTIFICATION=C

attached base packages:
[1] stats graphics  grDevices datasets  utils methods   base

other attached packages:
[1] TestClass_1.0

loaded via a namespace (and not attached):
[1] tools_2.13.0







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


Re: [Rd] Reference classes and ".requireCachedGenerics"

2011-02-15 Thread John Chambers

No worries, and we will get rid of the warning message.

Certain of the S4 classes require methods for particular primitive 
functions.  If a subclass of one of those classes is loaded from a 
package, then we need to turn on method dispatch for the corresponding 
primitive(s).  For efficiency, this information is precomputed and 
stored in the variable you mentioned.  It's quite reasonable for several 
instances to be encountered.  Nothing specific to reference classes 
except that they need, e.g., methods for `$`.


The variable name can be added to a "dont.mind" list to suppress the 
warning.


Thanks for the catch.

John


On 2/15/11 9:45 AM, Jon Clayden wrote:

Dear all,

If I load a package which creates reference classes whilst another
such package is also loaded, I get a warning about masking of the
".requireCachedGenerics" variable. (FWIW, both packages are
lazy-loaded.) Googling this variable name turned up only one previous
discussion, which didn't immediately help, except to suggest that it
may be related to my defining an S3 method for one or more of the
classes. It also pointed me at bits of the R source, but it wasn't
obvious to me from that, what this variable is for.

Aside from being a nuisance, I wonder if this is indicative of a
problem on R's side or on mine, so I'd be glad for any clarification.

This is R 2.12.1 on Mac OS X.6.6, though it still happens with the new
2.12.2 beta. Any feedback welcome.

Thanks,
Jon

__
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] Reference classes and ".requireCachedGenerics"

2011-02-15 Thread John Chambers
PS: this is another glitch that arises when you don't use NAMESPACE 
files.  If the .requireCachedGenerics is in a NAMESPACE and not 
exported, the conflict does not arise.


On 2/15/11 12:52 PM, John Chambers wrote:

No worries, and we will get rid of the warning message.

Certain of the S4 classes require methods for particular primitive
functions. If a subclass of one of those classes is loaded from a
package, then we need to turn on method dispatch for the corresponding
primitive(s). For efficiency, this information is precomputed and stored
in the variable you mentioned. It's quite reasonable for several
instances to be encountered. Nothing specific to reference classes
except that they need, e.g., methods for `$`.

The variable name can be added to a "dont.mind" list to suppress the
warning.

Thanks for the catch.

John


On 2/15/11 9:45 AM, Jon Clayden wrote:

Dear all,

If I load a package which creates reference classes whilst another
such package is also loaded, I get a warning about masking of the
".requireCachedGenerics" variable. (FWIW, both packages are
lazy-loaded.) Googling this variable name turned up only one previous
discussion, which didn't immediately help, except to suggest that it
may be related to my defining an S3 method for one or more of the
classes. It also pointed me at bits of the R source, but it wasn't
obvious to me from that, what this variable is for.

Aside from being a nuisance, I wonder if this is indicative of a
problem on R's side or on mine, so I'd be glad for any clarification.

This is R 2.12.1 on Mac OS X.6.6, though it still happens with the new
2.12.2 beta. Any feedback welcome.

Thanks,
Jon

__
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



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


Re: [Rd] Extending type list: names and inherited methods issue

2011-03-06 Thread John Chambers

The "names" slot is not part of the basic vector types/classes.

If you want to extend named lists, extend the class "namedList":

> getClass("namedList")
Class "namedList" [package "methods"]

Slots:

Name:  .Data names
Class:  list character

Extends:
Class "list", from data part
Class "vector", by class "list", distance 2

Known Subclasses: "listOfMethods"

> setClass("myNamedList", contains = "namedList")
[1] "myNamedList"
>
> mm <- new("myNamedList", list(a=1,b=2))
> mm
An object of class  "myNamedList"
$a
[1] 1

$b
[1] 2


On 3/4/11 3:30 AM, Renaud Gaujoux wrote:

Hi,

I want to extend the type list, but it looks like the names are not
handled properly (in the show method), not the [ method. See below for
code example.
I imagine this comes from the S3/S4 mixing, but I would like to
understand and the recommended work around (that avoid redefining all
the list methods [, $, etc...).
Thank you.

Bests,
Renaud

# define S4 class that inherits from list
setClass('A', contains='list')

# nothing to say when one creates an object with an unnamed list
x <- new('A', list(1,2,3))
x

# set the names: seems ok but they are not printed
names(x) <- letters[1:3]
names(x)
x
# same thing if one put the S3 .Data slot
names(x@.Data) <- letters[4:6]
names(x)
x

# the subsetting works but returns a list instead of the expected object
of class A
class(x[1])


 > sessionInfo()
R version 2.12.1 (2010-12-16)
Platform: x86_64-pc-linux-gnu (64-bit)

locale:
[1] LC_CTYPE=en_ZA.utf8 LC_NUMERIC=C LC_TIME=en_ZA.utf8
LC_COLLATE=en_ZA.utf8 LC_MONETARY=C LC_MESSAGES=en_ZA.utf8
LC_PAPER=en_ZA.utf8
[8] LC_NAME=C LC_ADDRESS=C LC_TELEPHONE=C LC_MEASUREMENT=en_ZA.utf8
LC_IDENTIFICATION=C

attached base packages:
[1] stats graphics grDevices utils datasets methods base



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


Re: [Rd] Testing for a reference class object

2011-03-10 Thread John Chambers
There is a virtual class "refClass" that all reference classes subclass, 
so is(x, "refClass") is the natural test, as in:


> foo <- setRefClass("foo", fields = "bar")
> x <- foo$new()
> is(x, "refClass")
[1] TRUE


On 3/10/11 7:40 AM, Jeffrey Horner wrote:

Hi all,

I've constructed the following function to test whether or not an
object was created from a reference class:

isRefClassObject<- function(x) isS4(x)&&
is.environment(attr(x,'.xData'))&&
exists('.refClassDef',attr(x,'.xData'))

but I'm unsure if it's a complete test or if there's a better way to
test. Regardless, It would be nice to have such a function in the
methods package.

I have a case where I'd like to ensure that an object is constructed
from a reference class AND that it implements a certain method:

if (isRefClassObject(x)&&  'run' %in% getRefClass(x)$methods())
 x$run()

Thanks,

Jeff


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


Re: [Rd] S4 generic functions/methods vs enclosures

2011-04-06 Thread John Chambers
Look at ?ReferenceClasses for this OOP paradigm in R, which is quite 
different from the functional paradigm of S4 methods.


On 4/6/11 7:54 AM, A Zege wrote:

Apologies for asking something that is probably very obvious, i just started
with S4 classes and i guess i am not finding documentation that lays out the
grammar rules and gives enough examples.

I understand that main method of writing a member function is to write a
generic function and setMethod for this particular class. This, however,
presumes that there is "virtuality" for this function, i.e. it could be used
with other inherited classes . Truth is, many, if not most of my functions
don't have virtuality in mind. I want to write them inside classes to
achieve incapsulaton only -- use class member data without passing it as
parameters or making global to a bunch of functions and have some specific
class member functions that don't pollute a global namespace and can be
called only for a particular class. This is what enclosured do in R. Is
there some obvious way of setting this environment local to a class and
without writing generic functions that i am missing?


Would appreciate any pointers


--
View this message in context: 
http://r.789695.n4.nabble.com/S4-generic-functions-methods-vs-enclosures-tp3430950p3430950.html
Sent from the R devel mailing list archive at Nabble.com.

__
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] How to debug reference classes?

2011-04-07 Thread John Chambers
This is a good wish-list item.  The natural mechanism would be a version 
of the standard trace() function as a reference method with the same 
arguments as the current trace(), minus those that make no sense.  So:

   xx$trace(edit, browser)
for example, to trace execution of the reference method "edit" defined 
in the class of xx.  The mechanism does not exist now, and will require 
some modifications or extensions to the existing trace() implementation.


Meanwhile, the following slightly ugly workaround seems to apply trace() 
to a reference method.  Here, xx is the object created in the example 
for ReferenceClasses, with method $edit().  [Actually running the 
example removes the class definition, so this was done from a copy of 
the source code for the example.]


The steps in the workaround:

- make a copy of the method,
  edit <- xx$edit

- arrange to trace it in xx:
  trace(edit, browser, where = xx)
(this produces a note and a warning, but they seem harmless)

- remove the copy (just to be safe)
  rm(edit)

- now run things with whatever trace action you speficied.

- if needed after debugging, untrace() the method.
  untrace("edit", where = xx)

An example is below.

Of course, one could also just define xx$edit to call a regular 
function, say myEdit() and trace that.  But the workaround doesn't 
require changing the existing definition.


Suggestions for a better or less ugly workaround are welcome.  I'll look 
at fixing up a trace() method for 2.13.1


John

==
> edit <- xx$edit
> trace(edit, browser, where = xx)
Constructing traceable class "refMethodDefWithTrace"
Environment of class "refMethodDef" is locked; using global environment 
for new class

Tracing function "edit" in package "2011-04-07 14:34:43"
[1] "edit"
Warning message:
In getPackageName(whereF) :
  Created a package name, "2011-04-07 14:34:43", when none found
> rm(edit)
> xx$edit(1,2,3)
Tracing xx$edit(1, 2, 3) on entry
Called from: eval(expr, envir, enclos)
Browse[1]> objects()
[1] "i" "j" "value"
Browse[1]> j
[1] 2
Browse[1]> j <- 3
Browse[1]>
> xx$data
 [,1] [,2] [,3]
[1,]153
[2,]26   10
[3,]37   11
[4,]48   12
> untrace("edit", where = xx)
Untracing function "edit" in package "2011-04-07 14:34:43"
> xx$edit(1,2,-1)
> xx$data
 [,1] [,2] [,3]
[1,]1   -13
[2,]26   10
[3,]37   11
[4,]48   12



On 4/7/11 12:00 PM, A Zege wrote:

How do you debug methods of a reference class? I've been using mtrace, which
is excellent, but i cannot figure out how to mtrace a reference class
method. Maybe there is some other way to debug these, for example with
ordinary trace? for now i am only able to use options(error=recover), which
is not giving me idea where exactly in the code i am once i am stopped on an
error.

--
View this message in context: 
http://r.789695.n4.nabble.com/How-to-debug-reference-classes-tp3434269p3434269.html
Sent from the R devel mailing list archive at Nabble.com.

__
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] How to debug reference classes?

2011-04-07 Thread John Chambers
Good to know.  However, _please_ don't use the horrible kludge in the 
attr(..) expression.  From my experimenting, it worked fine just to say:


mtrace(edit, from = xx)

and even if that did not work, from = as.environment(xx) is identical in 
effect to the attr() expression and means something.  (Usually the 
coercion to "environment" happens automatically.)


The attr() expression is strongly deprecated and very much not 
guaranteed to work.  First, it's discouraged to use the .xData slot, 
which is part of the implementation and not part of the API.  And ditto 
to access _any_ slot by attr(), for the same reason.


However, in my experimenting the technique required xx$edit to have been 
evaluated at some point before the call to mtrace(). Reference methods 
are copied to the object when first required (for efficiency).  Because 
my workaround explicitly used xx$edit, the problem didn't arise.  Just 
evaluating xx$edit should be enough.


On the "before instantiated" point.  I assume you mean in order to trace 
the method in all objects generated from the reference class.  I had 
thought about that too.  The same mechanism I described in my previous 
mail works for this as well, but requires a kludge to get the 
environment containing the methods.  The steps I outlined are as before 
but modified (in the example) as follows:


> mm =  mEditor$def@refMethods
> edit = mm$edit
> trace(edit, browser, where = mm)

(mm is the environment with the methods).  Then the objects generated by 
mEditor$new() will have the traced version.


The same technique didn't seem to work for mtrace(), but a modification 
might.


John


On 4/7/11 4:56 PM, mark.braving...@csiro.au wrote:

'mtrace' will work with reference classes, at least after an object is 
instantiated. I'm not familiar with the guts of reference classes, but the 
following quick experiment was successful.. If you run the example in 
'?ReferenceClasses' up to&  including this line :

xx<- mEditor$new(data = xMat)

and then do this:

mtrace( edit, from=attr( xx, '.xData'))

and then run the next line of the example, which is

xx$edit(2, 2, 0)

then the debug window will come up as normal.

Now, what about if you want to mtrace 'edit' before objects are instantiated? 
Here the S4 structure defeated me temporarily, but I probably would have been 
able to beat it if I'd had more time... There are some notes on debugging S4 
methods in 'package?debug' (note that '?mtrace' itself is out-of-date on S4-- I 
have gotten S4 debugging to work, but it's only described in 'package?debug') 
and that might be enough to get you going.

HTH

Mark ('debug' package author)

Mark Bravington
CSIRO CMIS
Marine Lab
Hobart
Australia

From: r-devel-boun...@r-project.org [r-devel-boun...@r-project.org] On Behalf 
Of A Zege [andre.z...@gmail.com]
Sent: 08 April 2011 05:00
To: r-devel@r-project.org
Subject: [Rd] How to debug reference classes?

How do you debug methods of a reference class? I've been using mtrace, which
is excellent, but i cannot figure out how to mtrace a reference class
method. Maybe there is some other way to debug these, for example with
ordinary trace? for now i am only able to use options(error=recover), which
is not giving me idea where exactly in the code i am once i am stopped on an
error.

--
View this message in context: 
http://r.789695.n4.nabble.com/How-to-debug-reference-classes-tp3434269p3434269.html
Sent from the R devel mailing list archive at Nabble.com.

__
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



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


Re: [Rd] self-referential representations in S4

2011-04-20 Thread John Chambers
The warning is there because all is not "just fine", in general and in 
particular not in your example.


If a superclass is not virtual, the prototype object for the new class 
must have a member of that class in the appropriate slot.  How could it 
do so in this case?  As a result, your class will return an invalid 
object from a call to new().


So one might argue that the current rules are too lax, and this should 
be an error.


The fundamental point is that S4 classes, as opposed to the new 
reference classes, don't deal in "references", self- or other.


Ways to deal with such recursive structures are discussed in section 9.7 
of Software for Data Analysis.


One version of what you were perhaps trying to do might, for a binary 
tree, be:


> setClassUnion("MyNode", c("NULL", "vector"))
[1] "MyNode"
>
> setClass("FullNode", representation(left = "MyNode", right ="MyNode",
+   parent = "MyNode"))
[1] "FullNode"
> setIs("FullNode", "MyNode")

Nodes can be full, a vector as a leaf, or empty.

John

On 4/19/11 3:10 PM, James Bullard wrote:


I'm trying to do the following:


setClass("MyNode", representation(parent = "MyNode"))

[1] "MyNode"
Warning message:
undefined slot classes in definition of "MyNode": parent(class "MyNode")

I scanned the docs, but found nothing. The representation function has no
problem, it's the setClass function which gives the warning.

What I'm trying to understand is why have the warning - it seems to work
just fine when I instantiate the class. Can we add an argument to the
setClass to suppress the warning?

This question was asked previously, but not answered in any satisfactory way:

http://r.789695.n4.nabble.com/Linked-List-in-R-td3303021.html

thanks, jim




R version 2.12.2 Patched (2011-03-09 r54717)
Platform: x86_64-unknown-linux-gnu (64-bit)

locale:
  [1] LC_CTYPE=en_US.UTF-8   LC_NUMERIC=C
  [3] LC_TIME=en_US.UTF-8LC_COLLATE=en_US.UTF-8
  [5] LC_MONETARY=C  LC_MESSAGES=en_US.UTF-8
  [7] LC_PAPER=en_US.UTF-8   LC_NAME=C
  [9] LC_ADDRESS=C   LC_TELEPHONE=C
[11] LC_MEASUREMENT=en_US.UTF-8 LC_IDENTIFICATION=C

attached base packages:
[1] stats graphics  grDevices utils datasets  methods   base

other attached packages:
[1] h5r_1.1

loaded via a namespace (and not attached):
[1] tools_2.12.2

__
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] problem subsetting of a reference class

2011-04-21 Thread John Chambers

You're confusing functional and OOP-style methods.

Since you define an OOP-style method, you need to invoke it in OOP style.

With your example:


> tmp$`[`("random")
 [1] -1.439131143 -0.630354726  0.822006263 -0.651707539  0.475332681
 [6]  0.002680224  1.539035675 -0.117609566  2.066227300  1.111270997
>


You could if you wanted define a functional method via setMethod() to 
allow functional access, by invoking the $`[`() method--preferably after 
changing its name.  It's probably a matter of opinion whether that's a 
good use of OOP-style methods.



On 4/21/11 12:24 PM, A Zege wrote:

I am trying to define subset operator for a reference class and hitting some
problem i am unable to diagnose.To give an example, here is a toy class
generator that is a wrapper around a list




tmpGEN<-setRefClass("TMP", fields=list(
namelist="list"
))
tmpGEN$methods('add'=function(obj, name){
namelist[[name]]<<-obj
})

tmpGEN$methods('['=function(name){
if(class(name)!="character")
stop('to return cache element need to pass its 
name')
ind<-match(name, names(namelist))
if(is.na(ind))
stop('data to remove is not in namelist')
namelist[[name]]
})


==

when i try to use it, the following happens
v<-rnorm(10)
tmp<-tmpGEN$new()
tmp$add(v, 'random')

. up until here everything is ok, class is generated and vector is
added. Now when i do
tmp['random']

i get error message

Error in tmp["random"] : object of type 'S4' is not subsettable

Not sure if it means that i cannot define "[" operator for a class or if i
am doing it syntactically wrong


--
View this message in context: 
http://r.789695.n4.nabble.com/problem-subsetting-of-a-reference-class-tp3466690p3466690.html
Sent from the R devel mailing list archive at Nabble.com.

__
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] Reference Classes: Accessing methods via [[...]], bug?

2011-05-01 Thread John Chambers

Yes, as presented on that site it makes a little more sense:

"While experimenting with the new reference classes in R I noticed some 
odd behaviour if you use the "[[ ]]" notation for methods 
(X[["doSomething"]] instead of X$doSomething). This notation works for 
fields, but I initially thought it wouldn't work for methods until I 
found that if you execute "class(X$doSomething)" you can then use "[[ 
]]" afterwards. The simple example below illustrates the point."


For reference classes, "[[" is not meant to be used either for fields or 
methods.  That it "works" at all is an artifact of the implementation 
using environments.  And arguably the failure to throw an error in that 
circumstance is a bug.


Please use the API as described in the ?ReferenceClasses documentation. 
 These are encapsulated methods, in the usual terminology, with the 
operator "$" playing the role normally assigned to "." in other languages.


A separate  but related issue:  It is possible to define S4 methods for 
reference classes, as discussed in a previous thread, arguably also an 
artifact in that a reference class is implemented as an S4 class of the 
same name.  These are functional methods, associated with a generic 
function, and so outside the encapsulation paradigm.


It would be interesting to get some experience and opinions on whether 
this is a good idea or not.  It breaks encapsulation, in that the 
behavior of the class can no longer be inferred from the class 
definition alone.  On the other hand, it is convenient and relates to 
"operator overloading" in some other languages.


John

On 4/30/11 7:54 PM, Hadley Wickham wrote:

If this message is garbled for anyone else, the original question on
stackoverflow is here:
http://stackoverflow.com/questions/5841339/using-notation-for-reference-class-methods

Hadley

On Sat, Apr 30, 2011 at 11:35 AM, Chad Goymer  wrote:


I've been trying to use methods for reference classes via the notation "[[...]]" 
(X[["doSomething"]] rather than X$doSomething), but it failed to work. However, I did find that if you use 
the usual "$" notation first, "[[...]]" can be used afterwards. The following simple example 
illustrates the point:

setRefClass("Number", +   fields = list(+ value = "numeric"+   ),+   methods = list(+ addOne = function() 
{+   value<<- value + 1+ }+   )+ )>  X<- new("Number", value = 1)>  X[["value"]][1] 1
X[["addOne"]]()Error: attempt to apply non-function>  class(X[["addOne"]]) # NULL[1] 
"NULL"
class(X$addOne)[1] "refMethodDef"attr(,"package")[1] "methods"
X[["addOne"]]()>  X[["value"]][1] 2>  class(X[["addOne"]])[1] 
"refMethodDef"attr(,"package")[1] "methods"

Is this a bug?
Chad Goymer

[[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


Re: [Rd] Reference Classes: Accessing methods via [[...]], bug?

2011-05-01 Thread John Chambers

On 5/1/11 3:37 PM, Martin Morgan wrote:

On 05/01/2011 03:09 PM, John Chambers wrote:

Yes, as presented on that site it makes a little more sense:

"While experimenting with the new reference classes in R I noticed some
odd behaviour if you use the "[[ ]]" notation for methods
(X[["doSomething"]] instead of X$doSomething). This notation works for
fields, but I initially thought it wouldn't work for methods until I
found that if you execute "class(X$doSomething)" you can then use "[[
]]" afterwards. The simple example below illustrates the point."

For reference classes, "[[" is not meant to be used either for fields or
methods. That it "works" at all is an artifact of the implementation
using environments. And arguably the failure to throw an error in that
circumstance is a bug.

Please use the API as described in the ?ReferenceClasses documentation.
These are encapsulated methods, in the usual terminology, with the
operator "$" playing the role normally assigned to "." in other
languages.

A separate but related issue: It is possible to define S4 methods for
reference classes, as discussed in a previous thread, arguably also an
artifact in that a reference class is implemented as an S4 class of the
same name. These are functional methods, associated with a generic
function, and so outside the encapsulation paradigm.

It would be interesting to get some experience and opinions on whether
this is a good idea or not. It breaks encapsulation, in that the
behavior of the class can no longer be inferred from the class
definition alone. On the other hand, it is convenient and relates to
"operator overloading" in some other languages.


I have written 'show' methods for reference classes (is there another
way to pretty-print them?) and S4 methods that dispatch to reference
methods (in particular, yield(x) on connection-like classes dispatching
to x$yield()). The latter partly to provide end-user familiarity
(limiting need for the beleaguered user to have to learn yet another
syntax for invoking methods, though maybe hiding hints about important
differences in object behavior --


Just a comment on this point:


I am dreading the introductory class
where one tries to explain S3, S4, and reference classes)


Well, your "introductory" class sounds a bit advanced.  :-)

My feeling is actually anticipation more than dread.  The confusion over 
what "OOP" means in S and R has been a major hassle since S3 methods 
were introduced.  I think we have an opportunity now to clarify the 
discussion as well as introduce some useful new software and better 
inter-system interfaces.


Part of the motivation for the reference classes was to bring a general 
OOP view to R.  One can start from some essential concepts of objects 
and their properties, inheritance and class definition, as have evolved 
over a very long time.


Next, there is a fundamental choice of paradigm between "encapsulated" 
OOP as the rest of the world knows it, and "functional" OOP as practiced 
by S and R, and a few other languages.  While the two paradigms are 
quite different, there is no need to view them as opposed.  They provide 
different advantages and tend to suit different goals--very roughly, 
functional object creation and reproducible results versus persistent 
objects whose properties one would like to have evolve over time using 
their encapsulated methods.


As these remarks may suggest, I'm trying to write up this perspective in 
some detail.  To be continued 


John

> and partly to
> provide a distinction between a 'developer' API and a user API (again
> with questionable merits).


Martin



John

On 4/30/11 7:54 PM, Hadley Wickham wrote:

If this message is garbled for anyone else, the original question on
stackoverflow is here:
http://stackoverflow.com/questions/5841339/using-notation-for-reference-class-methods



Hadley

On Sat, Apr 30, 2011 at 11:35 AM, Chad
Goymer wrote:


I've been trying to use methods for reference classes via the
notation "[[...]]" (X[["doSomething"]] rather than X$doSomething),
but it failed to work. However, I did find that if you use the usual
"$" notation first, "[[...]]" can be used afterwards. The following
simple example illustrates the point:

setRefClass("Number", + fields = list(+ value = "numeric"+ ),+
methods = list(+ addOne = function() {+ value<<- value + 1+ }+ )+ )>
X<- new("Number", value = 1)> X[["value"]][1] 1
X[["addOne"]]()Error: attempt to apply non-function>
class(X[["addOne"]]) # NULL[1] "NULL"
class(X$addOne)[1] "refMethodDef"attr(,"package")[1] "methods"
X[["addOne"]]()> X[["value"]][1] 2> class(X[["addOne"]]

Re: [Rd] Reference Classes: Accessing methods via [[...]], bug?

2011-05-04 Thread John Chambers

On 5/3/11 2:39 PM, Hadley Wickham wrote:

Part of the motivation for the reference classes was to bring a general OOP
view to R.  One can start from some essential concepts of objects and their
properties, inheritance and class definition, as have evolved over a very
long time.

Next, there is a fundamental choice of paradigm between "encapsulated" OOP
as the rest of the world knows it, and "functional" OOP as practiced by S
and R, and a few other languages.  While the two paradigms are quite
different, there is no need to view them as opposed.  They provide different
advantages and tend to suit different goals--very roughly, functional object
creation and reproducible results versus persistent objects whose properties
one would like to have evolve over time using their encapsulated methods.


My biggest worry with the introduction of reference classes is that
many people will just stick to the style of OOP that they're familiar
with, and not bother to learn the strengths of the generic function
approach.


Well, that says that presenting the choices well is important.  Agreed.

But the alternative is (and has been) for people from the "other" OOP 
background to hack something using the functional S4/S3 paradigm and 
then complain when it doesn't behave as expected. Not really preferable.





As these remarks may suggest, I'm trying to write up this perspective in
some detail.  To be continued 


Are you familiar with "Concepts, Techniques, and Models of Computer
Programming" by van Roy and Haridi?  That's what really helped me to
understand the strengths and weaknesses of the various styles of
programming.


Thanks, I wasn't.  Yes, interesting similar distinction between 
functional and "type" decomposition.  An important associated aspect for 
us is the distinction between reference objects and "ordinary" R 
objects, not AFAICS conveyed by their more abstract treatment.


John


Hadley



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


Re: [Rd] General "nil" reference class object

2011-05-04 Thread John Chambers

Interesting idea.

One approach would be to test against the _environment_ of the prototype 
object in the class definition.  Since the initialize method for a 
reference class must call new.env(), one knows that a real object from 
the class has a different environment.  Using that fact one could have 
functions

  nullObject(Class)
to get the null, and
  isNullObject(x)
to test.

My feeling is that this approach is better for R than having one single 
nil object, because nullObject(Class) would still be a valid object from 
the class.


Something to mull over.
  John


On 5/4/11 6:09 AM, Jon Clayden wrote:

Dear John and others,

I've been wondering about whether there's any way to indicate a "nil"
reference class object, which will represent "no value", and be tested
for, but not fail the internal type checking. NULL is the obvious
choice (or seems so to me), but can only be used if an explicit class
union is created:


Foo<- setRefClass("Foo")
Bar<- setRefClass("Bar", fields=list(foo="Foo"))
Bar$new(foo=NULL)

Error in as(value, "Foo") :
   no method or default for coercing "NULL" to "Foo"

setClassUnion("FooOrNull", c("Foo","NULL"))

[1] "FooOrNull"

Bar<- setRefClass("Bar", fields=list(foo="FooOrNull"))
Bar$new(foo=NULL)

An object of class "Bar"


is.null(Bar$new(foo=NULL)$foo)

[1] TRUE

Other languages allow things like "MyClass object = null", and it
seems to me that it would be helpful to have a value which will always
give TRUE for "is(object,)", but will
specifically indicate a nil reference. One possible ad-hoc solution is
to define the "empty" object of a base class to be "nil" (see below),
but it seems like it would be better to have a value specifically
designed for this purpose.


nilObject<- Foo$new()
is.nilObject<- function (x) identical(x,nilObject)
Bar<- setRefClass("Bar", fields=list(foo="Foo"), methods=list(

+ initialize=function (foo=nilObject) { initFields(foo=foo) }))

is.nilObject(Bar$new()$foo)

[1] TRUE

Is there already something like this that I'm not aware of? If not,
would it be possible and generally desirable to create it?

All the best,
Jon


--
Jonathan D Clayden, PhD
Lecturer in Neuroimaging and Biophysics
Imaging and Biophysics Unit
UCL Institute of Child Health
30 Guilford Street
LONDON  WC1N 1EH
United Kingdom

__
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] Reference Classes: (Was: Accessing methods via [[...]], bug?)

2011-05-04 Thread John Chambers

On 5/4/11 9:24 AM, Hadley Wickham wrote:

Are you familiar with "Concepts, Techniques, and Models of Computer
Programming" by van Roy and Haridi?  That's what really helped me to
understand the strengths and weaknesses of the various styles of
programming.


Thanks, I wasn't.  Yes, interesting similar distinction between functional
and "type" decomposition.  An important associated aspect for us is the
distinction between reference objects and "ordinary" R objects, not AFAICS
conveyed by their more abstract treatment.


Another discussion I found useful was in SICP:
http://mitpress.mit.edu/sicp/full-text/book/book-Z-H-17.html#%_sec_2.4.3

I really like the metaphor of method dispatch as a table with types in
the columns and operations in the rows - then you can think of generic
functions oo as being row-based, and class based oo as column-based.


Except that functional method dispatch with multiple dispatch is 
dispatched on a K-tple of classes if the generic function has K 
arguments in its signature.


This is not a trivial distinction because it means that a method can 
depend on more than one class definition, so it's not just a matter of 
distributing the same information in different ways, but a fundamentally 
more complicated structure for functional OOP (for better and/or for worse).


John



Hadley



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


Re: [Rd] Reference Classes: replacing '.self' with an .Rda image of '.self' from within a method? (was replacing '.self' with an .Rda image of '.self' from within a method?)

2011-05-04 Thread John Chambers
It makes no sense to replace the .self field:  that field is initialized 
to be a reference to the object.  If you change it, it's no longer that 
reference.


There are many things wrong with your example, so it's better to take a 
very simple version:


> mkTest <- setRefClass("test",fields = list(a = "numeric"))
> x <- mkTest$new(a=1:10)

Now suppose we replace the .self field with another one:
> y <- mkTest$new(a = 11:20)
> x$.self <- y$.self

At this point x is messed up and does not correspond to the .self field:

> x$a
 [1]  1  2  3  4  5  6  7  8  9 10
> x$.self$a
 [1] 11 12 13 14 15 16 17 18 19 20

The same problem results no matter how you change the field.  The only 
difference with a method is that you do get a warning message.


> pseudoSelf <- as.environment(list(a = 5))
> x$.self <- pseudoSelf
> x$a
 [1]  1  2  3  4  5  6  7  8  9 10
> x$.self$a
[1] 5
> mkTest$methods(screwup = function(newSelf) .self <<- newSelf)
Warning message:
In .checkFieldsInMethod(def, fieldNames, allMethods) :
  Non-local assignment to non-field names (possibly misspelled?)
.self <<- newSelf
( in method "screwup" for class "test")
> x <- mkTest$new(a=1:10)
> x$screwup(pseudoSelf)
> x$a
 [1]  1  2  3  4  5  6  7  8  9 10
> x$.self$a
[1] 5

We need to make the .self field read-only.


On 5/4/11 12:39 PM, Janko Thyson wrote:

Sorry guys,

but I chose a really stupid name before (no "reference classes").

Hope it's okay to re-post.

Cheers,
Janko

 >>> ORIGINAL MESSAGE <<<

Dear list,

Is it possible to update or reassign '.self' with an image of '.self'
(e.g. a locally stored .Rda file) from within a method?

I know that this might sound akward, but here's the use case:
1) Ref Class Definition
setRefClass(Class="Test",
fields=list(A="character", B="character"),
methods=list(importImage=function(path){
variable <- load(path)
expr <- paste("assign('", variable, "',", variable, ", envir=.self)",
sep="")
eval(parse(text=expr))
}
)
2) Initialize Method Definition
setMethod(
f="initialize",
signature=signature(.Object="Test"),
definition=function(
.Object,
path=NULL
){
obj <- callNextMethod(.Object)
if(!is.null(path){
obj$importImage(path=path)
}
return(obj)
}
3) Intended and "Extended" Use
Method 'importImage' was originally intended to read either an object of
name 'A' or 'B' from a respective path and overwrite the respective
fields in an obj of class 'Test'.
Now I wondered how I could "reassign"/update the object of class 'Test'
itself by reading a respective .Rda image of an object of class 'Test'
from within 'obj$importImage()'.
The way I've written 'importImage()', it did not work. Yet I wonder if
it's possible.
4) My Workaround (but I'm looking for something more elegantly)
In the class definition:
[...]
methods=list(importImage=function(path){
variable <- load(path)
if(variable != ".self"){
expr <- paste("assign('", variable, "',", variable, ", envir=.self)",
sep="")
eval(parse(text=expr))
return(TRUE)
} else {
return(.self)
}
})
[...]

In the initialize method:
setMethod(
f="initialize",
signature=signature(.Object="Test"),
definition=function(
.Object,
path=NULL
){
obj <- callNextMethod(.Object)
if(!is.null(path){
rslt <- obj$importImage(path=path)
if(!is.logical(rslt)){
obj <- rslt
}
}
return(obj)
}

Thanks for any comments,
Janko

__
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


[Rd] Examples for performance studies

2011-05-09 Thread John Chambers
A number of activities are underway related to understanding R 
performance in practice and to exploring techniques for improving 
performance generally or in important special cases.  I'm writing 
directly on behalf of an informal group centered in the Computer Science 
department here at Stanford, but also on behalf of similar activities 
elsewhere.


We would all be helped by realistic examples of serious computations 
with R, where substantial computing is required and the results are 
important to users.  The more and the more representative the data 
available, the more likely that useful performance tools can be designed.


If you can provide us with examples that we can use and share, please 
send a description to:

  Justin Talbot 

As examples accumulate, the plan is to make them available to the 
community---details to be worked out.


Thanks in advance,
  John Chambers

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


Re: [Rd] Reference Classes copy(shallow=FALSE) unexpected behavior.

2011-05-11 Thread John Chambers

Good suggestion for this case.

But the general problem is tricky.  What about reference objects 
contained in attributes or slots of other objects, etc?  What is  needed 
for total copying is a switch in the low-level duplication code that 
says to copy reference objects.  It's also possible that one does NOT 
want all such objects copied.


For now, it may be that specialized copy() methods are needed for 
classes that have subsidiary reference objects inside non-reference objects.


John

On 5/11/11 6:37 AM, Hadley Wickham wrote:

Hi Manuel,

The source code for copy is short and pretty readable, so I'd
encourage you to look at it:


setRefClass("XXX")$copy

Class method definition for method copy()
function (shallow = FALSE)
{
 def<- .refClassDef
 value<- new(def)
 vEnv<- as.environment(value)
 selfEnv<- as.environment(.self)
 for (field in names(def@fieldClasses)) {
 if (shallow)
 assign(field, get(field, envir = selfEnv), envir = vEnv)
 else {
 current<- get(field, envir = selfEnv)
 if (is(current, "envRefClass"))
 current<- current$copy(FALSE)
 assign(field, current, envir = vEnv)
 }
 }
 value
}

The basic problem is that you have a list of reference class objects,
and currently copy does not recurse into lists.  I think this could be
fixed with

deep_copy<- function(x) {
   if (is(current, "envRefClass")) {
 x$copy()
   } else if (is.list(x))
 lapply(x, deep_copy)
   } else {
 x
   }
}

function (shallow = FALSE){
 def<- .refClassDef
 value<- new(def)
 vEnv<- as.environment(value)
 selfEnv<- as.environment(.self)
 for (field in names(def@fieldClasses)) {
 if (shallow)
 assign(field, get(field, envir = selfEnv), envir = vEnv)
 else {
 current<- get(field, envir = selfEnv)
 assign(field, deep_copy(current), envir = vEnv)
 }
 }
 value
}

Hadley

2011/5/11 Manuel Castejón Limas:

Dear Hadley,

Thank you very much for your interest in the question proposed.
The Con class is a Reference Class. P and k are from class listCon.

I provide in the following lines a little more detail in order to be able
to reproduce the case.

#Class declaration
gCon<- setRefClass("Con", fields=list(from="ANY",weight="numeric"))
gListAMORE<- setRefClass("listAMORE", fields=list(.Data="list"))
gListCon<- setRefClass("listCon", contains="listAMORE")

# Let's create a few connections
con1<- gCon$new(from=1, weight=1.1)
con2<- gCon$new(from=2, weight=2.2)
con3<- gCon$new(from=3, weight=3.3)

# And a list of connections
lcon<-gListCon$new()
lcon$.Data<- list(con1, con2, con3)

# At this point, lcon contains:
lcon$.Data
[[1]]
An object of class "Con"


[[2]]
An object of class "Con"


[[3]]
An object of class "Con"


# Let's copy lcon to k
k<- lcon$copy(shallow=FALSE)

# Now k is a new object but the cons are shared with lcon!
k$.Data
[[1]]
An object of class "Con"


[[2]]
An object of class "Con"


[[3]]
An object of class "Con"



Best regards

Manuel



El 11/05/11 14:00, "Hadley Wickham"  escribió:


2011/5/10 Manuel Castejón Limas:

Dear all,

I've just discovered the 'Reference Classes'.
In a previous attempt ---a year ago--- to re-implement in a Object
Oriented
fashion the AMORE package using S4 classes I strongly felt the need of
such
capability. It's great to have the Reference Classes now available.
Along
with the discovery of the Rcpp package, this new programming paradigm
has
boosted my interest in rewriting that package.

Nevertheless, I have found a surprising behavior in the
$copy(shallow=FALSE)
method. Let's have a look at the results which I believe are
self-explanatories. The ".Data" field is a list which contains objects
from
the "Con" class  ---connections for what is worth---.


What sort of class is the Con class? S4 or reference?

Hadley


--
Assistant Professor / Dobelman Family Junior Chair
Department of Statistics / Rice University
http://had.co.nz/












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


Re: [Rd] By default, `names<-` alters S4 objects

2011-05-15 Thread John Chambers

This is basically a case of a user error that is not being caught:

On 5/14/11 3:47 PM, Hervé Pagès wrote:

Hi,

I was stumped by this. The two S4 objects below looked exactly the same:

 > a1
An object of class "A"
Slot "aa":
integer(0)
 > a2
An object of class "A"
Slot "aa":
integer(0)

 > str(a1)
Formal class 'A' [package ".GlobalEnv"] with 1 slots
..@ aa: int(0)
 > str(a2)
Formal class 'A' [package ".GlobalEnv"] with 1 slots
..@ aa: int(0)

But they were not identical:

 > identical(a1,a2)
[1] FALSE

Then I found that one had a "names" attribute but not the other:

 > names(attributes(a1))
[1] "aa" "class" "names"
 > names(attributes(a2))
[1] "aa" "class"

 > names(a1)
NULL
 > names(a2)
NULL

Which explained why they were not reported as identical.

After tracking the history of 'a1', I found that it was created with
something like:

 > setClass("A", representation(aa="integer"))
[1] "A"
 > a1 <- new("A")
 > names(a1) <- "K"
 > names(a1)
NULL

So it seems that, by default (i.e. in the absence of a specialized
method), the `names<-` primitive is adding a "names" attribute to the
object. Could this behaviour be modified so it doesn't alter the object?


Eh?  But you did alter the object.  Not only that, you altered it in 
what is technically an invalid way:  Adding a names attribute to a class 
that has no names slot.


The modification that would make sense would be to give you an error in 
the above code.  Not a bad idea, but it's likely to generate more 
complaints in other contexts, particularly where people don't 
distinguish the "list" class from lists with names (the "namedList" class).


A plausible strategy:
 1.  If the class has a vector data slot and no names slot, assign the 
names but with a warning.


 2. Otherwise, throw an error.

(I.e., I would prefer an error throughout, but discretion )

Comments?

John




Thanks,
H.




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


Re: [Rd] By default, `names<-` alters S4 objects

2011-05-16 Thread John Chambers
You set up a names slot in a non-vector.  Maybe that should be allowed, 
maybe not.  But in any case I would not expect the names() primitive to 
find it, because your object has a non-vector type ("S4").  You could do 
a@names if you thought that made sense:



> setClass("A", representation(names="character"))
[1] "A"
> a <- new("A")
> a@names <- "xx"
> a@names
[1] "xx"
> names(a)
NULL


If you wanted something sensible, it's more like:

> setClass("B", representation(names = "character"), contains = "integer")
[1] "B"
> b <- new("B", 1:5)
> names(b) <- letters[1:5]
> b
An object of class "B"
[1] 1 2 3 4 5
Slot "names":
[1] "a" "b" "c" "d" "e"

> names(b)
[1] "a" "b" "c" "d" "e"

This allows both the S4 and the primitive code to deal with a 
well-defined object.


John


On 5/15/11 3:02 PM, Hervé Pagès wrote:

On 11-05-15 11:33 AM, John Chambers wrote:

This is basically a case of a user error that is not being caught:


Sure!

https://stat.ethz.ch/pipermail/r-devel/2009-March/052386.html

..



Ah, that's interesting. I didn't know I could put a names slot in my
class. Last time I tried was at least 3 years ago and that was causing
problems (don't remember the exact details) so I ended up using NAMES
instead. Trying again with R-2.14:

 > setClass("A", representation(names="character"))

 > a <- new("A")

 > attributes(a)
$names
character(0)

$class
[1] "A"
attr(,"package")
[1] ".GlobalEnv"

 > names(a)
NULL

 > names(a) <- "K"

 > attributes(a)
$names
[1] "K"

$class
[1] "A"
attr(,"package")
[1] ".GlobalEnv"

 > names(a)
NULL

Surprise! But that's another story...



The modification that would make sense would be to give you an error in
the above code. Not a bad idea, but it's likely to generate more
complaints in other contexts, particularly where people don't
distinguish the "list" class from lists with names (the "namedList"
class).

A plausible strategy:
1. If the class has a vector data slot and no names slot, assign the
names but with a warning.

2. Otherwise, throw an error.

(I.e., I would prefer an error throughout, but discretion )


Or, at a minimum (if no consensus can be reached about the above
strategy), not add a "names" attribute set to NULL. My original
post was more about keeping the internal representation of objects
"normalized", in general, so identical() is more likely to be
meaningful.

Thanks,
H.



Comments?

John




Thanks,
H.




__
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] By default, `names<-` alters S4 objects

2011-05-16 Thread John Chambers



On 5/16/11 10:09 AM, Hervé Pagès wrote:

On 11-05-16 09:36 AM, John Chambers wrote:

You set up a names slot in a non-vector. Maybe that should be allowed,
maybe not. But in any case I would not expect the names() primitive to
find it, because your object has a non-vector type ("S4").


But the names<-() primitive *does* find it. So either names() and
names<-() should both find it, or they shouldn't. I mean, if you care
about consistency and predictability of course.


That's not the only case where borderline or mistaken behavior is caught 
on assignment, but not on access.  The argument is that assignment can 
afford to check things, but access needs to be fast.  Slot access is 
another case.  There, assignment ensures legality so access can be quick.


The catch is that there are sometimes backdoor ways to assignments, 
partly because slots, attributes and some "builtin" properties like 
names overlap.


What we were talking about before was trying to evolve a sensible rule 
for assigning names to S4 objects.  Let's try to discuss what people 
need to do before carping or indulging in sarcasm.


John



H.



You could do
a@names if you thought that made sense:


> setClass("A", representation(names="character"))
[1] "A"
> a <- new("A")
> a@names <- "xx"
> a@names
[1] "xx"
> names(a)
NULL


If you wanted something sensible, it's more like:

> setClass("B", representation(names = "character"), contains =
"integer")
[1] "B"
> b <- new("B", 1:5)
> names(b) <- letters[1:5]
> b
An object of class "B"
[1] 1 2 3 4 5
Slot "names":
[1] "a" "b" "c" "d" "e"

> names(b)
[1] "a" "b" "c" "d" "e"

This allows both the S4 and the primitive code to deal with a
well-defined object.

John


On 5/15/11 3:02 PM, Hervé Pagès wrote:

On 11-05-15 11:33 AM, John Chambers wrote:

This is basically a case of a user error that is not being caught:


Sure!

https://stat.ethz.ch/pipermail/r-devel/2009-March/052386.html

..



Ah, that's interesting. I didn't know I could put a names slot in my
class. Last time I tried was at least 3 years ago and that was causing
problems (don't remember the exact details) so I ended up using NAMES
instead. Trying again with R-2.14:

> setClass("A", representation(names="character"))

> a <- new("A")

> attributes(a)
$names
character(0)

$class
[1] "A"
attr(,"package")
[1] ".GlobalEnv"

> names(a)
NULL

> names(a) <- "K"

> attributes(a)
$names
[1] "K"

$class
[1] "A"
attr(,"package")
[1] ".GlobalEnv"

> names(a)
NULL

Surprise! But that's another story...



The modification that would make sense would be to give you an error in
the above code. Not a bad idea, but it's likely to generate more
complaints in other contexts, particularly where people don't
distinguish the "list" class from lists with names (the "namedList"
class).

A plausible strategy:
1. If the class has a vector data slot and no names slot, assign the
names but with a warning.

2. Otherwise, throw an error.

(I.e., I would prefer an error throughout, but discretion )


Or, at a minimum (if no consensus can be reached about the above
strategy), not add a "names" attribute set to NULL. My original
post was more about keeping the internal representation of objects
"normalized", in general, so identical() is more likely to be
meaningful.

Thanks,
H.



Comments?

John




Thanks,
H.




__
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] By default, `names<-` alters S4 objects

2011-05-17 Thread John Chambers
One point that may have been unclear, though it's surprising if so.  The 
discussion was about assigning names to S4 objects from classes that do 
NOT have a formal "names" slot.  Of course, having a "names" slot is not 
illegal, it's what one should do to deal with names in S4.  Look at 
class "namedList" for example.


Assigning names() to such a class would go through without warning as it 
does now.


> getClass("namedList")
Class "namedList" [package "methods"]

Slots:

Name:  .Data names
Class:  list character

Extends:
Class "list", from data part
Class "vector", by class "list", distance 2

Known Subclasses: "listOfMethods"
> xx <- new("namedList", list(a=1,b=2))
> names(xx)
[1] "a" "b"
> names(xx) <- c("D", "E")
> xx@names
[1] "D" "E"
>

There was no question of breaking inheritance.

On 5/16/11 4:13 PM, Hervé Pagès wrote:

On 11-05-16 01:53 PM, John Chambers wrote:



On 5/16/11 10:09 AM, Hervé Pagès wrote:

On 11-05-16 09:36 AM, John Chambers wrote:

You set up a names slot in a non-vector. Maybe that should be allowed,
maybe not. But in any case I would not expect the names() primitive to
find it, because your object has a non-vector type ("S4").


But the names<-() primitive *does* find it. So either names() and
names<-() should both find it, or they shouldn't. I mean, if you care
about consistency and predictability of course.


That's not the only case where borderline or mistaken behavior is caught
on assignment, but not on access. The argument is that assignment can
afford to check things, but access needs to be fast. Slot access is
another case. There, assignment ensures legality so access can be quick.

The catch is that there are sometimes backdoor ways to assignments,
partly because slots, attributes and some "builtin" properties like
names overlap.

What we were talking about before was trying to evolve a sensible rule
for assigning names to S4 objects. Let's try to discuss what people need
to do before carping or indulging in sarcasm.


What *you* were talking about but not what my original post was about.
Anyway, about the following proposal:

1. If the class has a vector data slot and no names slot, assign the
names but with a warning.

2. Otherwise, throw an error.

(I.e., I would prefer an error throughout, but discretion )

I personally don't like it because it breaks inheritance. Let's
say I have a class B with a vector data slot and no names slot.
According to 1. names<-() would work out-of-the-box on it (with
a warning), but now if I extend it by adding a names slot, it
breaks.

One thing to consider though is that this works right now (and with
no warning):

 > setClass("I", contains="integer")
[1] "I"
 > i <- new("I", 1:4)
 > names(i) <- LETTERS[1:4]
 > attributes(i)
$class
[1] "I"
attr(,"package")
[1] ".GlobalEnv"

$names
[1] "A" "B" "C" "D"

 > names(i)
[1] "A" "B" "C" "D"

and it's probably what most people would expect (sounds reasonable
after all). So this needs to keep working (with no warning). I can
see 2 ways to avoid breaking inheritance:

(a) not allow a names slot to be added to class I or any
of its subclasses (in other words the .Data and names
slots cannot coexist),
or
(b) have names() and names<-() keep working when the names slot is
added but that is maybe dangerous as it might break C code that
is trying to access the names, that is, inheritance might break
but now at the C level

Now for classes that don't have a .Data slot, they can of course
have a names slot. I don't have a strong opinion on whether names()
and names<-() should access it by default, but honestly that's really
a very small convenience offered to the developer of the class. Also,
for the sake of consistency, the same would need to be done for dim,
dimnames and built-in attributes in general. And also that won't work
if those built-in-attributes-made-slots are not declared with the right
type in the setClass statement (i.e. "character" for names, "integer"
for dim, etc...). And also by default names() would return character(0)
and not NULL. So in the end, potentially a lot of complications /
surprise / inconsistencies for very little value.

Thanks,
H.



John



H.



You could do
a@names if you thought that made sense:


> setClass("A", representation(names="character"))
[1] "A"
> a <- new("A")
> a@names <- "xx"
> a@names
[1] "xx"
> names(a)
NULL


If you wanted something sensible, it's more like:

> setClass(&

Re: [Rd] By default, `names<-` alters S4 objects

2011-05-17 Thread John Chambers



On 5/17/11 9:53 AM, Hervé Pagès wrote:

On 11-05-17 09:04 AM, John Chambers wrote:

One point that may have been unclear, though it's surprising if so. The
discussion was about assigning names to S4 objects from classes that do
NOT have a formal "names" slot. Of course, having a "names" slot is not
illegal, it's what one should do to deal with names in S4.


IMO it looks more like what one should avoid to do right now because
it's broken (as reported previously):

 > setClass("A", representation(names="character"))
 > a <- new("A")
 > names(a) <- "K"
 > names(a)
NULL

And on that particular issue here is what you said:

You set up a names slot in a non-vector. Maybe that should be
allowed, maybe not.

And now:

Of course, having a "names" slot is not illegal, it's what one
should do to deal with names in S4.

??!]


Good grief.  The classes like namedList _are_ vectors, that's the point.

Anyway, this is a waste of time.  I will add some code to r-devel that 
checks S4 objects when assigning names.  People can try it out on their 
examples.




H.



Look at class
"namedList" for example.

Assigning names() to such a class would go through without warning as it
does now.

> getClass("namedList")
Class "namedList" [package "methods"]

Slots:

Name: .Data names
Class: list character

Extends:
Class "list", from data part
Class "vector", by class "list", distance 2

Known Subclasses: "listOfMethods"
> xx <- new("namedList", list(a=1,b=2))
> names(xx)
[1] "a" "b"
> names(xx) <- c("D", "E")
> xx@names
[1] "D" "E"
>

There was no question of breaking inheritance.

On 5/16/11 4:13 PM, Hervé Pagès wrote:

On 11-05-16 01:53 PM, John Chambers wrote:



On 5/16/11 10:09 AM, Hervé Pagès wrote:

On 11-05-16 09:36 AM, John Chambers wrote:

You set up a names slot in a non-vector. Maybe that should be
allowed,
maybe not. But in any case I would not expect the names()
primitive to
find it, because your object has a non-vector type ("S4").


But the names<-() primitive *does* find it. So either names() and
names<-() should both find it, or they shouldn't. I mean, if you care
about consistency and predictability of course.


That's not the only case where borderline or mistaken behavior is
caught
on assignment, but not on access. The argument is that assignment can
afford to check things, but access needs to be fast. Slot access is
another case. There, assignment ensures legality so access can be
quick.

The catch is that there are sometimes backdoor ways to assignments,
partly because slots, attributes and some "builtin" properties like
names overlap.

What we were talking about before was trying to evolve a sensible rule
for assigning names to S4 objects. Let's try to discuss what people
need
to do before carping or indulging in sarcasm.


What *you* were talking about but not what my original post was about.
Anyway, about the following proposal:

1. If the class has a vector data slot and no names slot, assign the
names but with a warning.

2. Otherwise, throw an error.

(I.e., I would prefer an error throughout, but discretion )

I personally don't like it because it breaks inheritance. Let's
say I have a class B with a vector data slot and no names slot.
According to 1. names<-() would work out-of-the-box on it (with
a warning), but now if I extend it by adding a names slot, it
breaks.

One thing to consider though is that this works right now (and with
no warning):

> setClass("I", contains="integer")
[1] "I"
> i <- new("I", 1:4)
> names(i) <- LETTERS[1:4]
> attributes(i)
$class
[1] "I"
attr(,"package")
[1] ".GlobalEnv"

$names
[1] "A" "B" "C" "D"

> names(i)
[1] "A" "B" "C" "D"

and it's probably what most people would expect (sounds reasonable
after all). So this needs to keep working (with no warning). I can
see 2 ways to avoid breaking inheritance:

(a) not allow a names slot to be added to class I or any
of its subclasses (in other words the .Data and names
slots cannot coexist),
or
(b) have names() and names<-() keep working when the names slot is
added but that is maybe dangerous as it might break C code that
is trying to access the names, that is, inheritance might break
but now at the C level

Now for classes that don't have a .Data slot, they can of course
have a names slot. I don't have a strong opinion on whether names()
and names<-() should access it by default, but honestly that's really
a very small convenience offered to the developer of the class. Also,
for the sak

Re: [Rd] possibly invalid assertion in setRefClass?

2011-06-02 Thread John Chambers
Right, but Michael's point is valid.  It's the standard bug from having 
to explicitly check for a non-empty list before taking names(x).


Will fix.  Thanks for the catch.

John

On 6/1/11 9:21 AM, William Dunlap wrote:

-Original Message-
From: r-devel-boun...@r-project.org
[mailto:r-devel-boun...@r-project.org] On Behalf Of Michael Lawrence
Sent: Wednesday, June 01, 2011 9:15 AM
To: r-devel@r-project.org
Subject: [Rd] possibly invalid assertion in setRefClass?


setRefClass("Foo", fields = list())

Error in setRefClass("Foo", fields = list()) :
   A list argument for fields must have nonempty names for all
the fields

In my opinion, the above should not fail. There are no fields.


You can work around it by attaching an empty names attribute
to fields:
   >  setRefClass("Foo", fields = structure(list(), names=character()))
   Generator object for class "Foo":

   No fields defined

Class Methods:
   "callSuper", "copy", "export", "field", "getClass", "getRefClass",
"import", "initFields"


Reference Superclasses:
   "envRefClass"

Bill Dunlap
Spotfire, TIBCO Software
wdunlap tibco.com




Thanks,
Michael

[[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



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


Re: [Rd] Bug or feature: using "ANY" as a generic field class (was: '[R] Is there a (virtual) class that all R objects inherit from?)

2011-06-03 Thread John Chambers
Well, your mail is unclear as to what you expected, but there is one bug 
shown by your example.


The behavior of S4 classes is sensible, at least as far as the example 
shows:



> setClass("A", representation(x="ANY"))
[1] "A"
> setClass("B", contains="A", representation(x="character"))
[1] "B"
> new("B", x=1:3)
Error in validObject(.Object) :
  invalid class "B" object: invalid object for slot "x" in class "B": 
got class "integer", should be or extend class "character"


You couldn't expect the new() call to work, as the error message clearly 
explains.  A legitimate call does work:


> new("B", x = "abc")
An object of class "B"
Slot "x":
[1] "abc"

The reference classes should work the same way, but don't, as your 
example shows.


A <- setRefClass(
+ Class="A",
+ fields=list(
+ .PRIMARYDATA="ANY"
+ ),
+ contains=c("VIRTUAL")
+ )
> B <- setRefClass(
+ Class="B",
+ fields=list(
+ .PRIMARYDATA="character"
+ ),
+ contains=c("A")
+ )
Error in `insertFields<-`(`*tmp*`, value = "character") :
  The overriding class("character") of field ".PRIMARYDATA" is not a 
subclass of the existing field definition ("ANY")


We'll fix that.  And, yes, "ANY" is intended as a universal superclass, 
but is usually not mentioned explicitly.



On 6/3/11 6:53 AM, Janko Thyson wrote:

Dear list,

I was wondering if you could help me out in clarifying something:
Is it possible to use class "ANY" in slots/fields of formal classes if you
a) do not want to restrict valid classes of that field and
b) if you are making explicit use of class inheritance?

It seems to work in simple scenarios but produces errors when class
inheritance comes into play. So I was wondering if that's a feature or a
bug.

If using "ANY" is not the right way, I'd appreciate a pointer to how you
can to this.

See previous post with an example below.

Regards,
Janko

On 06/03/2011 01:53 AM, Janko Thyson wrote:

On 31.05.2011 18:17, Martin Morgan wrote:

On 05/30/2011 07:02 AM, Janko Thyson wrote:

Dear list,

I would like to set one specific Reference Class field to be of an
arbitrary class. Is there a class that all R objects inherit from? I
thought that "ANY" was something like this, but obviously that's not
true:


inherits(1:3, "ANY")

[1] FALSE


I can't speak to the implementation, but ANY functions as a base class
in terms of slot / field assignment and inheritance, e.g.,

setClass("A", representation(x="ANY"))
new("A", x=1:3)

Martin


Hi Martin,

sorry for the late response. The way you do it works. Yet, when you
declare dependencies more explicitly (contains=XY), then R complains. Is
this a feature or a bug (with respect to the "less explicit" way working
just fine)? See the example below:

# S4
setClass("A", representation(x="ANY"))
new("A", x=1:3)

setClass("A", representation(x="ANY"))
setClass("B", contains="A", representation(x="character"))
new("B", x=1:3)

# Reference Classes
setRefClass(
Class="A",
fields=list(
.PRIMARYDATA="ANY"
),
contains=c("VIRTUAL")
)
B<- setRefClass(
Class="B",
fields=list(
.PRIMARYDATA="character"
),
contains=c("A")
)


Bug, I'd say. Martin



Regards,
Janko


Regards,
Janko

[[alternative HTML version deleted]]

__
r-h...@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-help
PLEASE do read the posting guide
http://www.R-project.org/posting-guide.html
and provide commented, minimal, self-contained, reproducible code.








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


Re: [Rd] Bug or feature: using "ANY" as a generic field class (was: '[R] Is there a (virtual) class that all R objects inherit from?)

2011-06-06 Thread John Chambers
Should now behave as expected in r-devel and 2.13 patched, as of SVN 
56045, June 4.  (noted in the NEWS file.)



On 6/6/11 6:27 AM, Janko Thyson wrote:

Thanks a lot for your reply and I'm sorry if I didn't make it quite
clear what I expected, but you got it right:

I'd simply like to see the same behavior for Reference Classes as for S4
classes when extending classes with "ANY" fields as featured in the
example below.

 > setClass("A", representation(x="ANY"))
[1] "A"
 > setClass("B", contains="A", representation(x="character"))
[1] "B"
 > new("B", x = "abc")
An object of class "B"
Slot "x":
[1] "abc"

Thanks for addressing this!

Regards,
Janko

On 03.06.2011 19:13, John Chambers wrote:

Well, your mail is unclear as to what you expected, but there is one
bug shown by your example.

The behavior of S4 classes is sensible, at least as far as the example
shows:


> setClass("A", representation(x="ANY"))
[1] "A"
> setClass("B", contains="A", representation(x="character"))
[1] "B"
> new("B", x=1:3)
Error in validObject(.Object) :
invalid class "B" object: invalid object for slot "x" in class "B":
got class "integer", should be or extend class "character"

You couldn't expect the new() call to work, as the error message
clearly explains. A legitimate call does work:

> new("B", x = "abc")
An object of class "B"
Slot "x":
[1] "abc"

The reference classes should work the same way, but don't, as your
example shows.

A <- setRefClass(
+ Class="A",
+ fields=list(
+ .PRIMARYDATA="ANY"
+ ),
+ contains=c("VIRTUAL")
+ )
> B <- setRefClass(
+ Class="B",
+ fields=list(
+ .PRIMARYDATA="character"
+ ),
+ contains=c("A")
+ )
Error in `insertFields<-`(`*tmp*`, value = "character") :
The overriding class("character") of field ".PRIMARYDATA" is not a
subclass of the existing field definition ("ANY")

We'll fix that. And, yes, "ANY" is intended as a universal superclass,
but is usually not mentioned explicitly.


On 6/3/11 6:53 AM, Janko Thyson wrote:

Dear list,

I was wondering if you could help me out in clarifying something:
Is it possible to use class "ANY" in slots/fields of formal classes
if you
a) do not want to restrict valid classes of that field and
b) if you are making explicit use of class inheritance?

It seems to work in simple scenarios but produces errors when class
inheritance comes into play. So I was wondering if that's a feature or a
bug.

If using "ANY" is not the right way, I'd appreciate a pointer to how you
can to this.

See previous post with an example below.

Regards,
Janko

On 06/03/2011 01:53 AM, Janko Thyson wrote:

On 31.05.2011 18:17, Martin Morgan wrote:

On 05/30/2011 07:02 AM, Janko Thyson wrote:

Dear list,

I would like to set one specific Reference Class field to be of an
arbitrary class. Is there a class that all R objects inherit from? I
thought that "ANY" was something like this, but obviously that's not
true:


inherits(1:3, "ANY")

[1] FALSE


I can't speak to the implementation, but ANY functions as a base class
in terms of slot / field assignment and inheritance, e.g.,

setClass("A", representation(x="ANY"))
new("A", x=1:3)

Martin


Hi Martin,

sorry for the late response. The way you do it works. Yet, when you
declare dependencies more explicitly (contains=XY), then R
complains. Is
this a feature or a bug (with respect to the "less explicit" way
working
just fine)? See the example below:

# S4
setClass("A", representation(x="ANY"))
new("A", x=1:3)

setClass("A", representation(x="ANY"))
setClass("B", contains="A", representation(x="character"))
new("B", x=1:3)

# Reference Classes
setRefClass(
Class="A",
fields=list(
.PRIMARYDATA="ANY"
),
contains=c("VIRTUAL")
)
B<- setRefClass(
Class="B",
fields=list(
.PRIMARYDATA="character"
),
contains=c("A")
)


Bug, I'd say. Martin



Regards,
Janko


Regards,
Janko

[[alternative HTML version deleted]]

__
r-h...@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-help
PLEASE do read the posting guide
http://www.R-project.org/posting-guide.html
and provide commented, minimal, self-contained, reproducible code.








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




--
-

Re: [Rd] Overloading S4 methods

2011-06-06 Thread John Chambers
This is a bug, medium-subtle, but also raises an interesting software 
design point.


The Bug:

Nothing specific about "ANY" and "missing", but the issue is whether the 
method was inherited (the "ANY" case) or defined directly (the "missing" 
case).


Generic functions keep a cached table of dispatched methods, to save 
determining inherited methods repeatedly for calls with the same 
signature.  When pkg B is loaded, the inherited methods are reset, but 
apparently the directly defined ones were not (but should have been if 
pkg B overrides the method).


It's interesting that this bug seems not to have been reported before, 
which leads to:


The Software Design Point:

When a package (B) extends the class/method software in another package 
(A), typically B adds new classes and perhaps new generic functions with 
methods for previous classes in A as well as classes in B.  It might 
also extend the behavior for classes in A to other generic functions.


What is less usual is to directly override an existing method for a 
class that belongs to A.  Notice that there can be side-effects, such as 
behavior of examples or tests in package A depending on whether B has 
been loaded or not.  And objects created entirely from A could have 
their computations change after B was loaded.


Nothing at all illegal here, and we'll make it work.  But a more 
predictable implementation for most applications would, say, define a 
new class in B that extended the class in A.  In your example (very 
helpful, by the way) one might have a class "mynumB", perhaps with the 
same slots as "mynum" but with modified behavior.


If you want to keep the current implementation, though, a workaround 
until the bug is fixed would be something like:


setMethod("plot", c("mynum", "missing"), getMethod("plot", c("mynum", 
"missing")))


executed after B is attached (I think it could be in the .onLoad 
function for B, but have not tested that).


John


On 6/6/11 4:11 AM, Iago Mosqueira wrote:

On Wed, Jun 1, 2011 at 6:04 PM, Martin Morgan  wrote:

On 06/01/2011 04:39 AM, Iago Mosqueira wrote:


Dear all,

I am experiencing some problems with S4 method overloading. I have
defined a generic for graphics:plot, using

setGeneric("plot", useAsDefault = plot)

and with

importFrom('graphics', 'plot') and

exportMethods('plot') in the NAMESPACE file of pkg A.


I'd guess you were creating two generics (explicitly in pkgA, implicitly in
pkgB). Maybe

  export(plot)

in NAMESPACE of pkg A,

  importFrom('pkgA', plot)
  exportMethods(plot)

in pkg B. Feel free to post to the list if that's helpful.

Martin



I then proceed to define a method for signature c('myS4class',
'missing'). This works as expected: selectMethod('plot',
c('myS4class', 'missing')) returns the newly defined method, and the
method gets called when invoked.

Another pkg, B, wishes to overload this and redefines the method for
the same signature. A method is defined for c('myS4class', 'missing'),
and exported on the NAMESPACE. The new method is shown by
selectMethod() after pkg B has been loaded, but a call to

plot(anobjectofmyS4class)

comes up with the result of running the first method, from pkg A. I
have tried importing 'plot' in B's NAMESPACE from both graphics or A,
but the end result is the same.

Package B does the same thing for a method created by pkg A, myMethod,
and that works fine.

Any pointers or where this might be going wrong? How is it that a
different method than the one shown by selectMethod() is being run?
Something to do with the 'missing' part of the signature?

Many thanks,



Iago Mosqueira


Dear all,

I have tried Martin's suggestion, but the problem persists. It seems
to be related to having 'missing' in the signature, as doing the same
kind of overloading for c('myclass', 'ANY') work as expected.

I am attaching 2 simple packages where I attempt this repeated
overloading of plot for the same class. Script below, also found in
Bpkg/tests.test.R, shows what I have encountered so far:
plot('myclass', 'ANY') can be re-overloaded, but plot('myclass',
'missing') cannot in the same way. If I run

trace("plot", browser, exit=browser, signature = c("mynum", "missing"))

the  new method is actually called.

Any hint on what I am doing wrong or where to look for an explanation
will be much appreciated.

Best regards,


Iago Mosqueira



__
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] Reference Classes: shortcut like 'isS4' for Ref Classes?

2011-06-06 Thread John Chambers

As it says on the help page ?ReferenceClasses:

All reference classes inherit from the class "envRefClass"

So,
  is(x, "envRefClass")

And, less well documented but less typing:

  is(x, "refClass")
also works.

On 6/6/11 9:48 AM, Janko Thyson wrote:

Dear list,

is there a shortcut-function to check whether a class is a Reference
Class or not? There's something like this for S4 classes
('isS4(object)'), but I couldn't find anything regarding Ref Classes.

Currently, I'm doing it this way, which is a bit clumsy:

A <- setRefClass("A", fields=list(X="numeric"))
a <- A$new()

isRefClass <- function(object, ...){
return(getClass(class(object))@class == "refClassRepresentation")
# getRefClass(class(object))@class == "refObjectGenerator"
}

isRefClass(a)
[1] TRUE

Regards,
Janko

__
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] Overloading S4 methods

2011-06-07 Thread John Chambers
Yes, Dylan is in many ways more authoritarian than R!  Possibly also 
with fewer users to be annoyed.


We might go to a warning as Iago suggests.  If we did add a warning, it 
would be likely be more useful in the setMethod() call than at CMD check 
time, after the package has been designed and implemented.


John

On 6/7/11 6:15 AM, luke-tier...@uiowa.edu wrote:

On Mon, 6 Jun 2011, John Chambers wrote:


This is a bug, medium-subtle, but also raises an interesting software
design point.

The Bug:

Nothing specific about "ANY" and "missing", but the issue is whether
the method was inherited (the "ANY" case) or defined directly (the
"missing" case).

Generic functions keep a cached table of dispatched methods, to save
determining inherited methods repeatedly for calls with the same
signature. When pkg B is loaded, the inherited methods are reset, but
apparently the directly defined ones were not (but should have been if
pkg B overrides the method).

It's interesting that this bug seems not to have been reported before,
which leads to:

The Software Design Point:

When a package (B) extends the class/method software in another
package (A), typically B adds new classes and perhaps new generic
functions with methods for previous classes in A as well as classes in
B. It might also extend the behavior for classes in A to other generic
functions.

What is less usual is to directly override an existing method for a
class that belongs to A. Notice that there can be side-effects, such
as behavior of examples or tests in package A depending on whether B
has been loaded or not. And objects created entirely from A could have
their computations change after B was loaded.


Dylan is simliar in using a generic funciton model. One of the Dylan
books -- I forget which one -- strongly recomends that a library only
define a method if either it also defines the generic or if it defines
one of the classes the method is specialized on. THis isn't an enforced
requirement but a strong recommendation.

Best,

luke



Nothing at all illegal here, and we'll make it work. But a more
predictable implementation for most applications would, say, define a
new class in B that extended the class in A. In your example (very
helpful, by the way) one might have a class "mynumB", perhaps with the
same slots as "mynum" but with modified behavior.

If you want to keep the current implementation, though, a workaround
until the bug is fixed would be something like:

setMethod("plot", c("mynum", "missing"), getMethod("plot", c("mynum",
"missing")))

executed after B is attached (I think it could be in the .onLoad
function for B, but have not tested that).

John


On 6/6/11 4:11 AM, Iago Mosqueira wrote:

On Wed, Jun 1, 2011 at 6:04 PM, Martin Morgan wrote:

On 06/01/2011 04:39 AM, Iago Mosqueira wrote:


Dear all,

I am experiencing some problems with S4 method overloading. I have
defined a generic for graphics:plot, using

setGeneric("plot", useAsDefault = plot)

and with

importFrom('graphics', 'plot') and

exportMethods('plot') in the NAMESPACE file of pkg A.


I'd guess you were creating two generics (explicitly in pkgA,
implicitly in
pkgB). Maybe

export(plot)

in NAMESPACE of pkg A,

importFrom('pkgA', plot)
exportMethods(plot)

in pkg B. Feel free to post to the list if that's helpful.

Martin



I then proceed to define a method for signature c('myS4class',
'missing'). This works as expected: selectMethod('plot',
c('myS4class', 'missing')) returns the newly defined method, and the
method gets called when invoked.

Another pkg, B, wishes to overload this and redefines the method for
the same signature. A method is defined for c('myS4class', 'missing'),
and exported on the NAMESPACE. The new method is shown by
selectMethod() after pkg B has been loaded, but a call to

plot(anobjectofmyS4class)

comes up with the result of running the first method, from pkg A. I
have tried importing 'plot' in B's NAMESPACE from both graphics or A,
but the end result is the same.

Package B does the same thing for a method created by pkg A, myMethod,
and that works fine.

Any pointers or where this might be going wrong? How is it that a
different method than the one shown by selectMethod() is being run?
Something to do with the 'missing' part of the signature?

Many thanks,



Iago Mosqueira


Dear all,

I have tried Martin's suggestion, but the problem persists. It seems
to be related to having 'missing' in the signature, as doing the same
kind of overloading for c('myclass', 'ANY') work as expected.

I am attaching 2 simple packages where I attempt this repeated
overloading of plot for the same class. Script below, also found in
Bpkg/tes

Re: [Rd] Overloading S4 methods

2011-06-07 Thread John Chambers

On 6/7/11 2:02 PM, Iago Mosqueira wrote:

Can then the warning be turned off in any way to avoid it showing up
on check? Maybe an argument to confirm 'I know what I am doing so I
need no warning, thank you very much'.


Well, this is still new territory since the bug didn't seem to have been 
encountered before your example.  We won't add the warning in the 
immediate future, and as Luke pointed out, even Dylan just advises. 
This may be more a matter for a "code tools" approach.  So not to worry 
just yet!


John




Iago

On Tue, Jun 7, 2011 at 7:06 PM, John Chambers  wrote:

Yes, Dylan is in many ways more authoritarian than R!  Possibly also with
fewer users to be annoyed.

We might go to a warning as Iago suggests.  If we did add a warning, it
would be likely be more useful in the setMethod() call than at CMD check
time, after the package has been designed and implemented.

John

On 6/7/11 6:15 AM, luke-tier...@uiowa.edu wrote:


On Mon, 6 Jun 2011, John Chambers wrote:


This is a bug, medium-subtle, but also raises an interesting software
design point.

The Bug:

Nothing specific about "ANY" and "missing", but the issue is whether
the method was inherited (the "ANY" case) or defined directly (the
"missing" case).

Generic functions keep a cached table of dispatched methods, to save
determining inherited methods repeatedly for calls with the same
signature. When pkg B is loaded, the inherited methods are reset, but
apparently the directly defined ones were not (but should have been if
pkg B overrides the method).

It's interesting that this bug seems not to have been reported before,
which leads to:

The Software Design Point:

When a package (B) extends the class/method software in another
package (A), typically B adds new classes and perhaps new generic
functions with methods for previous classes in A as well as classes in
B. It might also extend the behavior for classes in A to other generic
functions.

What is less usual is to directly override an existing method for a
class that belongs to A. Notice that there can be side-effects, such
as behavior of examples or tests in package A depending on whether B
has been loaded or not. And objects created entirely from A could have
their computations change after B was loaded.


Dylan is simliar in using a generic funciton model. One of the Dylan
books -- I forget which one -- strongly recomends that a library only
define a method if either it also defines the generic or if it defines
one of the classes the method is specialized on. THis isn't an enforced
requirement but a strong recommendation.

Best,

luke



Nothing at all illegal here, and we'll make it work. But a more
predictable implementation for most applications would, say, define a
new class in B that extended the class in A. In your example (very
helpful, by the way) one might have a class "mynumB", perhaps with the
same slots as "mynum" but with modified behavior.

If you want to keep the current implementation, though, a workaround
until the bug is fixed would be something like:

setMethod("plot", c("mynum", "missing"), getMethod("plot", c("mynum",
"missing")))

executed after B is attached (I think it could be in the .onLoad
function for B, but have not tested that).

John


On 6/6/11 4:11 AM, Iago Mosqueira wrote:


On Wed, Jun 1, 2011 at 6:04 PM, Martin Morgan  wrote:


On 06/01/2011 04:39 AM, Iago Mosqueira wrote:


Dear all,

I am experiencing some problems with S4 method overloading. I have
defined a generic for graphics:plot, using

setGeneric("plot", useAsDefault = plot)

and with

importFrom('graphics', 'plot') and

exportMethods('plot') in the NAMESPACE file of pkg A.


I'd guess you were creating two generics (explicitly in pkgA,
implicitly in
pkgB). Maybe

export(plot)

in NAMESPACE of pkg A,

importFrom('pkgA', plot)
exportMethods(plot)

in pkg B. Feel free to post to the list if that's helpful.

Martin



I then proceed to define a method for signature c('myS4class',
'missing'). This works as expected: selectMethod('plot',
c('myS4class', 'missing')) returns the newly defined method, and the
method gets called when invoked.

Another pkg, B, wishes to overload this and redefines the method for
the same signature. A method is defined for c('myS4class', 'missing'),
and exported on the NAMESPACE. The new method is shown by
selectMethod() after pkg B has been loaded, but a call to

plot(anobjectofmyS4class)

comes up with the result of running the first method, from pkg A. I
have tried importing 'plot' in B's NAMESPACE from both graphics or A,
but the end result is the same.

Package B does the same thing for a method created by pkg A, myMethod,
and that works fine.

Any point

Re: [Rd] Overloading S4 methods

2011-06-08 Thread John Chambers

The bug should be fixed in r-devel and 2.13 patched, as of svn rev. 56090.

John

On 6/7/11 12:42 AM, Iago Mosqueira wrote:

On Mon, Jun 6, 2011 at 11:28 PM, John Chambers  wrote:

This is a bug, medium-subtle, but also raises an interesting software design
point.

The Bug:

Nothing specific about "ANY" and "missing", but the issue is whether the
method was inherited (the "ANY" case) or defined directly (the "missing"
case).

Generic functions keep a cached table of dispatched methods, to save
determining inherited methods repeatedly for calls with the same signature.
  When pkg B is loaded, the inherited methods are reset, but apparently the
directly defined ones were not (but should have been if pkg B overrides the
method).

It's interesting that this bug seems not to have been reported before, which
leads to:

The Software Design Point:

When a package (B) extends the class/method software in another package (A),
typically B adds new classes and perhaps new generic functions with methods
for previous classes in A as well as classes in B.  It might also extend the
behavior for classes in A to other generic functions.

What is less usual is to directly override an existing method for a class
that belongs to A.  Notice that there can be side-effects, such as behavior
of examples or tests in package A depending on whether B has been loaded or
not.  And objects created entirely from A could have their computations
change after B was loaded.

Nothing at all illegal here, and we'll make it work.  But a more predictable
implementation for most applications would, say, define a new class in B
that extended the class in A.  In your example (very helpful, by the way)
one might have a class "mynumB", perhaps with the same slots as "mynum" but
with modified behavior.

If you want to keep the current implementation, though, a workaround until
the bug is fixed would be something like:

setMethod("plot", c("mynum", "missing"), getMethod("plot", c("mynum",
"missing")))

executed after B is attached (I think it could be in the .onLoad function
for B, but have not tested that).

John


Many thanks for the very complete explanation. We are using this
mechanism to provide ggplot2-based plot for some classes, to
substitute the initial lattice-based ones, so the effects are limited
to visual output and not results of computation, but it is good you
reminded me of the possible side effects of this strategy. Is maybe a
warning during R CMD check appropriate here?


Adding the call to setMethod(..., getMethod()) did not work if placed
inside .onLoad, and in fact had the effect of getMethod() now
returning the Apkg method after Bpkg was loaded.

Running the line after Bpkg has loaded did sort it out. What would
then be the best way of adding this command to the pkg loading
process? I have also tried adding it to a zzz.R file on iuts own but
that did not work, I still need to re-run it after loading has
finished.

Many thanks,


Iago




On 6/6/11 4:11 AM, Iago Mosqueira wrote:


On Wed, Jun 1, 2011 at 6:04 PM, Martin Morganwrote:


On 06/01/2011 04:39 AM, Iago Mosqueira wrote:


Dear all,

I am experiencing some problems with S4 method overloading. I have
defined a generic for graphics:plot, using

setGeneric("plot", useAsDefault = plot)

and with

importFrom('graphics', 'plot') and

exportMethods('plot') in the NAMESPACE file of pkg A.


I'd guess you were creating two generics (explicitly in pkgA, implicitly
in
pkgB). Maybe

  export(plot)

in NAMESPACE of pkg A,

  importFrom('pkgA', plot)
  exportMethods(plot)

in pkg B. Feel free to post to the list if that's helpful.

Martin



I then proceed to define a method for signature c('myS4class',
'missing'). This works as expected: selectMethod('plot',
c('myS4class', 'missing')) returns the newly defined method, and the
method gets called when invoked.

Another pkg, B, wishes to overload this and redefines the method for
the same signature. A method is defined for c('myS4class', 'missing'),
and exported on the NAMESPACE. The new method is shown by
selectMethod() after pkg B has been loaded, but a call to

plot(anobjectofmyS4class)

comes up with the result of running the first method, from pkg A. I
have tried importing 'plot' in B's NAMESPACE from both graphics or A,
but the end result is the same.

Package B does the same thing for a method created by pkg A, myMethod,
and that works fine.

Any pointers or where this might be going wrong? How is it that a
different method than the one shown by selectMethod() is being run?
Something to do with the 'missing' part of the signature?

Many thanks,



Iago Mosqueira


Dear all,

I have tried Martin's suggestion, but the problem persists. It seem

Re: [Rd] Reference Class error message: may be caused by lazy evaluation?

2011-06-09 Thread John Chambers

Good catch.

Here's the problem.  To save space and time, reference methods are not 
all copied to every object in the class.  Instead, the methods are 
copied in when first accessed.   Methods are functions which use the 
object as their environment.  So that is the sense in which "lazy 
evaluation" is involved.


If a method calls another method (add() calling addOne() in your 
example), then the method for the `$` operator knows to copy over that 
method (addOne).  (The second of my examples below shows this.)  But if 
the method _refers_ to another method without calling it, the code 
analysis does not currently catch the reference.


We can fix that, although it's a little subtle. Meanwhile, your 
showself() is a good workaround.


For anyone interested, the code below illustrates.

One point of style.  I would suggest saving the generator object and 
calling its $new() method, as below, rather than treating the reference 
class as an S4 class.  The result is identical AFAIK, but the style is 
more typical of such OOP languages.


John

---
> tc <-  setRefClass("testclass", fields = list(a = "numeric"),
+ methods = list(

+   ))
> t1 <- tc$new(a=1)
> ss = t1$show
> ss
Class method definition for method show()
function ()
{
print(addOne)
}

> ev = environment(ss)
> ev

> t1
An object of class "testclass"
  #  same environment
> objects(ev)
[1] "a""show"  # not addOne, though
> t1$addOne
Class method definition for method addOne()
function ()
{
a <<- a + 1
print(a)
}

> objects(ev)
[1] "a"  "addOne" "show"  #  now addOne is there


On 6/8/11 4:38 PM, Tengfei Yin wrote:

Dear All,

I came across an error message recently when constructing a reference class,
an example is attached below, it looks like only if I call a specific method
in advance, otherwise it cannot be found in defined method without using
.self, this make it difficulty that sometimes in my initialize method, I
need to call other method defined in the same reference class, the
workaround for this is add .sef to it.


###  example begin 
setRefClass("testclass", fields = list(a = "numeric"),
 methods = list(
   addOne = function(){
 a<<- a+1
 print(a)
   },
   add = function(){
 addOne()
   },
   show = function(){
 print(addOne)
   },
   showself = function(){
 print(.self$addOne)
   }
   ))

obj<- new("testclass", a = 1)
obj$show()  #
Error in print(addOne) : object 'addOne' not found
obj$addOne()   #
return 2, works
obj$show()  #
after calling addOne(), show() works

## works if use .self$...
obj2<- new("testclass", a = 1)
obj2$showself()

## works when call the method directly within another method
obj3<- new("testclass", a = 1)
obj3$add()

 end ##

I am still learning this new technique, if I made any mistake I didn't
notice before, please let me know, I will really appreciate that.

Thanks a lot!

Tengfei



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


Re: [Rd] Class not found when search in .onLoad

2011-06-23 Thread John Chambers
The workaround is to use the package's namespace, as you did.  That's 
one of the reasons why pkgname is an argument to .onLoad().


Depending on what you want to do, you can either use the namespace as an 
argument where= or get the class definition from the namespace and use 
it in place of the class name.


A side advantage is that such checks work regardless of whether or not 
the classes, etc. are exported from the package.  Also, on the remote 
chance there is another class of the same name, the check works 
unambiguously on your package's version.


The relevant part of your script, modified accordingly, seems to work as 
desired.


John


# script.R


setClass('A', representation(data='numeric'))

setClass('B', contains='A') # the argument is contains=

check.classes <- function(where){

message("isClass('A', where = where): ", methods::isClass('A', where = 
where))


message("isClass('B', where = where): ", methods::isClass('B', where = 
where))


classA <- getClass('A', where = where)
classB <- getClass('B', where = where)
message("extends(classB, classA): ", methods::extends(classB, classA))
}

.onLoad <- function(libname, pkgname=NULL){
cat("\n## .onLoad ##\n")
check.classes(asNamespace(pkgname))
}

.onAttach <- function(libname, pkgname){
cat("\n## .onAttach ##\n")
check.classes(asNamespace(pkgname))
}




On 6/23/11 4:22 AM, Renaud Gaujoux wrote:

Hi,

I am facing with a strange behaviour of isClass and extends when these
are called in .onLoad in both R 2.12.1 and R 2.13.0. This is preventing
my package from doing some object initializations at a proper place
(i.e. in .onLoad).

Suppose one defines two S4 classes in a package, and that one needs to
check the inheritance between these two when loading the package (e.g.
to validate slots in objects).
See package attached or code below (not sure attachments can go through).

in R 2.13.0:
At the loading check after installation, the classes are not found by
`isClass` and `extends` when these are called in .onLoad, but are
correctly found when called in .onAttach.
However findClass correctly finds the class in both case, as well as
isClass if it is called with the argument
`where=asNamespace('')`.
When the package is loaded from an open R session, the behaviour is the
same.

in R 2.12.1:
the classes are correctly found by isClass and extends when these are
called in .onLoad or .onAttach, but only at installation (i.e. at the
loading check after R CMD INSTALL).
When the package is loaded from an open R session, one fails to find the
classes only in .onLoad while in .onAttach they are correctly found.

This is really an issue as up to now I was using .onAttach to do my
checks and initialization, but it is not a wise thing as package that
would only need to import my package (load and not attach) will not get
internal objects properly initialized. All this should be done in
.onLoad, but I cannot do it due to this behaviour of `extends`.

Can someone provide some explanations or work around.

Thank you,
Renaud



# script.R


setClass('A', representation(data='numeric'))

setClass('B', contain='A')

check.classes <- function(){

a <- new('A')
b <- new('B')

message("isClass('A'): ", methods::isClass('A'))
message("isClass('A') in namespace: ", methods::isClass('A',
where=asNamespace('anRpackage')))
message("findClass('A'): ")
print(methods::findClass('A'))

message("isClass('B'): ", methods::isClass('B'))
message("isClass('B') in namespace: ", methods::isClass('B',
where=asNamespace('anRpackage')))
message("findClass('B'): ")
print(methods::findClass('B'))

message("extends('B', 'A'): ", methods::extends('B', 'A'))
message("is(a, 'A'): ", is(a, 'A'))
message("inherits(a, 'A'): ", inherits(a, 'A'))
message("is(b, 'A'): ", is(b, 'A'))
}

.onLoad <- function(libname, pkgname=NULL){
cat("\n## .onLoad ##\n")
check.classes()
}

.onAttach <- function(libname, pkgname){
cat("\n## .onAttach ##\n")
check.classes()
}




..


###
UNIVERSITY OF CAPE TOWN
This e-mail is subject to the UCT ICT policies and e-mail disclaimer
published on our website at
http://www.uct.ac.za/about/policies/emaildisclaimer/ or obtainable from
+27 21 650 9111. This e-mail is intended only for the person(s) to whom
it is addressed. If the e-mail has reached you in error, please notify
the author. If you are not the intended recipient of the e-mail you may
not use, disclose, copy, redirect or print the content. If this e-mail
is not related to the business of UCT it is sent by the sender in the
sender's individual capacity.

###




__
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] Class not found when search in .onLoad

2011-06-24 Thread John Chambers

On 6/24/11 12:53 AM, Renaud Gaujoux wrote:

Thank you John for your response.

Things are a little bit more complicated though. The inheritance checks
are not only made in .onLoad, they are part of a class validity method,
which is called in .onLoad because some objects from this class are
created at this stage. Such objects can also be created at any moment,
not in a call from .onLoad.

More or less briefly:
class 'A' is in fact a virtual class defined in the package's namespace,
with the purpose of defining a common interface. While the package does
provide some derived classes (i.e. defined within the namespace), users
too must be able to define derived classes from 'A' (i.e. not defined
within the namespace).
In another class from the namespace, the validity method checks that one
of its character slot contains the name of a class that inherits from
interface 'A'.


Strictly speaking, that is not meaningful.  A class (like any R object) 
is uniquely referenced by a name *and an environment*.  The name of a 
package can be used to construct the environment, but your "character 
slot" won't identify a class reliably unless the character string has a 
"package" attribute.


Look at class(x), for example, from an object from one of these classes. 
 It will have a "package" attribute identifying the package.
The character string with the package attribute is what you should be 
storing in the slot (or else store the class definition---takes more 
space but is slightly more efficient).




I was just expecting `isClass` and `extends` to also work in .onLoad
without specifying the argument `where` (i.e. searching everywhere,
starting by the package's namespace if called within a namespace). The
argument `where` being there to allow finer search.

There is no argument pkgname to the validity method, to directly apply
the work around. I guess I can always check the presence of the class in
the some-how hard-coded namespace, and if it is not found there look for
the class elsewhere:

#...
clref <- getClass('A', .Force=TRUE, where=THE.NAMESPACE)
cl <- getClass(name, .Force=TRUE, where=THE.NAMESPACE)
if( is.null(cl) )
cl <- getClass(name, .Force=TRUE)

if( !extends(cl, clref) )
return('invalid slot')
#...

I will use this, in last resort, although it feels strange as it will
only be to deal with the case where objects are created within a call to
.onLoad.

I am really interested in understanding why all this:

- what makes this call so different?
In my sample package, if I add a call `check.classes()` directly in
script.R, the classes are correctly found when the installation sources
the script prepare the package for lazy loading.
- why things seemed to work ok in R-2.12.1 at the installation loading
check, but do not work when loading the package from an R session?

Could you please briefly give some explanations or pointers?

Thank you.

Bests,
Renaud

On 23/06/2011 18:44, John Chambers wrote:

The workaround is to use the package's namespace, as you did. That's
one of the reasons why pkgname is an argument to .onLoad().

Depending on what you want to do, you can either use the namespace as
an argument where= or get the class definition from the namespace and
use it in place of the class name.

A side advantage is that such checks work regardless of whether or not
the classes, etc. are exported from the package. Also, on the remote
chance there is another class of the same name, the check works
unambiguously on your package's version.

The relevant part of your script, modified accordingly, seems to work
as desired.

John


# script.R


setClass('A', representation(data='numeric'))

setClass('B', contains='A') # the argument is contains=

check.classes <- function(where){

message("isClass('A', where = where): ", methods::isClass('A', where =
where))

message("isClass('B', where = where): ", methods::isClass('B', where =
where))

classA <- getClass('A', where = where)
classB <- getClass('B', where = where)
message("extends(classB, classA): ", methods::extends(classB, classA))
}

.onLoad <- function(libname, pkgname=NULL){
cat("\n## .onLoad ##\n")
check.classes(asNamespace(pkgname))
}

.onAttach <- function(libname, pkgname){
cat("\n## .onAttach ##\n")
check.classes(asNamespace(pkgname))
}




On 6/23/11 4:22 AM, Renaud Gaujoux wrote:

Hi,

I am facing with a strange behaviour of isClass and extends when these
are called in .onLoad in both R 2.12.1 and R 2.13.0. This is preventing
my package from doing some object initializations at a proper place
(i.e. in .onLoad).

Suppose one defines two S4 classes in a package, and that one needs to
check the inheritance between these two when loading the package (e.g.
t

Re: [Rd] Ref Classes: bug with using '.self' within initialize methods?

2011-07-02 Thread John Chambers
I don't have anything to suggest on your specific example but perhaps 
these two notes are relevant.


1. As is mentioned in the documentation, it's generally a bad idea to 
write S4 initialize() methods for reference classes, rather than 
reference class methods for $initialize():
  "a reference method is recommended rather than a method for the S4 
generic function initialize(), because some special initialization is 
required for reference objects _before_ the initialization of fields."




2. In a simple example, there is no problem using .self in a 
$initialize() method.


##
ss <- setRefClass("ss", fields = c("a", "b", "c"),
methods = list(
initialize = function(...) {
callSuper(...)
.self$b <- .self$a
},
check = function()
 .self$c <- .self$a
))

s1 <- ss$new(a=1)
s1$check()
stopifnot(identical(s1$a, 1), identical(s1$a, s1$b),
  identical(s1$a, s1$c))
###

On 6/29/11 9:36 AM, Janko Thyson wrote:

Dear list,

I'm wondering if the following error I'm getting is a small bug in the
Reference Class paradigm or if it makes perfect sense.

When you write an explicit initialize method for a Ref Class, can you
then make use of '.self' WITHIN this initialize method just as you would
once an object of the class has actually been initialized?
Because it seems to me that you can not.

Below is an example that shows that calling '.self$someInitFoo()' within
the initialize method for 'MyClass' does not work (see section "METHODS"
in example below). Instead I have to go with
'someInitFooRefInner(.self=.Object, ...)' (see section "UPDATED METHOD"
in example below). Yet, this is only possible because there actually IS
such a method (I try to stick to the recommendations at ?setRefClass
where it says: "Reference methods should be kept simple; if they need to
do some specialized *R* computation, that computation should use a
separate *R* function that is called from the reference method")

The same problem occurs when, say 'someInitFoo()' calls yet another Ref
Class method (as is the case in the example below with a call to
'.self$someFoo()').

Is this a desired behavior?

Thanks for any clarifying comments!
Janko

# CODE EXAMPLE #

# CLASSES
setRefClass(
  Class="MyVirtual",
  contains=c("VIRTUAL"),
  methods=list(
  initialize=function(...){
  callSuper(...)
  return(.self)
  },
  someInitFoo=function(flds, ...){
  someInitFooRefInner(
  .self=.self,
  flds=flds
  )
  }
  )
)
GENERATOR<- setRefClass(
  Class="MyClass",
  contains=c("MyVirtual"),
  fields=list(
  A="character",
  B="numeric"
  ),
  methods=list(
  someFoo=function(...){
  someFooRefInner(.self=.self, ...)
  }
  )
)
# /

# GENERICS
setGeneric(name="someInitFooRefInner",
  def=function(.self, ...) standardGeneric("someInitFooRefInner"),
  signature=c(".self")
)
setGeneric(name="someFooRefInner",
  def=function(.self, ...) standardGeneric("someFooRefInner"),
  signature=c(".self")
)
# /

# METHODS
setMethod(
  f="someInitFooRefInner",
  signature=signature(.self="MyVirtual"),
  definition=function(.self, flds, ...){
  print("Trying to call '.self$someFoo()")
  try(.self$someFoo())
  print("Trying to call 'someFooRefInner(.self=.self)")
  try(someFooRefInner(.self=.self))
  return(flds)
  }
)
setMethod(
  f="someFooRefInner",
  signature=signature(.self="MyVirtual"),
  definition=function(.self, ...){
  print("hello world!")
  }
)
setMethod(
  f="initialize",
  signature=signature(.Object="MyVirtual"),
  definition=function(.Object, GENERATOR=NULL, ...){
  # MESSAGE
  if(class(.Object) == "MyVirtual"){
  cat(paste("initializing object of class '", class(.Object),
"'",
  sep=""), sep="\n")
  } else {
  cat(paste("initializig object of class'", class(.Object),
  "' inheriting from class 'MyVirtual'", sep=""), sep="\n")
  }
  # /
  # GET GENERATOR OBJECT
  if(is.null(GENERATOR)){
  GENERATOR<- getRefClass(class(.Object))
  }
  flds<- names(GENERATOR$fields())
  .Object$someInitFoo(
  flds=flds,
  ...
  )
  return(.Object)
  }
)
# /

x<- GENERATOR$new()

# UPDATED METHOD
setMethod(
  f="initialize",
  signature=signature(.Object="MyVirtual"),
  definition=function(.Object, GENERATOR=NULL, ...){
  # MESSAGE
  if(class(.Object) == "MyVirtual"){
  cat(paste("initializing object of class '", class(.Object),
"'",
  sep=""), sep="\n")
  } else {
  cat(paste("initializig object of class'", class(.Object),
 

[Rd] Same class name, different package

2011-07-21 Thread John Chambers
In principle, two separately developed packages could use the same class 
name, and a user could then attach both and attempt to use methods for 
both classes.


That has never worked, but some changes have been added to r-devel to 
handle this case.  The changes involve extending the "signature" class 
to include package information.  For compatibility, packages will need 
to be re-installed from a version of R labelled 56466 or later, although 
an attempt is made to fill in missing information.


John

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


Re: [Rd] Same class name, different package

2011-07-24 Thread John Chambers
A point that has come up a couple of times with the new test is that two 
classes from two packages may be "the same class".  Should that turn on 
duplicate classes?


One situation where the answer seems to be No is when the two classes 
are identical declarations of S3 classes, via setOldClass().


A recent update (rev. 56492) tries to check for equivalent classes, with 
some special leeway for that case, and does not turn on the  duplicate 
class flag.  It's not clear what is really needed or wanted in all 
circumstances, so further experience will be helpful.


If duplicate classes do exist, a utility findDuplicateClasses(details = 
FALSE) will give the names of the duplicated classes.  It's not yet 
exported so you need to call methods:::findDuplicateClasses()


John


On 7/21/11 10:29 AM, John Chambers wrote:

In principle, two separately developed packages could use the same
class name, and a user could then attach both and attempt to use
methods for both classes.

That has never worked, but some changes have been added to r-devel to
handle this case.  The changes involve extending the "signature" class
to include package information.  For compatibility, packages will need
to be re-installed from a version of R labelled 56466 or later,
although an attempt is made to fill in missing information.

John

__
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] Same class name, different package

2011-07-25 Thread John Chambers

On 7/25/11 12:07 AM, Martin Maechler wrote:

John Chambers
 on Sun, 24 Jul 2011 14:58:23 -0700 writes:


 >  A point that has come up a couple of times with the new
 >  test is that two classes from two packages may be "the
 >  same class".  Should that turn on duplicate classes?

 >  One situation where the answer seems to be No is when the
 >  two classes are identical declarations of S3 classes, via
 >  setOldClass().

 >  A recent update (rev. 56492) tries to check for equivalent
 >  classes, with some special leeway for that case, and does
 >  not turn on the duplicate class flag.  It's not clear what
 >  is really needed or wanted in all circumstances, so
 >  further experience will be helpful.

 >  If duplicate classes do exist, a utility
 >  findDuplicateClasses(details = FALSE) will give the names
 >  of the duplicated classes.  It's not yet exported so you
 >  need to call methods:::findDuplicateClasses()

 >  John

I haven't yet looked into the many situations that are "out
there" for CRAN and Bioconductor packages and am just speaking
from my own S4-using perspective:

I think

   ImportClassesFrom(...)

should be much more widely used, in order to diminish such class
"conflicts".
Wherever the new code produces warnings (does it?) about
duplicate class names, it would be good to "advertize" the
ImportClassesFrom()   clause for those cases where the two
class definitions look to be identical.


No argument there.

But I think the situation is different for setOldClass() and for "real" 
S4 classes, with a warning more suitable in the second case.


With S3 classes, the scenario that will happen fairly often is:  Package 
A has an S3 class "foo"; Packages B and C both (independently) want to 
use/extend that class in S4 code.  Both will include setOldClass("foo") 
calls.


The problem here is that the two generated classes for "foo" will belong 
to packages B and C (there being no way in general to find where S3 
class "foo" is defined--indeed in a sense it's not defined at all).


Various approaches are possible, varying in ugliness.  One might be to 
associate all these converted S3 classes with a special pseudo-package. 
 Another, which I don't much like, is to ask the setOldClass() call to 
specify which package the S3 class comes from, and hope that all the 
packages in the above scenario make the same choice.


The short term approach will probably be to allow multiple identical 
setOldClass() effects without warning.  (The actual code as of today 
generates warning messages on all identical classes only if 
options(warn=1) has been set.)


John



Martin


 >  On 7/21/11 10:29 AM, John Chambers wrote:
 >>  In principle, two separately developed packages could use
 >>  the same class name, and a user could then attach both
 >>  and attempt to use methods for both classes.
 >>
 >>  That has never worked, but some changes have been added
 >>  to r-devel to handle this case.  The changes involve
 >>  extending the "signature" class to include package
 >>  information.  For compatibility, packages will need to be
 >>  re-installed from a version of R labelled 56466 or later,
 >>  although an attempt is made to fill in missing
 >>  information.
 >>
 >>  John

__
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


[Rd] Reference classes: assignments to fields

2011-07-31 Thread John Chambers
In R-devel, a recent change (Rev. 56572) makes assignments to fields in 
reference classes consistent with assignments to slots in S4 classes, 
when the field was declared with a class in the call to setRefClass().


The value assigned must come from the declared class for the field, if 
any, or from a subclass of that class.  Previously, if the field had a 
declared class the value for assignment was unconditionally coerced to 
that class.


The added test may produce new error messages, e.g., if you declare a 
field "integer" and assign a numeric, such as 1 rather than 1L.


John

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


Re: [Rd] initFields() method no longer coerces arguments in R-devel

2011-08-05 Thread John Chambers

There is also an item in the NEWS file:

Field assignments in reference classes are now consistent with 
slots in S4 classes: the assigned value must come from the declared 
class (if any) for the field or from a subclass.


On 8/5/11 7:24 AM, Simon Urbanek wrote:

It's worth actually reading the list you post to ...
http://r.789695.n4.nabble.com/Reference-classes-assignments-to-fields-td3708168.html


On Aug 5, 2011, at 6:41 AM, Jon Clayden wrote:


Dear all,

I've just had a package update bounced from CRAN because of a recent
change in R-devel which seems to affect the behaviour of the
initFields() reference class method. (The change must be very recent
because I tested the package on a week-old build of R-devel.) It seems
that the method no longer coerces its arguments to the expected type
of each field. For a simple example:


Foo<- setRefClass("Foo", fields=list(number="integer"), 
methods=list(initialize=function (number = NULL) initFields(number=number)))
Foo$new()

Error in function (value)  :
  invalid replacement for field ‘number’, should be from class
“integer” or a subclass (was class “NULL”)

(This used to work, with "number" being set to "integer(0)"). In fact
it is now extremely strict, not even allowing a double literal which
is equal to an integer:


Foo$new(number=1)

Error in function (value)  :
  invalid replacement for field ‘number’, should be from class
“integer” or a subclass (was class “numeric”)

I don't see anything about this in the NEWS, so I was wondering if I
could get clarification on whether this is now the intended behaviour,
before I further modify the package. I must say that this will be a
bit of a pain to "correct"...

All the best,
Jon

__
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



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


Re: [Rd] S4 method dispatch

2011-09-18 Thread John Chambers
The distinction here is "simple inheritance"  ("Software for Data 
Analysis", p. 346).  Your first example is simple inheritance (would be 
clearer if you used the contains= argument).  In the second version you 
supply an explicit coerce method, so method dispatch can no longer just 
pass in the object from the subclass, but has to call the coerce method 
explicitly.  Details in the reference.


If you need to have an explicit coerce method, it's possible to emulate 
simple inheritance, but the programming may be more subtle than you want 
to take on.  When your method is called, it actually gets also an 
argument strict= which will be FALSE for method dispatch. You need to 
take account of the strict= argument in writing your method.  See ?setAs 
for a few more details.  Someone on the list may have an example.


John

On 9/18/11 3:33 AM, Edzer Pebesma wrote:

As a follow-up, I managed to isolate the problem I sent earlier this
week, and reduced it to a small case (I'm using R 2.13.1,
i486-pc-linux-gnu (32-bit)).

The following script does what I expect:


setClass("A", representation(x = "numeric"))
setClass("AB", representation("A"))

setGeneric("doNothing<-", function(obj, value)
   standardGeneric("doNothing<-"))

setReplaceMethod("doNothing", c("A", "character"),
   function(obj, value) obj)

x = new("AB", x = 10)
doNothing(x) = "irrelevant"
class(x)

setAs("AB", "A", function(from) new("A", x = from@x))
x = new("AB", x = 10)
doNothing(x) = "irrelevant"
class(x)


and results in class(x) being "AB".
However, the following, very similar script:


setClass("A", representation(x = "numeric"))
setClass("AB", representation("A"))

setGeneric("doNothing<-", function(obj, value)
   standardGeneric("doNothing<-"))

setReplaceMethod("doNothing", c("A", "character"),
   function(obj, value) obj)

setAs("AB", "A", function(from) new("A", x = from@x))

x = new("AB", x = 10)
doNothing(x) = "irrelevant"
class(x)


returns "A" as the class of x. Why is this the case? Is this behaviour
intentional?

Best regards,


On 09/14/2011 11:00 PM, Edzer Pebesma wrote:

List,

In order to get rid of some old, unreadable S3 code in package sp, I'm
trying to rewrite things using S4 methods. Somewhere I fail, and I
cannot sort out why. In order to isolate the problem, I created two
functions, doNothing<- and dosth, and both should do nothing. The issue
is that in most cases they do nothing, but in some cases dosth(obj)
changes the class of obj and breaks with the error. I couldn't find a
pattern when this happens, but have a few cases where it consistently
breaks. Here's the code snippet:

setGeneric("doNothing<-", function(object, value)
 standardGeneric("doNothing<-"))

setReplaceMethod("doNothing",
 signature(object = "Spatial", value = "ANY"),
 function(object, value) object)

dosth = function(obj) {
 cl1 = class(obj)
 doNothing(obj) = TRUE
 cl2 = class(obj)
 if (!identical(cl1, cl2)) {
 print(paste(cl1, cl2))
 stopifnot(identical(cl1, cl2))
 }
 obj
}

When things go wrong, dosth and doNothing are called with a subclass of
Spatial, e.g. an object of class SpatialGrid, but when this gets in
doNothing, the object is suddenly of class Spatial, and is then returned
as an object of class Spatial, which should never happen.

For instance, I have a case where consistently

setMethod("fullgrid", c("Spatial"),
 function(obj) { is(obj, "SpatialGrid") })

class(g)

[1] "SpatialGrid"
attr(,"package")
[1] "sp"

fullgrid(g)

[1] FALSE

is obviously false, but in other cases it works fine.

When I change the signature of doNothing to signature(object = "ANY",
value = "ANY"), the problem disappears.

I tried to make a self-contained example that reproduced the issue, but
could only get something that worked as expected.

I would appreciate any help or suggestions.




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


Re: [Rd] S4 method dispatch

2011-09-30 Thread John Chambers



On 9/30/11 12:48 AM, Edzer Pebesma wrote:

Thanks, John!

I did not manage to figure out how the strict= works, but changed class
inheritance such that simple inheritance did not take place.

I see you're advocating to use the contains= to stress inheritance; back
in 2005, I followed the green book, which did not yet have this.

If I now would change class definitions from using the representation=
into contains= to express inheritance, does the binary representation
also change, i.e. do people relying on sp classes get into problem with
old, saved objects read by the new software? I'm asking this because
there's lots of it around, e.g. all the world administrative regions
available as .RData files from http://gadm.org/


It's just a question of readability: Better to have a clear statement of 
inheritance rather than plowing through the representation list for 
empty name fields.  And easier to discuss (e.g., section 9.3 of SoDA).


You're hardly the only sinner in the flock.  I imagine many packages on 
CRAN would have failed by now if there was a problem.  I only complain 
about it when feeling fussy.


John
.


On 09/18/2011 11:04 PM, John Chambers wrote:

The distinction here is "simple inheritance" ("Software for Data
Analysis", p. 346). Your first example is simple inheritance (would be
clearer if you used the contains= argument). In the second version you
supply an explicit coerce method, so method dispatch can no longer just
pass in the object from the subclass, but has to call the coerce method
explicitly. Details in the reference.

If you need to have an explicit coerce method, it's possible to emulate
simple inheritance, but the programming may be more subtle than you want
to take on. When your method is called, it actually gets also an
argument strict= which will be FALSE for method dispatch. You need to
take account of the strict= argument in writing your method. See ?setAs
for a few more details. Someone on the list may have an example.

John

On 9/18/11 3:33 AM, Edzer Pebesma wrote:

As a follow-up, I managed to isolate the problem I sent earlier this
week, and reduced it to a small case (I'm using R 2.13.1,
i486-pc-linux-gnu (32-bit)).

The following script does what I expect:


setClass("A", representation(x = "numeric"))
setClass("AB", representation("A"))

setGeneric("doNothing<-", function(obj, value)
standardGeneric("doNothing<-"))

setReplaceMethod("doNothing", c("A", "character"),
function(obj, value) obj)

x = new("AB", x = 10)
doNothing(x) = "irrelevant"
class(x)

setAs("AB", "A", function(from) new("A", x = from@x))
x = new("AB", x = 10)
doNothing(x) = "irrelevant"
class(x)


and results in class(x) being "AB".
However, the following, very similar script:


setClass("A", representation(x = "numeric"))
setClass("AB", representation("A"))

setGeneric("doNothing<-", function(obj, value)
standardGeneric("doNothing<-"))

setReplaceMethod("doNothing", c("A", "character"),
function(obj, value) obj)

setAs("AB", "A", function(from) new("A", x = from@x))

x = new("AB", x = 10)
doNothing(x) = "irrelevant"
class(x)


returns "A" as the class of x. Why is this the case? Is this behaviour
intentional?

Best regards,


On 09/14/2011 11:00 PM, Edzer Pebesma wrote:

List,

In order to get rid of some old, unreadable S3 code in package sp, I'm
trying to rewrite things using S4 methods. Somewhere I fail, and I
cannot sort out why. In order to isolate the problem, I created two
functions, doNothing<- and dosth, and both should do nothing. The issue
is that in most cases they do nothing, but in some cases dosth(obj)
changes the class of obj and breaks with the error. I couldn't find a
pattern when this happens, but have a few cases where it consistently
breaks. Here's the code snippet:

setGeneric("doNothing<-", function(object, value)
standardGeneric("doNothing<-"))

setReplaceMethod("doNothing",
signature(object = "Spatial", value = "ANY"),
function(object, value) object)

dosth = function(obj) {
cl1 = class(obj)
doNothing(obj) = TRUE
cl2 = class(obj)
if (!identical(cl1, cl2)) {
print(paste(cl1, cl2))
stopifnot(identical(cl1, cl2))
}
obj
}

When things go wrong, dosth and doNothing are called with a subclass of
Spatial, e.g. an object of class SpatialGrid, but when this gets in
doNothing, the object is suddenly of class Spatial, and is then
returned
as an object of class Spatial, which should never happen.

For instance, I have a case where consistently

setMethod("fullgrid", c("Spatial"),
function(obj) { is(obj, &quo

Re: [Rd] Plans to improve reference classes?

2015-06-23 Thread John Chambers
I understand Hadley's point; it's a consequence of the modification of the 
environment of the ref. class methods.

Good point, but it seems we can make that an option (there are advantages to it 
of code quality and ease of writing, when it works);

Let's discuss possibilities, off-list until things are a bit clearer.

John

On Jun 23, 2015, at 8:06 AM, Hadley Wickham  wrote:

>> 1) Is there any example or writeup on the difficulties of extending
>> reference classes across packages? Just so I can fully understand the
>> issues.
> 
> Here's a simple example:
> 
> library(scales)
> library(methods)
> 
> MyRange <- setRefClass("MyRange", contains = "DiscreteRange")
> a_range <- MyRange()
> a_range$train(1:10)
> # Error in a_range$train(1:10) : could not find function "train_discrete"
> 
> where train_discrete() is an non-exported function of the scales
> package called by the train() method of DiscreteRange.
> 
> There are also some notes about portable vs. non-portable R6 classes
> at http://cran.r-project.org/web/packages/R6/vignettes/Portable.html
> 
>> 2) In what sorts of situations does the performance of reference
>> classes cause problems? Sure, it's an order of magnitude slower than
>> constructing a simple environment, but those timings are in
>> microseconds, so one would need a thousand objects before it started
>> to be noticeable. Some motivating use cases would help.
> 
> It's a bit of a pathological case, but the switch from RefClasses to
> R6 made a noticeable performance improvement in shiny. It's hard to
> quantify the impact on an app, but the impact on the underlying
> reactive implementation was quite profound: http://rpubs.com/wch/27260
> vs  http://rpubs.com/wch/27264
> 
> R6 also includes a vignette with detailed benchmarking:
> http://cran.r-project.org/web/packages/R6/vignettes/Performance.html
> 
> I've added Winston to the thread since he's the expert.
> 
> Hadley
> 
> -- 
> http://had.co.nz/
> 
> __
> 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] For integer vectors, `as(x, "numeric")` has no effect.

2015-12-07 Thread John Chambers
We do need an explicit method here, I think.

The issue is that as() uses methods for the generic function coerce() but 
cannot use inheritance in the usual way (if it did, you would be immediately 
back with no change, since "integer" inherits from "numeric").

Copying in the general method for coercing to "numeric" as an explicit method 
for "integer" gives the expected result:

> setMethod("coerce", c("integer", "numeric"), getMethod("coerce", c("ANY", 
> "numeric")))
[1] "coerce"
> typeof(as(1L, "numeric"))
[1] "double"

Seems like a reasonable addition to the code, unless someone sees a problem.

John


On Dec 7, 2015, at 3:37 PM, Benjamin Tyner  wrote:

> Perhaps it is not that surprising, given that
> 
>> mode(1L)
>[1] "numeric"
> 
> and
> 
>> is.numeric(1L)
>[1] TRUE
> 
> On the other hand, this is curious, to say the least:
> 
>> is.double(as(1L, "double"))
>[1] FALSE
> 
>> Here's the surprising behavior:
>> 
>>x <- 1L
>>xx <- as(x, "numeric")
>>class(xx)
>>## [1] "integer"
>> 
>> It occurs because the call to `as(x, "numeric")` dispatches the coerce
>> S4 method for the signature `c("integer", "numeric")`, whose body is
>> copied in below.
>> 
>> function (from, to = "numeric", strict = TRUE)
>> if (strict) {
>> class(from) <- "numeric"
>> from
>> } else from
>> 
>> This in turn does nothing, even when strict=TRUE, because that
>> assignment to class "numeric" has no effect:
>> 
>> x <- 10L
>> class(x) <- "numeric"
>> class(x)
>> [1] "integer"
>> 
>> Is this the desired behavior for `as(x, "numeric")`?
> 
> __
> 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] For integer vectors, `as(x, "numeric")` has no effect.

2015-12-11 Thread John Chambers
Somehow, the most obvious fixes are always back-incompatible these days.

The example intrigued me, so I looked into it a bit (should have been doing 
something else, but )

You're right that this is the proverbial thin-edge-of-the-wedge.

The problem is in setDataPart(), which will be called whenever a class extends 
one of the vector types.

It does
as(value, dataClass)
The key point is that the third argument to as(), strict=TRUE by default.  So, 
yes, the change will cause all integer vectors to become double when the class 
extends "numeric".  Generally, strict=TRUE makes sense here and of course 
changing THAT would open up yet more incompatibilities.

For back compatibility, one would have to have some special code in 
setDataPart() for the case of integer/numeric.

John

(Historically, the original sin was probably not making a distinction between 
"numeric" as a virtual class and "double" as a type/class.)


On Dec 11, 2015, at 1:25 AM, Martin Maechler  wrote:

>>>>>> Martin Maechler 
>>>>>>on Tue, 8 Dec 2015 15:25:21 +0100 writes:
> 
>>>>>> John Chambers 
>>>>>>on Mon, 7 Dec 2015 16:05:59 -0800 writes:
> 
>>> We do need an explicit method here, I think.
>>> The issue is that as() uses methods for the generic function coerce() but 
>>> cannot use inheritance in the usual way (if it did, you would be 
>>> immediately back with no change, since "integer" inherits from "numeric").
> 
>>> Copying in the general method for coercing to "numeric" as an explicit 
>>> method for "integer" gives the expected result:
> 
>>>> setMethod("coerce", c("integer", "numeric"), getMethod("coerce", c("ANY", 
>>>> "numeric")))
>>> [1] "coerce"
>>>> typeof(as(1L, "numeric"))
>>> [1] "double"
> 
>>> Seems like a reasonable addition to the code, unless someone sees a problem.
>>> John
> 
>> I guess that that some package checks (in CRAN + Bioc + ... -
>> land) will break,
>> but I still think we should add such a coercion to R.
> 
>> Martin
> 
> Hmm...  I've tried to add the above to R
> and do notice that there are consequences that may be larger than
> anticipated:
> 
> Here is example code:
> 
>   myN   <- setClass("myN",   contains="numeric")
>   myNid <- setClass("myNid", contains="numeric", 
> representation(id="character"))
>   NN <-setClass("NN", representation(x="numeric"))
> 
>   (m1 <- myN  (1:3))
>   (m2 <- myNid(1:3, id = "i3"))
>   tools::assertError(NN (1:3))# in all R versions
> 
>   ## # current R  |  new R
>   ## # ---|--
>   class(getDataPart(m1)) # integer|  numeric
>   class(getDataPart(m2)) # integer|  numeric
> 
> 
> In other words, with the above setting, the traditional
> gentleperson's agreement in S and R,
> 
>  __ "numeric" sometimes conveniently means "integer" or "double"  __
> 
> will be slightly less often used ... which of course may be a
> very good thing.
> 
> However, it breaks strict back compatibility also in cases where
> the previous behavior may have been preferable:
> After all integer vectors need only have the space of doubles.
> 
> Shall we still go ahead and do apply this change to R-devel
> and then all package others will be willing to update where necessary?
> 
> As this may affect the many hundreds of bioconductor packages
> using S4 classes, I am -- exceptionally -- cross posting to the
> bioc-devel list.
> 
> Martin Maechler
> 
> 
>>> On Dec 7, 2015, at 3:37 PM, Benjamin Tyner  wrote:
> 
>>>> Perhaps it is not that surprising, given that
>>>> 
>>>>> mode(1L)
>>>> [1] "numeric"
>>>> 
>>>> and
>>>> 
>>>>> is.numeric(1L)
>>>> [1] TRUE
>>>> 
>>>> On the other hand, this is curious, to say the least:
>>>> 
>>>>> is.double(as(1L, "double"))
>>>> [1] FALSE
>>>> 
>>>>> Here's the surprising behavior:
>>>>> 
>>>>> x <- 1L
>>>>> xx <- as(x, "numeric")
>>>>> class(xx)
>>>>> ## [1] "integer"
>>>>> 
>>>>> It occurs becaus

Re: [Rd] For integer vectors, `as(x, "numeric")` has no effect.

2015-12-19 Thread John Chambers
As I tried to say on Dec. 11, there are two levels of "fix":

1.  The fix to the complaint in the OP's subject heading is to conform to the 
default third argument, strict=TRUE: as(1L, "numeric") == 1.0

This generates some incompatibilities, as for classes that extend "numeric". 
But still leaves class(1.0) "numeric" and typeof(1.0) "double".

The workaround for class definitions that really need NOT to coerce integers to 
double is to define a class union, say
  setClassUnion("Number", c("numeric", "integer"))
and use that for the slot.

2.  The "right" concept is arguably that "numeric" is a virtual class with two 
subclasses, "double" and "integer".  Given a time machine back to < 1998, that 
would be my choice.  But already in the 1998 S4 book, "numeric" was equated 
with "double".

so, there it is, IMO.  This is what you get with a successful open-source 
language:  Much hassle to do the "right thing" after the fact and the more 
change, the more hassle.

Fix 1. seems to me an actual bug fix, so my inclination would be to go with 
that (on r-devel), advertising that it may change the effective definition of 
some classes.

But I can sympathize with choosing 1, 2 or neither.

John

PS:  Until Jan. 4, I may be even poorer at replying than usual, while getting 
the current book off to the publisher.

On Dec 19, 2015, at 3:32 AM, Martin Maechler  wrote:

>>>>>> Martin Maechler 
>>>>>>on Sat, 12 Dec 2015 10:32:51 +0100 writes:
> 
>>>>>> John Chambers 
>>>>>>on Fri, 11 Dec 2015 10:11:05 -0800 writes:
> 
>>> Somehow, the most obvious fixes are always back-incompatible these days.
>>> The example intrigued me, so I looked into it a bit (should have been doing 
>>> something else, but )
> 
>>> You're right that this is the proverbial thin-edge-of-the-wedge.
> 
>>> The problem is in setDataPart(), which will be called whenever a class 
>>> extends one of the vector types.
> 
>>> It does
>>> as(value, dataClass)
>>> The key point is that the third argument to as(), strict=TRUE by default.  
>>> So, yes, the change will cause all integer vectors to become double when 
>>> the class extends "numeric".  Generally, strict=TRUE makes sense here and 
>>> of course changing THAT would open up yet more incompatibilities.
> 
>>> For back compatibility, one would have to have some special code in 
>>> setDataPart() for the case of integer/numeric.
> 
>>> John
> 
>>> (Historically, the original sin was probably not making a distinction 
>>> between "numeric" as a virtual class and "double" as a type/class.)
> 
>> Yes, indeed.  In the mean time, I've seen more cases where
>> "the change will cause all integer vectors to become double when the class  
>> extends "numeric". 
>> seems detrimental.
> 
>> OTOH, I still think we could go in the right direction ---
>> hopefully along the wishes of bioconductor S4 development, see
>> Martin Morgan's e-mail:
> 
>> [This is all S4 - only; should not much affect base R / S3]
>> Currently,   "integer" is a subclass of "numeric"  and so the
>> "integer become double" part seems unwanted to me.
>> OTOH,  it would really make sense to more formally
>> have the basic subclasses of  "numeric" to be "integer" and "double",
>> and  to let  as(*, "double") to become different to as(*, "numeric")
>> [Again, this is just for the S4 classes and as() coercions, *not* e.g. 
>> for as.numeric() / as.double() !]
> 
>> In the DEPRECATED part of the NEWS for R 2.7.0 (April 2008) we
>> have had
> 
>> oThe S4 pseudo-classes "single" and double have been removed.
>> (The S4 class for a REALSXP is "numeric": for back-compatibility
>> as(x, "double") coerces to "numeric".)
> 
>> I think the removal of "single" was fine, but in hindsight,
>> maybe the removal of "double" -- which was partly broken then --
>> possibly could rather have been a fixup of "double" along the
>> following
> 
>> Current "thought experiment proposal" :
> 
>> 1) "numeric" := {"integer", "double"}   { class - subclasses }
>> 2) as(1L, "numeric")  continues to return 1L .. since integer is
>> one case of "numeric"
>> 3) as(1L, "double")  newly 

Re: [Rd] [Bioc-devel] For integer vectors, `as(x, "numeric")` has no effect.

2015-12-26 Thread John Chambers
Re: coerce() methods.

Important to realize that as() does not call selectMethod() in the standard 
way, but restricts inheritance to the first argument:
   asMethod <- selectMethod("coerce", sig, optional = TRUE, 
  c(from = TRUE, to = FALSE), fdef = coerceFun, 
A valid comparison would have to take account of this.

Once the method has been _correctly_ selected, it is stored in the internal 
table and therefore  will be returned by .findMethodInTable without repeating a 
search.

John

On Dec 25, 2015, at 11:51 PM, Herv� Pag�s  wrote:

> Or maybe the "right" concept is that "numeric" is a virtual class
> with 3 subclasses: "complex", "double", and "integer". Anyway it's
> probably too late for implementing the "right" concept so it doesn't
> really matter.
> 
> Thanks Martin for offering to fix the as(1L, "numeric") bug. Very
> much appreciated. I guess that means fixing the class(x) <- "numeric"
> bug on integer vectors:
> 
>  > x <- 1L
>  > class(x) <- "numeric"
>  > class(x)
>  [1] "integer"
> 
> My wish for 2016: that selectMethod() always tells the truth. For
> example selectMethod("coerce", c("integer", "numeric")) doesn't
> in a fresh session, only after you call as(1L, "numeric")). Full
> story here:
> 
>  https://stat.ethz.ch/pipermail/r-devel/2010-April/057098.html
> 
> Thanks,
> H.
> 
> 
> On 12/19/2015 10:09 AM, John Chambers wrote:
>> As I tried to say on Dec. 11, there are two levels of "fix":
>> 
>> 1.  The fix to the complaint in the OP's subject heading is to conform to 
>> the default third argument, strict=TRUE: as(1L, "numeric") == 1.0
>> 
>> This generates some incompatibilities, as for classes that extend "numeric". 
>> But still leaves class(1.0) "numeric" and typeof(1.0) "double".
>> 
>> The workaround for class definitions that really need NOT to coerce integers 
>> to double is to define a class union, say
>>   setClassUnion("Number", c("numeric", "integer"))
>> and use that for the slot.
>> 
>> 2.  The "right" concept is arguably that "numeric" is a virtual class with 
>> two subclasses, "double" and "integer".  Given a time machine back to < 
>> 1998, that would be my choice.  But already in the 1998 S4 book, "numeric" 
>> was equated with "double".
>> 
>> so, there it is, IMO.  This is what you get with a successful open-source 
>> language:  Much hassle to do the "right thing" after the fact and the more 
>> change, the more hassle.
>> 
>> Fix 1. seems to me an actual bug fix, so my inclination would be to go with 
>> that (on r-devel), advertising that it may change the effective definition 
>> of some classes.
>> 
>> But I can sympathize with choosing 1, 2 or neither.
>> 
>> John
>> 
>> PS:  Until Jan. 4, I may be even poorer at replying than usual, while 
>> getting the current book off to the publisher.
>> 
>> On Dec 19, 2015, at 3:32 AM, Martin Maechler  
>> wrote:
>> 
>>>>>>>> Martin Maechler 
>>>>>>>>on Sat, 12 Dec 2015 10:32:51 +0100 writes:
>>> 
>>>>>>>> John Chambers 
>>>>>>>>on Fri, 11 Dec 2015 10:11:05 -0800 writes:
>>> 
>>>>> Somehow, the most obvious fixes are always back-incompatible these days.
>>>>> The example intrigued me, so I looked into it a bit (should have been 
>>>>> doing something else, but )
>>> 
>>>>> You're right that this is the proverbial thin-edge-of-the-wedge.
>>> 
>>>>> The problem is in setDataPart(), which will be called whenever a class 
>>>>> extends one of the vector types.
>>> 
>>>>> It does
>>>>> as(value, dataClass)
>>>>> The key point is that the third argument to as(), strict=TRUE by default. 
>>>>>  So, yes, the change will cause all integer vectors to become double when 
>>>>> the class extends "numeric".  Generally, strict=TRUE makes sense here and 
>>>>> of course changing THAT would open up yet more incompatibilities.
>>> 
>>>>> For back compatibility, one would have to have some special code in 
>>>>> setDataPart() for the case of integer/numeric.
>>> 
>>>>&

Re: [Rd] Source code of early S versions

2016-02-29 Thread John Chambers
The Wikipedia statement may be a bit misleading.

S was never open source.  Source versions would only have been available with a 
nondisclosure agreement, and relatively few copies would have been distributed 
in source.  There was a small but valuable "beta test" network, mainly 
university statistics departments.

And two shameless plugs:

1.  there is a chapter on the history of all this in my forthcoming book on 
"Extending R"

2. Rick Becker will give a keynote talk on the history of S at the useR! 2016 
conference (user2016.org); 2016 is the 40th anniversary of the first work on S.

John

PS:  somehow "historical" would be less unnerving than "archeological"


On Feb 29, 2016, at 8:40 AM, Barry Rowlingson  
wrote:

> According to Wikipedia:
> 
> "In 1980 the first version of S was distributed outside Bell
> Laboratories and in 1981 source versions were made available."
> 
> but I've been unable to locate any version of S online. Does anyone
> have a copy, somewhere, rusting away on an old hard disk or slowly
> flaking off a tape? I've had a rummage round the CMU Statlib on
> archive.org but no sign of it, and its hard to search for "S"
> generally.
> 
> Obviously this would be for archaeological purposes, but there's
> bound to be someone out there who'd like to try and compile it on a
> modern system. It might at least be nice to see it in a nice format on
> Gitlab, for example. But maybe there's licensing problems.
> 
> Anyone interested in the history of S should read Richard Becker's
> article from the mid 90s:
> 
> http://sas.uwaterloo.ca/~rwoldfor/software/R-code/historyOfS.pdf
> 
> Barry
> 
> [apologies if S talk is off-topic. Surprisingly I've just discovered
> the S-news mailing list still runs, but looking at the recent archive
> I don't think I'd get much success there]
> 
> __
> 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] strange behavior in 'inherits' check for loaded S4 object

2016-07-31 Thread John Chambers
(Just returning from the "wilds" of Canada, so not able to comment on the 
specifics, but ...)

There is a basic point about generic functions that may be related to the 
"private" class question and my earlier remarks that Martin alluded to.

R (and S4 before it)  allows packages to define methods for a generic function 
in another package.  Say, for plot() in graphics.

The current model is that the generic plot() remains one function, specifically 
a generic associated with the graphics package.

Package A might define a method corresponding to one or two classes defined in 
that package.  When A is loaded, those methods are added to the table for 
plot() in the current session.

Now suppose a user calls a function, foo(), in package B, and that foo() in 
turn calls plot().  This is the same plot() function, and in particular will 
include the methods supplied from package A.

This is regardless of the two packages having any overt connection.  Also, the 
methods are accepted by the generic function regardless of whether the class is 
explicitly exported or not.  In this sense, classes cannot be entirely private 
if methods are defined for a non-local function.  Namespaces are not directly 
relevant.

Whether this can lead to strange behavior isn't clear, and if so, is it a sign 
that something undesirable was done in the particular example?  (In Extending 
R, I suggested a "right to write methods" that  would discourage a package from 
having methods unless it owned the function or some of the classes.)

R could adopt a different model for generic functions, where a package that 
defined a method for a non-exported class would create a "local" version of the 
generic, but that would likely raise some other issues.

But seems like a useful topic for discussion.

John

On Jul 30, 2016, at 11:07 AM, Martin Maechler  
wrote:

>>>>>> Kevin Ushey 
>>>>>>on Fri, 29 Jul 2016 11:46:19 -0700 writes:
> 
>> I should add one more item that may be related here --
>> calling 'methods:::.requirePackage' returns a different
>> result based on whether the package namespace is already
>> loaded or not.
> 
>> If the package namespace is not loaded, the package is
>> loaded and attached, and the package environment is
>> returned:
> 
>>> methods:::.requirePackage("digest")
>>Loading required package: digest > package:digest> attr(,"name") [1] "package:digest"
>> attr(,"path") [1]
>> "/Users/kevin/Library/R/3.3/library/digest"
>>> "digest" %in% loadedNamespaces()
>>[1] TRUE
>>> "package:digest" %in% search()
>>[1] TRUE
> 
>> On the other hand, if the package namespace has already
>> been loaded, the package namespace is returned without
>> attaching the package:
> 
>>> requireNamespace("digest")
>>Loading required namespace: digest
>>> methods:::.requirePackage("digest")
>>
>>> "digest" %in% loadedNamespaces()
>>[1] TRUE
>>> "package:digest" %in% search()
>>[1] FALSE
> 
>> This may be intentional, but the behavior seems surprising
>> and could be responsible for the behavior outlined
>> earlier.
> 
> Yes, the behavior you outlined earlier is buggy, and I also have
> seen similar bugous behavior for the case of non-exported
> classes.
> 
> Part of it is historical:  The S4 code was mostly written before
> namespaces were introduced into R;   I vaguely remember John
> Chambers (the principal creator of S4) saying that he did not
> intend the formal classes to be not visible... which in some
> sense only contains the fact that he (or anybody) would not
> think much about hidden objects before they were introduced.
> 
> Still, in the mean time, most of us have seen many cases where
> we wanted to have "private" classes,  and many packages do have
> them, too and they "mostly work" ;-)
> 
> In other words, I agree that it would be very desirable to get
> to the bottom of this and fix such problems.
> 
> .requirePackage() is among the parts of the methods package code
> which are quite delicate (and not much documented AFAIK, the hidden
> .requirePackage() function is a good example!).
> 
> Delicate for at least two reasons:
> 
> 1) They are not only used in crucial steps when "bootstrapping"
>   the methods package ('methods' has to define its own S4
>   generics, methods, and classes before the package "exists"),
> 
> 1b) they are also used both when building and installing another
>'methods'-dependent package.  This coul

Re: [Rd] strange behavior in 'inherits' check for loaded S4 object

2016-08-02 Thread John Chambers
Agreed that this looks like a real bug, and is independent of how one regards 
the more general issue about specifying methods for a public generic and a 
non-exported class.

John

On Aug 2, 2016, at 11:48 AM, Kevin Ushey  wrote:

> Hi Martin, John,
> 
> Thanks for the responses! I've tidied up some of the notes from this
> mailing list thread and posted them on the bug tracker.
> 
> John, in this case, I think namespaces are relevant because for
> non-exported S4 classes, the class information is made available
> through the '.__C__' symbol in the package's namespace, but
> not the package environment that gets attached to the search path. In
> this (rare, yet not impossible) sequence of events, it looks like R
> attempts to resolve the '.__C__' symbol in the wrong
> environment, and so class information lookup fails, and we end up
> caching the wrong inheritance information.
> 
> Thanks,
> Kevin
> 
> On Sun, Jul 31, 2016 at 5:12 AM, John Chambers  wrote:
>> (Just returning from the "wilds" of Canada, so not able to comment on the 
>> specifics, but ...)
>> 
>> There is a basic point about generic functions that may be related to the 
>> "private" class question and my earlier remarks that Martin alluded to.
>> 
>> R (and S4 before it)  allows packages to define methods for a generic 
>> function in another package.  Say, for plot() in graphics.
>> 
>> The current model is that the generic plot() remains one function, 
>> specifically a generic associated with the graphics package.
>> 
>> Package A might define a method corresponding to one or two classes defined 
>> in that package.  When A is loaded, those methods are added to the table for 
>> plot() in the current session.
>> 
>> Now suppose a user calls a function, foo(), in package B, and that foo() in 
>> turn calls plot().  This is the same plot() function, and in particular will 
>> include the methods supplied from package A.
>> 
>> This is regardless of the two packages having any overt connection.  Also, 
>> the methods are accepted by the generic function regardless of whether the 
>> class is explicitly exported or not.  In this sense, classes cannot be 
>> entirely private if methods are defined for a non-local function.  
>> Namespaces are not directly relevant.
>> 
>> Whether this can lead to strange behavior isn't clear, and if so, is it a 
>> sign that something undesirable was done in the particular example?  (In 
>> Extending R, I suggested a "right to write methods" that  would discourage a 
>> package from having methods unless it owned the function or some of the 
>> classes.)
>> 
>> R could adopt a different model for generic functions, where a package that 
>> defined a method for a non-exported class would create a "local" version of 
>> the generic, but that would likely raise some other issues.
>> 
>> But seems like a useful topic for discussion.
>> 
>> John
>> 
>> On Jul 30, 2016, at 11:07 AM, Martin Maechler  
>> wrote:
>> 
>>>>>>>> Kevin Ushey 
>>>>>>>>   on Fri, 29 Jul 2016 11:46:19 -0700 writes:
>>> 
>>>> I should add one more item that may be related here --
>>>> calling 'methods:::.requirePackage' returns a different
>>>> result based on whether the package namespace is already
>>>> loaded or not.
>>> 
>>>> If the package namespace is not loaded, the package is
>>>> loaded and attached, and the package environment is
>>>> returned:
>>> 
>>>>> methods:::.requirePackage("digest")
>>>>   Loading required package: digest >>> package:digest> attr(,"name") [1] "package:digest"
>>>> attr(,"path") [1]
>>>> "/Users/kevin/Library/R/3.3/library/digest"
>>>>> "digest" %in% loadedNamespaces()
>>>>   [1] TRUE
>>>>> "package:digest" %in% search()
>>>>   [1] TRUE
>>> 
>>>> On the other hand, if the package namespace has already
>>>> been loaded, the package namespace is returned without
>>>> attaching the package:
>>> 
>>>>> requireNamespace("digest")
>>>>   Loading required namespace: digest
>>>>> methods:::.requirePackage("digest")
>>>>   
>>>>> "digest" %in% loadedNamespaces()
>>>>   [1] TRUE
>>>>> "package:digest&qu

Re: [Rd] c(, ) / help(dotsMethods) etc

2016-09-10 Thread John Chambers
(Brief reply, I'm traveling but as per below, this is on my radar right now so 
wanted to comment.)

Two points regarding "dotsMethods".

1.  To clarify the limitation.  It's not that all the arguments have to be of 
the same class, but there must be one class that they belong to or subclass.  
(So, as in the example in the documentation, the method could be defined for a 
class union or other virtual class that all the actual arguments inherit from.)

2.  The current documentation is a mess.  In common with lots of other very old 
documentation.  I'm in the process of rewriting a large chunk of the 
documentation including that for dotsMethods.  Sometime in the next few weeks, 
I hope to have it coherent enough to commit.

So far, I'm not trying to change any significant aspects of the code, including 
for "..." methods, which seem to do roughly what was intended.

John


On Sep 10, 2016, at 8:27 AM, Martin Maechler  wrote:

> I have been asked  (by Roger; thank you for the good question,
>   and I hope it's fine to answer to the public) :
> 
>> with Pi a sparse matrix and x,y, and ones
>> compatible n-vectors — when I do:
> 
>>> c(t(x) %*% Pi %*% ones, t(ones) %*% Pi %*% y )
>> [[1]] 1 x 1 Matrix of class "dgeMatrix"
>> [,1] [1,]
>> 0.1338527
>> [[2]] 1 x 1 Matrix of class "dgeMatrix"
> [,1] [1,]
>> 0.7810341
> 
>> I get a list whereas if Pi is an ordinary matrix I get a
>> vector.  Is this intentional?
> 
> Well, no.  But it has been "unavoidable" in the sense that it had not
> been possible to provide S4 methods for '...' in the "remote"
> past, when  Matrix was created.
> 
> Later ... also quite a few years ago, John Chambers had added
> that possibility, with still some limitation (all '...' must be
> of the same class), and also plans to remove some of the
> limitations, see   ?dotsMethods  in R.
> 
> I honestly have forgotten the history of my trying to provide 'c'
> methods for our "Matrix" objects after the  'dotsMethods'
> possibility had emerged,  but I know I tried and had not seen a
> way to succeed "satisfactorily",
> but maybe I now think I maybe should try again.
> I currently think this needs changes to R before it can be done
> satisfactorily, and this is the main reason why this is a public
> answer to R-devel@..., but I'm happy if I'am wrong.
> 
> The real challenge here is that I think that if it  should "work",
> it should work so in all cases, e.g., also for
> 
>c(NA, 3:2, Matrix(2:1), matrix(10:11))
> 
> and that's not so easy, e.g., the following class and method
> definitions do *not* achieve the desired result:
> 
> ## "mMatrix" is already hidden in Matrix pkg:
> setClassUnion("mMatrix", members = c("matrix", "Matrix"))
> setClassUnion("numMatrixLike", members =
>c("logical", "integer","numeric", "mMatrix"))
> 
> c.Matrix <- function(...) unlist(lapply(list(...), as.vector))
> ## NB: Must use   signature  '(x, ..., recursive = FALSE)' :
> setMethod("c", "Matrix", function(x, ..., recursive) c.Matrix(x,
> ...))
> ## The above is not sufficient for
> ##c(NA, 3:2, , ) :
> setMethod("c", "numMatrixLike", function(x, ..., recursive)
>   c.Matrix(x, ...))
> 
> ## but the above does not really help:
> 
>> c(Diagonal(3), NA, Matrix(10:11))   ## works fine,
> [1]  1  0  0  0  1  0  0  0  1 NA 10 11
> 
>> c(NA, Diagonal(3)) ## R's lowlevel c() already decided to use list():
> [[1]]
> [1] NA
> 
> [[2]]
> [,1] [,2] [,3]
> [1,]1..
> [2,].1.
> [3,]..1
> 
>> 
> --
> 
> BTW, I (and the package users) suffer from exactly the same
> problem with the "MPFR" (multi precision numbers) provided by my
> package Rmpfr:
> 
>> require(Rmpfr)
>> c(mpfr(3,100), 1/mpfr(7, 80)) ## works fine
> 2 'mpfr' numbers of precision  80 .. 100  bits
> [1]3 0.14285714285714285714285708
> 
>> c(pi, 1/mpfr(7, 80)) ## "fails" even worse than in 'Matrix' case
> [[1]]
> [1] 3.141593
> 
> [[2]]
> 'mpfr1' 0.14285714285714285714285708
> 
>> 
> 
> 
> Yes, it would be very nice  if  c(.)  could be used to
> concatenate quite arbitrary  R objects into one long atomic
> vector, but I don't see how to achieve this easily.
> 
> The fact, that  c()  just builds a list of its arguments if it
> ("thinks" it) cannot dispatch to a method, is a good strategy,
> but I'd hope it should be possible to have c() try to do better
> (and hence work for this case, and
> without a noticable performance penalty.
> 
> Suggestions are very welcome.
> Martin
> 
> __
> 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] cache most-recent dispatch

2013-07-02 Thread John Chambers
It's hard to see how repeated dispatch on the same classes can be that 
slow, _if_ the function being called each time is itself doing some 
substantial work.


The first call (in a session) with a particular signature searches for 
inherited methods and stores the method found in a table.  The following 
calls with that signature should do a single lookup in a hash table. 
Caching the last signature is unlikely to be dramatically faster, but we 
can experiment and see.


What is substantially different is calling a generic function vs calling 
a primitive or internal.  If the local paste you constructed is the 
default, base::paste, that is a .Internal.


Not going through the R generic function several thousand times would 
make a difference.


It's a fundamental point about R that function calls do enough work that 
they add significant time to a "trivial" computation, such as a 
primitive call.  There are various efforts going on these days to 
provide more efficient alternatives.  They're all helpful; my personal 
favorite when the game is worth it is to consider doing key computations 
in a seriously faster language, like C++ via Rcpp.


John

On 7/1/13 10:04 PM, Valerie Obenchain wrote:

Hi,

S4 method dispatch can be very slow. Would it be reasonable to cache the
most
recent dispatch, anticipating the next invocation will be on the same
type? This
would be very helpful in loops.

   fun0 <- function(x)
   sapply(x, paste, collapse="+")
   fun1 <- function(x) {
   paste <- selectMethod(paste, class(x[[1]]))
   sapply(x, paste, collapse="+")
   }
   lst <- split(rep(LETTERS, 100), rep(1:1300, 2))

   library(microbenchmark)
   microbenchmark(fun0(lst), times=10)
   ## Unit: milliseconds
   ##   expr  min   lq   median  uq  max neval
   ##  fun0(lst) 4.153287 4.180659 4.513539 5.19261 5.28048110

   setGeneric("paste")
   microbenchmark(fun0(lst), fun1(lst), times=10)
   ## > microbenchmark(fun0(lst), fun1(lst), times=10)
   ## Unit: milliseconds
   ##   expr   min   lqmedianuq   max neval
   ##  fun0(lst) 21.093180 21.27616 21.453174 21.833686 24.75879110
   ##  fun1(lst)  4.517808  4.53067  4.582641  4.682235  5.12185610

Dispatch seems to be especially slow when packages are involved, e.g.,
with the Bioconductor IRanges package
(http://bioconductor.org/packages/release/bioc/html/IRanges.html)

   removeGeneric("paste")
   library(IRanges)
   showMethods(paste)
   ## Function: paste (package BiocGenerics)
   ## ...="ANY"
   ## ...="Rle"
   selectMethod(paste, "ANY")
   ## Method Definition (Class "derivedDefaultMethod"):
   ##
   ## function (..., sep = " ", collapse = NULL)
   ## .Internal(paste(list(...), sep, collapse))
   ## 
   ##
   ## Signatures:
   ## ...
   ## target  "ANY"
   ## defined "ANY"

   microbenchmark(fun0(lst), fun1(lst), times=10)
   ## Unit: milliseconds
   ##   exprmin lq median uqmax
neval
   ##  fun0(lst) 233.539585 234.592491 236.311209 237.268506 243.181123
10
   ##  fun1(lst)   4.564914   4.592996   4.642898   4.729009   5.492706
10

   sessionInfo()
   ## R version 3.0.0 Patched (2013-04-04 r62492)
   ## Platform: x86_64-unknown-linux-gnu (64-bit)
   ##
   ## locale:
   ##  [1] LC_CTYPE=en_US.UTF-8   LC_NUMERIC=C
   ##  [3] LC_TIME=en_US.UTF-8LC_COLLATE=en_US.UTF-8
   ##  [5] LC_MONETARY=en_US.UTF-8LC_MESSAGES=en_US.UTF-8
   ##  [7] LC_PAPER=C LC_NAME=C
   ##  [9] LC_ADDRESS=C   LC_TELEPHONE=C
   ## [11] LC_MEASUREMENT=en_US.UTF-8 LC_IDENTIFICATION=C
   ##
   ## attached base packages:
   ## [1] parallel  stats graphics  grDevices utils datasets
methods
   ## [8] base
   ##
   ## other attached packages:
   ## [1] IRanges_1.19.15  BiocGenerics_0.7.2   microbenchmark_1.3-0
   ##
   ## loaded via a namespace (and not attached):
   ## [1] stats4_3.0.0


Thanks,
Valerie

__
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] Multiple return values / bug in rpart?

2013-08-13 Thread John Chambers
And just in case anyone is curious about the history, return() with 
multiple arguments was legal in S2 but the syntax in the blue book had 
only return(expr), whether enforced or not in the code.


  John


On 8/13/13 11:42 AM, luke-tier...@uiowa.edu wrote:

Both codetools and the compiler should be checking for use of multiple
args in return -- I'll look into adding that.

Best,

luke

On Tue, 13 Aug 2013, Duncan Murdoch wrote:


On 13-08-13 8:59 AM, Prof Brian Ripley wrote:

On 13/08/2013 13:54, Terry Therneau wrote:

I don't remember what rpartpl once did myself; as you point out it is a
routine that is no longer used and should be removed.  I've cc'd Brian
since he maintains the rpart code.

Long ago return() with multiple arguments was a legal shorthand for
returning a list. This feature was depricated in Splus, I think even
before R rose to prominence.  I vaguely remember a time when it's usage
generated a warning.


Yes, usage generated a warning then an error, but not parsing.

  > foo <- function() return(a=1, b=2)
  > foo()
Error in return(a = 1, b = 2) : multi-argument returns are not permitted


The fact that I've never noticed this unused routine is somewhat
embarrassing.  Perhaps I need a "not documented, never called" addition
to R CMD check to help me along.


But you cannot know 'never called'.  This is callable by
rpart:::rpartpl() : it is also possible that functions in your namespace
are called via eval()ing expressions at R or C level.  (There are
examples around for which that is the only usage.)


An approximation to "never called" is to run Rprof on your test code,
and see which functions are not mentioned.  I have a package under
construction with some students that can use this approach to identify
which lines are never seen while profiling the test code.

Duncan Murdoch

__
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] check warning with .onLoad() and setClass()

2013-10-03 Thread John Chambers
Don't use .onLoad() to set class (or other nontrivial) information at load 
time.  Use setLoadActions(), which was created exactly to get around the 
limitations of .onLoad().

For an example, see the Rcpp package, which uses this to set up load-time C++ 
linkages.

John Chambers

On Oct 3, 2013, at 3:22 AM, Rainer M Krug  wrote:

> Hi
> 
> I am writing a package in which I define a new class in the .onLoad()
> hook:
> 
> ,
> | .onLoad <- function(libname, pkgname) {
> | setClass(
> | "inDrak",
> | representation(
> | init = "SpatialGridDataFrame"
> | ),
> | contains = "simObj"
> | )
> | }
> `
> 
> The class "simObj" is defined in the package, which is in the depends
> section in the DESCRIPTION file:
> 
> ,
> | Package: InDrak
> | Type: Package
> | Title: Alien spread management simulation model for the Drakensberg
> | Version: 0.1-0
> | Date: 2013-10-03_11-55
> | Author: Rainer M. Krug
> | Maintainer: Rainer M Krug 
> | Description: Simulate the spread of three Invasive Alien Plants under 
> different
> | management and budget scenarios
> | License: GPL-3
> | LazyLoad: yes
> | Depends:
> | RSQLite,
> | simecol
> | Imports:
> | methods,
> | sp,
> | spgrass6,
> | DBI,
> | logger,
> | fireSim,
> | seedProd,
> | seedGerm,
> | seedDisp
> | LinkingTo: Rcpp
> | Collate:
> | 'beginYear.R'
> | 'clearAliens.R'
> | 'competition.R'
> | 'cumulativeDc.R'
> | 'dcToIndLayer.R'
> | 'dispProb2D.R'
> | 'endYear.R'
> | 'fireAliens.R'
> | 'germEst.R'
> | 'initfunc.R'
> | 'layerIO.R'
> | 'layerNames.R'
> | 'main.R'
> | 'newInDrak.R'
> | 'onLoad.R'
> | 'package.R'
> | 'parameter.R'
> | 'parmsAcacia.R'
> | 'parmsBudget.R'
> | 'parmsFire.R'
> | 'parmsPinus.R'
> | 'parmsRubus.R'
> | 'resetOptions.R'
> | 'seedDispersal.R'
> | 'seedProduction.R'
> | 'stats.R'
> `
> 
> If important, the NAMESPACE file is here:
> 
> ,
> | export(depRateName)
> | export(exportRaster)
> | export(fireLayerName)
> | export(ignitionRiskName)
> | export(importAliens)
> | export(importClearingHistory)
> | export(importFireHistory)
> | export(importIgnitionRisk)
> | export(importSpecies)
> | export(importVegetation)
> | export(layerExists)
> | export(layerName)
> | export(newInDrak)
> | export(parameter)
> | export(parmsAcacia)
> | export(parmsBudget)
> | export(parmsFire)
> | export(parmsPinus)
> | export(parmsRubus)
> | export(resetOptions)
> | export(statDistName)
> | export(suitName)
> | import(DBI)
> | import(fireSim)
> | import(logger)
> | import(methods)
> | import(seedDisp)
> | import(seedGerm)
> | import(seedProd)
> | import(sp)
> | import(spgrass6)
> `
> 
> The package builds fine, it installs without problems and works as
> expected, but when checking it, I get the following error:
> 
> ,
> | $ R CMD check ./InDrak_0.1-0.tar.gz 
> | * using log directory 
> ‘/Users/rainerkrug/Documents/Projects/R-Packages/inDrak/InDrak.Rcheck’
> | * using R version 3.0.1 (2013-05-16)
> | * using platform: x86_64-apple-darwin10.8.0 (64-bit)
> | * using session charset: UTF-8
> | * checking for file ‘InDrak/DESCRIPTION’ ... OK
> | * checking extension type ... Package
> | * this is package ‘InDrak’ version ‘0.1-0’
> | * checking package namespace information ... OK
> | * checking package dependencies ... OK
> | * checking if this is a source package ... OK
> | * checking if there is a namespace ... OK
> | * checking for executable files ... OK
> | * checking for hidden files and directories ... OK
> | * checking for portable file names ... OK
> | * checking for sufficient/correct file permissions ... OK
> | * checking whether package ‘InDrak’ can be installed ... OK
> | * checking installed package size ... OK
> | * checking package directory ... OK
> | * checking DESCRIPTION meta-information ... OK
> | * checking top-level files ... OK
> | * checking for left-over files ... OK
> | * checking index information ... OK
> | * checking package subdirectories ... OK
> | * checking R files for non-ASCII characters ... OK
> | * checking R files for syntax errors ... OK
> | * checking whether the package can be

Re: [Rd] check warning with .onLoad() and setClass()

2013-10-04 Thread John Chambers
The basic tool is setLoadActions(), which takes a function definition, with the 
package's namespace as its argument.  Read ?setLoadActions

There is no such thing as setLoadFunction, as far as the standard code in R.

While you haven't defined "didn't work", an off-the-top-of-the-head idea would 
be something like:

   setLoadActions(function(ns) {setClass(., where = ns)})


On Oct 4, 2013, at 7:07 AM, Rainer M Krug  wrote:

> Dirk Eddelbuettel  writes:
> 
>> On 4 October 2013 at 14:15, Rainer M Krug wrote:
>> | Hm. loadModule is Rcpp function, but I am only interested in using the
>> | setClass() function, which has nothing to do with Rcpp. I don't even use
>> | Rcpp in the package, only in one which is imported.
>> 
>> Sorry, assumed Reference Class created via Modules. My bad, and never mind.
>> 
>> But as John said, .onLoad() can be replaces since he made those changes in R
>> (and also in Rcpp). See ?setLoadAction, evalOnLoad(), ...
> 
> Ok - theat far I folow you. But how do I implement this?
> 
> I have now the following .onLoad() function:
> 
> ,
> | .onLoad <- function(libname, pkgname) {
> | setClass(
> | "inDrak",
> | representation(
> | init = "SpatialGridDataFrame"
> | ),
> | contains = "simObj"
> | )
> | }
> `
> 
> in the file ./R/onLoad.R in my package.
> 
> Now how can I now use the setLoadFunction()? I tried to simply put the
> setClass in the setLoadFunction() as follow into the ./R/onLoad.R file:
> 
> ,
> | setLoadFunction( function(libname, pkgname) {
> | setClass(
> | "inDrak",
> | representation(
> | init = "SpatialGridDataFrame"
> | ),
> | contains = "simObj"
> | )
> | }
> `
> 
> but this did not work. 
> 
> So what do I have to do with it? I only find very few examples using
> setLoadFunction().
> 
> Rainer
> 
> 
>> 
>> Dirk
> 
> 
> -- 
> Rainer M. Krug, PhD (Conservation Ecology, SUN), MSc (Conservation Biology, 
> UCT), Dipl. Phys. (Germany)
> 
> Centre of Excellence for Invasion Biology
> Stellenbosch University
> South Africa
> 
> Tel :   +33 - (0)9 53 10 27 44
> Cell:   +33 - (0)6 85 62 59 98
> Fax :   +33 - (0)9 58 10 27 44
> 
> Fax (D):+49 - (0)3 21 21 25 22 44
> 
> email:  rai...@krugs.de
> 
> Skype:  RMkrug
> 
> __
> 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] Possible problem with namespaceImportFrom() and methods for generic primitive functions

2013-10-18 Thread John Chambers
Very good report.

Should be fixed in the development version for 3.1.0 and in 3.0.2 patched. (svn 
revision 64076).

John


On Oct 18, 2013, at 8:51 AM, Karl Forner  wrote:

> Hi all,
> 
> I have a problem with a package that imports two other packages which both
> export a method for the `[` primitive function.
> 
> I set up a reproducible example here:
> https://github.com/kforner/namespaceImportFrom_problem.git
> 
> Basically, the testPrimitiveImport package imports testPrimitiveExport1 and
> testPrimitiveExport2, which both export a S4 class and a `[` method for the
> class.
> Then:
> R CMD INSTALL -l lib testPrimitiveExport1
> R CMD INSTALL -l lib testPrimitiveExport2
> 
> The command:
> R CMD INSTALL -l lib testPrimitiveImport
> 
> gives me:
> Error in namespaceImportFrom(self, asNamespace(ns)) :
>  trying to get slot "package" from an object of a basic class ("function")
> with no slots
> 
> I get the same message if I check the package (with R CMD check), or even
> if I try to load it using devtools::load_all()
> 
> 
> I tried to investigate the problem, and I found that the error arises in
> the base::namespaceImportFrom() function, and more precisely in
> this block:
>for (n in impnames) if (exists(n, envir = impenv, inherits = FALSE)) {
>if (.isMethodsDispatchOn() && methods:::isGeneric(n,  ns)) {
>genNs <- get(n, envir = ns)@package
> 
> Here n is '[', and the get(n, envir = ns) expression returns
> .Primitive("["), which is a function and has no @package slot.
> 
> This will only occur if exists(n, envir = impenv, inherits = FALSE) returns
> TRUE, i.e. if the '[' symbol is already in the imports env of the package.
> In my case, the first call to namespaceImportFrom() is for the first import
> of testPrimitiveExport1, which runs fine and populate the imports env with
> '['.
> But for the second call, exists(n, envir = impenv, inherits = FALSE) will
> be TRUE, so that the offending line will be called.
> 
> 
> I do not know if the problem is on my side, e.g. from a misconfiguration of
> the NAMESPACE file, or if it is a bug and in which case what should be done.
> 
> Any feedback appreciated.
> 
> Karl Forner
> 
>   [[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


Re: [Rd] advise on Depends

2013-10-25 Thread John Chambers
One additional point to Michael's summary:

The "methods" package itself should stay in Depends:, to be safe.

There are a number of function calls to the methods package that may be 
included in generated methods for user classes.  These have not been revised to 
work when the methods package is not attached, so importing the package only 
may run into problems.  This has been an issue, for example, in using Rscript.

John

On Oct 25, 2013, at 11:26 AM, Michael Lawrence  
wrote:

> On Wed, Oct 23, 2013 at 8:33 PM, Kasper Daniel Hansen <
> kasperdanielhan...@gmail.com> wrote:
> 
>> This is about the new note
>> 
>> Depends: includes the non-default packages:
>>  ‘BiocGenerics’ ‘Biobase’ ‘lattice’ ‘reshape’ ‘GenomicRanges’
>>  ‘Biostrings’ ‘bumphunter’
>> Adding so many packages to the search path is excessive and importing
>> selectively is preferable.
>> 
>> Let us say my package A either uses a class B (by producing an object that
>> has B embedded as a slot) from another package or provides a specific
>> method for a generic defined in another package (both examples using S4).
>> In both case my impression is that best practices is I ought to Depend on
>> such a package, so it is a available at run time to the user.
>> 
>> 
> For classes, you just need to import the class with importClassesFrom().
> For generics, as long as your package exports the method with
> exportMethods(), the generic will also be exported from your package,
> regardless of whether the defining package is attached. And the methods
> from the loaded-but-not-attached packages are available for the generic. So
> neither of these two is really a problem.
> 
> The rationale for Depends is that the user might always want to use
> functions defined by another package with objects consumed/produced by your
> package, such as generics for which your package has not defined any
> methods. For example, rtracklayer Depends on GenomicRanges, because it
> imports objects from files as GenomicRanges objects.  So just consider what
> the user sees when looking at your API. What's private, what's public?
> 
> Michael
> 
> 
>> Comments?
>> 
>> Best,
>> Kasper
>> 
>>[[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

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


Re: [Rd] advise on Depends

2013-10-25 Thread John Chambers
Software generated in methods for user classes calls functions in the methods 
package, as I said.  I don't  know the circumstances (if any) when such calls 
fail to find functions if  the whole package is  imported.   Perhaps someone on 
this list may have examples.

But for sure just importing the functions your package calls during 
installation (setClass(), setMethod(), etc.) won't always be enough.

When the S4 classes and methods were implemented in R in the early 2000s, it 
was assumed that the methods package would be considered part of the system, as 
the analogous code was in S.  

It would be nice to either have the package included in Rscript, CMD check, 
etc. or for some enterprising and very thorough person to go through and 
bullet-proof the generated code for the absence of the package from the search 
list.

Absent either of those, the defensive approach is to put methods in Depends.   
Or at least, import the package rather than just the obvious functions.

John


On Oct 25, 2013, at 3:46 PM, Paul Gilbert  wrote:

> 
> 
> On 13-10-25 05:21 PM, Henrik Bengtsson wrote:
>> On Fri, Oct 25, 2013 at 1:39 PM, John Chambers 
>> wrote:
>>> One additional point to Michael's summary:
>>> 
>>> The "methods" package itself should stay in Depends:, to be safe.
> 
> It would be nice to have more detail about when this is necessary, rather 
> than suggested as a general workaround. I thought the principle of putting 
> things in Imports was that it is safer. I have methods listed in Imports 
> rather than Depends in 16 of my packages, doing roughly what was the basis 
> for the original question, and I am not aware of a problem, yet.
> 
> Paul
> 
>>> 
>>> There are a number of function calls to the methods package that
>>> may be included in generated methods for user classes.  These have
>>> not been revised to work when the methods package is not attached,
>>> so importing the package only may run into problems.  This has been
>>> an issue, for example, in using Rscript.
>> 
>> To clarify that last sentence for those not aware (and hopefully
>> spare someone having to troubleshoot this), executing R
>> scripts/expressions using 'Rscript' rather than 'R' differs by which
>> packages are attached by default.  Example:
>> 
>> % Rscript -e "search()" [1] ".GlobalEnv""package:stats"
>> "package:graphics" [4] "package:grDevices" "package:utils"
>> "package:datasets" [7] "Autoloads" "package:base"
>> 
>> % R --quiet -e "search()"
>>> search()
>> [1] ".GlobalEnv""package:stats" "package:graphics" [4]
>> "package:grDevices" "package:utils" "package:datasets" [7]
>> "package:methods"   "Autoloads" "package:base"
>> 
>> Note how 'methods' is not attached when using Rscript.  This is
>> explained in help("Rscript"), help("options"), and in 'R
>> Installation and Administration'.
>> 
>> /Henrik
>> 
>> 
>>> 
>>> John
>>> 
>>> On Oct 25, 2013, at 11:26 AM, Michael Lawrence
>>>  wrote:
>>> 
>>>> On Wed, Oct 23, 2013 at 8:33 PM, Kasper Daniel Hansen <
>>>> kasperdanielhan...@gmail.com> wrote:
>>>> 
>>>>> This is about the new note
>>>>> 
>>>>> Depends: includes the non-default packages: ‘BiocGenerics’
>>>>> ‘Biobase’ ‘lattice’ ‘reshape’ ‘GenomicRanges’ ‘Biostrings’
>>>>> ‘bumphunter’ Adding so many packages to the search path is
>>>>> excessive and importing selectively is preferable.
>>>>> 
>>>>> Let us say my package A either uses a class B (by producing an
>>>>> object that has B embedded as a slot) from another package or
>>>>> provides a specific method for a generic defined in another
>>>>> package (both examples using S4). In both case my impression is
>>>>> that best practices is I ought to Depend on such a package, so
>>>>> it is a available at run time to the user.
>>>>> 
>>>>> 
>>>> For classes, you just need to import the class with
>>>> importClassesFrom(). For generics, as long as your package
>>>> exports the method with exportMethods(), the generic will also be
>>>> exported from your package, regardless of whether the defining
>>>>

Re: [Rd] unloadNamespace, getPackageName and "Created a package name xxx " warning

2013-10-29 Thread John Chambers
This was previously reported and fixed.  See the NEWS file and bug 
report 15481.


On 10/29/13 9:19 AM, Karl Forner wrote:

Dear all,

Consider this code:

library("data.table")
unloadNamespace('data.table')


It produces some warnings
Warning in FUN(X[[1L]], ...) :
   Created a package name, ‘2013-10-29 17:05:51’, when none found
Warning in FUN(X[[1L]], ...) :
   Created a package name, ‘2013-10-29 17:05:51’, when none found
...

The warning is produced by the getPackageName() function.
e.g.
getPackageName(parent.env(getNamespace('data.table')))

I was wondering what could be done to get rid of these warnings, which I
believe in the case "unloadNamespace" case are irrelevant.

The stack of calls is:
# where 3: sapply(where, getPackageName)
# where 4: findClass(what, classWhere)
# where 5: .removeSuperclassBackRefs(cl, cldef, searchWhere)
# where 6: methods:::cacheMetaData(ns, FALSE, ns)
# where 7: unloadNamespace(pkgname)

So for instance:

findClass('data.frame', getNamespace('data.table'))

generates a warning which once again seems irrelevant.

On the top of my head, I could imagine adding an extra argument to
getPackageName, say warning = TRUE, which would be set to FALSE in the
getPackageName call in findClass() body.

I also wonder if in the case of import namespaces, getPackageName() could
not find a more appropriate name:

parent.env(getNamespace('data.table'))


attr(,"name")
[1] "imports:data.table"

This namespace has a name that might be used to generate the package name.

My question is: what should be done ?

Thanks for your attention.

Karl Forner

[[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


Re: [Rd] Strange warnings when unloading packages with S4 classes

2013-12-19 Thread John Chambers
Previously reported and fixed in 3.0.2-patched (Bug 15481).  Unless there is a 
3.0.3, you will have to wait for 3.1.0.

On Dec 19, 2013, at 10:19 AM, Winston Chang  wrote:

> I've been seeing warnings when unloading packages. They can be seen with
> the shiny and sp packages, among others (this is on R 3.0.2). For example:
>> library(sp)
>> unloadNamespace('sp')
> Warning messages:
> 1: In FUN(X[[2L]], ...) :
>  Created a package name, ‘2013-12-19 12:14:24’, when none found
> 2: In FUN(X[[2L]], ...) :
>  Created a package name, ‘2013-12-19 12:14:24’, when none found
> 3: In FUN(X[[2L]], ...) :
>  Created a package name, ‘2013-12-19 12:14:24’, when none found
> 4: In FUN(X[[2L]], ...) :
>  Created a package name, ‘2013-12-19 12:14:24’, when none found
> 
> It appears to be related to the methods:::.removeSuperclassBackRefs
> function.
> 
> 
> I can get the warnings to appear when the following are both true:
> * The package has an S4 class which inherits from a class outside of the
> package.
> * The NAMESPACE file contains import(methods)
> 
> I've created some very simple test packages here which illustrate the
> problem, along with instructions on how to duplicate the warning.
> https://github.com/wch/s4unload
> 
> The warnings only appear when unloading the package where both of the
> conditions above are true. I'm not sure why import(methods) should make a
> difference, but it does.
> 
> Is this a bug in the implementation of S4?
> 
> Best,
> -Winston
> 
>   [[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


Re: [Rd] class() on substitute(...) output?

2014-01-03 Thread John Chambers

On Jan 3, 2014, at 9:46 AM, Hadley Wickham  wrote:

> On Thu, Jan 2, 2014 at 7:16 PM, Henrik Bengtsson  
> wrote:
>> Does it make sense to talk about the class of the output of
>> substitute(...)?  I'm puzzled by the following outputs:
>> 
>> ee <- list(
>>  A = substitute( a <- 1 ),
>>  B = substitute({ a <- 1 }),
>>  C = substitute(( a <- 1 )),
>>  D = substitute( a == 1 )
>> )
>> 
>>> t(sapply(ee, FUN=function(e) { c(typeof=typeof(e), mode=mode(e), 
>>> class=class(e)) }))
>>  typeof mode   class
>> A "language" "call" "<-"
>> B "language" "call" "{"
>> C "language" "(""("
>> D "language" "call" "call"
>> 
>> That the mode in C is "(", is motivated in help("mode"): "that some
>> calls have mode "(" which is S compatible."  However, what's the
>> explanation for the different classes?  Is that intended or just
>> "garbage" output?
> 
> ?class has:
> 
> "Many R objects have a class attribute, a character vector giving the
> names of the classes from which the object inherits. If the object
> does not have a class attribute, it has an implicit class, "matrix",
> "array" or the result of mode(x) (except that integer vectors have
> implicit class "integer"). (Functions oldClass and oldClass<- get and
> set the attribute, which can also be done directly.)"
> 
> which suggests either a bug or some tweaks are needed to the documentation.

Definitely not the former.  What happens is easy enough to see, if you follow 
the definition of the .Primitive.  Routine R_data_class in attrib.c does the 
computation.  When there is no class attribute, it supplies the definition for 
"matrix" and "array", turns the 3 types for functions into "function", and 
distinguishes among objects of type "language" to give specific classes to the 
syntactic functions called, such as `while`(),  `if`(), etc.

It does seem that the documentation should say something similar.

John

> 
> Is there any point in ever using mode() except for S+ compatibility?
> It just adds some confusing aliases on top of typeof.
> 
> Hadley
> 
> -- 
> http://had.co.nz/
> 
> __
> 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] Conflicting definitions for function redefined as S4 generics

2014-03-26 Thread John Chambers
I haven't looked at this in detail, but my guess is the following is the 
distinction:


A simple call setGeneric("sort") makes a generic of the existing 
function _with the existing package_:


> setGeneric("sort")
[1] "sort"
> sort
standardGeneric for "sort" defined from package "base"

function (x, decreasing = FALSE, ...)
standardGeneric("sort")

Methods may be defined for arguments: x, decreasing
Use  showMethods("sort")  for currently available ones.

The same thing will, I believe, happen automatically if one calls 
setMethod() without a prior call to setGeneric().


What BioGenerics does is different:  it excludes the two trailing 
arguments and so creates a new generic in its own namespace.


Similarly (from the global environment in this case):

> setGeneric("sort", signature="x")
Creating a new generic function for 'sort' in the global environment
[1] "sort"
> sort
standardGeneric for "sort" defined from package ".GlobalEnv"

function (x, decreasing = FALSE, ...)
standardGeneric("sort")

Methods may be defined for arguments: x
Use  showMethods("sort")  for currently available ones.


When packages are loaded, the methods in the new package are installed 
in the generic function (in memory) that corresponds to the information 
in the methods as to generic name and package slot.


As Duncan points out, it's essential to keep functions of the same name 
but different packages distinct.  Like all R objects, generic functions 
are referred to by the combination of a name and an environment, here a 
package namespace.


Just how this sorts out into the symptoms reported I can't say, but I 
suspect this is the underlying issue.


John





On 3/26/14, 7:11 AM, Ulrich Bodenhofer wrote:

First of all, thanks for the very interesting and encouraging replies
that have been posted so far!

Let me quickly add what I have tried up to now:

- setMethod("sort", signature("ExClust"), function(x, decreasing=FALSE,
%...%) %...% , sealed=TRUE) without any call to setGeneric(), i.e.
assuming that setMethod() would implicitly create an S4 generic out of
the S3 method sort(). Note that '%...%' in the code snippet stands for
some details that I left out.

- setGeneric("sort", def=function(x, decreasing=FALSE, ...)
standardGeneric("sort")), i.e. consistency with the S3 generic of sort()
in 'base', plus the call to setMethod() as shown above.

- setGeneric("sort", signature="x"), i.e. consistency with the generic's
definition in BiocGenerics, as suggested by Martin Morgan, plus the call
to setMethod() as shown above.

For all three trials, the result was exactly the same: (1) everything
works nicely if I load BiocGenerics before apcluster; (2) if I load
BiocGenerics after apcluster, apcluster's sort() function is broken and
gives the following error:

Error in rank(x, ties.method = "min", na.last = "keep") :
   unimplemented type 'list' in 'greater'
In addition: Warning message:
In is.na(x) : is.na() applied to non-(list or vector) of type 'S4'

Obviously, sort() is dispatched to the definition made by BiocGenerics:

 > showMethods("sort", includeDefs=TRUE)
Function: sort (package BiocGenerics)
x="ANY"
function (x, decreasing = FALSE, ...)
{
 if (!is.logical(decreasing) || length(decreasing) != 1L)
 stop("'decreasing' must be a length-1 logical vector.\nDid you
intend to set 'partial'?")
 UseMethod("sort")
}

So the method registered for class 'ExClust' is  lost if BiocGenerics is
attached. Just for your information: all these tests have been done with
R 3.0.2 and Bioconductor 2.13 (BiocGenerics version 0.8.0).

Thanks and best regards,
Ulrich



On 03/26/2014 02:48 PM, Duncan Murdoch wrote:

On 26/03/2014, 9:13 AM, Gabriel Becker wrote:

Perhaps a patch to R such that generics don't clobber each-other's
method
tables if the signatures agree? I haven't dug deeply, but simply merging
the method tables seems like it would be safe when there are no
conflicts.

That way this type of multiplicity would not be a problem, though it
wouldn't help (as it shouldn't) if the two generics didn't agree on
signature or both carried methods for the same class signature.


I don't think R should base the decision on the signature.

There are two very different situations where this might come up. In
one, package A and package B might both define a generic named foo()
that happens to have the same signature, but with nothing in common.
That should be allowed, and should behave the same as when they both
create functions with the same name:  it should be up to the user to
specify which generic is being called.  If R merged the two generics
into one, there would be chaos.

The other situation is more likely to apply to this case.  It sounds
as though both apcluster and BiocGenerics are creating a sort()
generic by promoting the base package S3 generic into an S4 generic.
Clearly they should not be creating separate generics, there's just one.

I don't know if there's something wrong with the way apcluster or
BiocGenerics are

Re: [Rd] Conflicting definitions for function redefined as S4 generics

2014-03-27 Thread John Chambers
I'm sympathetic to the problem.  But, whatever my opinion, it's not likely that 
the basic R paradigm with respect to S3/S4 methods will change much, and 
certainly not for a year.

Meanwhile, let's remember the essential idea.  Every function has a 
corresponding implicit generic form (well, partially ignoring primitives for 
the moment).

The standard approach to defining methods for a non-generic is either to just 
use setMethod() or to use the simple form of setGeneric("foo").  EIther way, 
the generic function and the method refer to the package from which foo() came. 
 If all packages defining methods for foo() follow this pattern, the result is 
a single table of methods in the generic for foo() during an R session.

See the "Basic Use" section of ?setGeneric. 

The difficulties come when some package sets up a _different_ version of foo() 
as a generic.  This becomes a separate, incompatible, generic function. When 
still other packages are involved, there is a potential for methods to be 
divided among multiple tables.  If people feel they need to do this, they have 
to sort out the consequences.  Ideally, in my opinion, they should rename the 
function so users can choose which version to call.

Finally, even if we managed to incorporate implicit generic versions of 
functions in base (don't hold your breath), it's extremely unlikely that these 
would lop off arguments from the non-generic function.  There is no real reason 
to prohibit some formal arguments from being in the formal arguments to the 
generic. 

In a few cases, some arguments may be prohibited from being dispatched on, 
e.g., if those arguments have to be evaluated in a non-standard way, and that 
is handled by the signature= argument.  In any case, the implicitGeneric() 
mechanism is designed to handle such issues.  Meaning that package programming 
should be fairly immune to change, so long as the Basic Use is followed.

Summary: So long as the recommendations of Basic Use are followed, I don't see 
the problem of multiple versions.  There are other aspects of the non-inclusion 
of S4 in the R paradigm that cause difficulties, but basic use approach should 
provide one consistent table of methods for each function.

John


On Mar 27, 2014, at 2:13 AM, Ulrich Bodenhofer  wrote:

> I fully agree, Michael, that this would be a great thing to have! I have 
> often wondered why R and the standard packages are still sticking so much to 
> the old-style S3 flavor though S4 is part of standard R. I acknowledge that 
> backward compatibility is important, but, as far as I got it, redefining a 
> function or S3 generic as an S4 generic should not harm existing 
> functionality (if done properly). If it turns out not to be a good option to 
> do this in the base package, why not as part of the methods package? That 
> will leave existing functionality of base unchanged and will provide a clean 
> situation to all users/packages using S4.
> 
> This should not create a compatibility problem on the Bioconductor side 
> either, since Bioconductor releases are explicitly bound to specific R 
> versions. Once again: I fully support this idea (not only for sort(), but 
> also for a wide range of other functions), though, not being an R core team 
> member, I do not really feel in the position to demand such a fundamental 
> change.
> 
> For the time being, it seems I have three options:
> 
> 1) not supplying the sort() function yet (it is not yet in the release, but 
> only in my internal devel version)
> 2) including a dependency to BiocGenerics
> 3) leaving the problem open, mentioning in the documentation that users who 
> want to use apcluster in conjunction with Bioconductor should load 
> BiocGenerics first
> 
> As far as I got it, there seems to be no other clean way to get rid of the 
> problem, right?
> 
> Best regards,
> Ulrich
> 
> 
> On 03/26/2014 02:44 PM, Michael Lawrence wrote:
>> That might be worth thinking about generally, but it would still be nice to 
>> have the base generics pre-defined, so that people are not copy and pasting 
>> the definitions everywhere, hoping that they stay consistent.
>> 
>> 
>> On Wed, Mar 26, 2014 at 6:13 AM, Gabriel Becker > > wrote:
>> 
>>Perhaps a patch to R such that generics don't clobber each-other's
>>method tables if the signatures agree? I haven't dug deeply, but
>>simply merging the method tables seems like it would be safe when
>>there are no conflicts.
>> 
>>That way this type of multiplicity would not be a problem, though
>>it wouldn't help (as it shouldn't) if the two generics didn't
>>agree on signature or both carried methods for the same class
>>signature.
>> 
>>~G
>> 
>> 
>>On Wed, Mar 26, 2014 at 4:38 AM, Michael Lawrence
>>mailto:lawrence.mich...@gene.com>> wrote:
>> 
>>The BiocGenerics package was designed to solve this issue within
>>Bioconductor. It wouldn't be the worst thing in the world

  1   2   3   4   >