Re: [Rd] c(, ) / help(dotsMethods) etc

2016-09-10 Thread Martin Maechler
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

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] table(exclude = NULL) always includes NA

2016-09-10 Thread Martin Maechler
> Suharto Anggono Suharto Anggono 
> on Sat, 10 Sep 2016 02:36:54 + writes:

> Looking at the code of function 'table' in R devel r71227, I see that the 
part "remove NA level if it was added only for excluded in factor(a, 
exclude=.)" is not quite right.
> In
> is.na(a) <- match(a0, c(exclude,NA), nomatch=0L)   ,
> I think that what is intended is
> a[a0 %in% c(exclude,NA)] <- NA  .
yes.
> So, it should be
>   is.na(a) <- match(a0, c(exclude,NA), nomatch=0L) > 0L
> or
>   is.na(a) <- as.logical(match(a0, c(exclude,NA), nomatch=0L))  .
> The parallel code
>is.na(a) <- match(a0,   exclude, nomatch=0L)
> is to be treated similarly.

indeed.  I may have been  very wrongly thinking that `is.na<-`
coerced its value to logical... or otherwise not thinking at all ;-)


> Example that gives wrong result in R devel r71225:
> table(3:1, exclude = 1)
> table(3:1, exclude = 1, useNA = "always")
> 

Thanks a lot, Suharto.   You are entirely correct.

I'm amazed that  table(*, exclude = *)  seems so rarely used / tested,
that this has gone undetected for almost four weeks.
It is fixed now with svn r71230.

Martin

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


Re: [Rd] c(, ) / help(dotsMethods) etc

2016-09-10 Thread Michael Lawrence
One option would be to use the same strategy that we use for cbind()
and rbind(), i.e., if dispatch fails, call a binary generic, c2(),
recursively. Could do the same for pmin() and pmax().

Michael

On Sat, 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] c(, ) / help(dotsMethods) etc

2016-09-10 Thread Martin Maechler
> John Chambers 
> on Sat, 10 Sep 2016 09:16:38 -0700 writes:

> (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.)

Thank you for the clarification.
I knew that the limitation "the same class" has not been a big
one, that's why I did use a class union in my example (below).
I thought there were other limitations.. never mind.

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

That's great!

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

Yes, I'm sorry if I sounded like saying something different.

That I think this [getting c() to work for a collection objects,
some S4] needs changes in R is because it seems that do_c()
fails to dispatch here, and hence the problem was with our C
function that has carried the comment 

| * To call this an ugly hack would be to insult all existing ugly hacks
| * at large in the world.

and I don't think I would be able to correctly patch that
infamous function (in src/main/eval.c) ...

Martin

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