Re: [Rd] Improving user-friendliness of S4 dispatch failure when mis-naming arguments?

2023-08-10 Thread Hadley Wickham
Hi Michael,

I can't help with S4, but I can help to make sure this isn't a problem
with S7. What do you think of the current error message? Do you see
anything obvious we could do to improve?

library(S7)

dbGetQuery <- new_generic("dbGetQuery", c("conn", "statement"))
dbGetQuery(connection = NULL, query = NULL)
#> Error: Can't find method for generic `dbGetQuery(conn, statement)`:
#> - conn : MISSING
#> - statement: MISSING

Hadley

On Wed, Aug 9, 2023 at 10:02 PM Michael Chirico via R-devel
 wrote:
>
> I fielded a debugging request from a non-expert user today. At root
> was running the following:
>
> dbGetQuery(connection = conn, query = query)
>
> The problem is that they've named the arguments incorrectly -- it
> should have been [1]:
>
> dbGetQuery(conn = conn, statement = query)
>
> The problem is that the error message "looks" highly confusing to the
> untrained eye:
>
> Error in (function (classes, fdef, mtable)  :   unable to find an
> inherited method for function ‘dbGetQuery’ for signature ‘"missing",
> "missing"’
>
> In retrospect, of course, this makes sense -- the mis-named arguments
> are getting picked up by '...', leaving the required arguments
> missing.
>
> But I was left wondering how we could help users right their own ship here.
>
> Would it help to mention the argument names? To include some code
> checking for weird combinations of missing arguments? Any other
> suggestions?
>
> Mike C
>
> [1] 
> https://github.com/r-dbi/DBI/blob/97934c885749dd87a6beb10e8ccb6a5ebea3675e/R/dbGetQuery.R#L62-L64
>
> __
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel



-- 
http://hadley.nz

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


Re: [Rd] Improving user-friendliness of S4 dispatch failure when mis-naming arguments?

2023-08-10 Thread Michael Chirico via R-devel
I forwarded that along to the original reporter with positive feedback
-- including the argument names is definitely a big help for cuing
what exactly is missing.

Would a patch to do something similar for S4 be useful?

On Thu, Aug 10, 2023 at 6:46 AM Hadley Wickham  wrote:
>
> Hi Michael,
>
> I can't help with S4, but I can help to make sure this isn't a problem
> with S7. What do you think of the current error message? Do you see
> anything obvious we could do to improve?
>
> library(S7)
>
> dbGetQuery <- new_generic("dbGetQuery", c("conn", "statement"))
> dbGetQuery(connection = NULL, query = NULL)
> #> Error: Can't find method for generic `dbGetQuery(conn, statement)`:
> #> - conn : MISSING
> #> - statement: MISSING
>
> Hadley
>
> On Wed, Aug 9, 2023 at 10:02 PM Michael Chirico via R-devel
>  wrote:
> >
> > I fielded a debugging request from a non-expert user today. At root
> > was running the following:
> >
> > dbGetQuery(connection = conn, query = query)
> >
> > The problem is that they've named the arguments incorrectly -- it
> > should have been [1]:
> >
> > dbGetQuery(conn = conn, statement = query)
> >
> > The problem is that the error message "looks" highly confusing to the
> > untrained eye:
> >
> > Error in (function (classes, fdef, mtable)  :   unable to find an
> > inherited method for function ‘dbGetQuery’ for signature ‘"missing",
> > "missing"’
> >
> > In retrospect, of course, this makes sense -- the mis-named arguments
> > are getting picked up by '...', leaving the required arguments
> > missing.
> >
> > But I was left wondering how we could help users right their own ship here.
> >
> > Would it help to mention the argument names? To include some code
> > checking for weird combinations of missing arguments? Any other
> > suggestions?
> >
> > Mike C
> >
> > [1] 
> > https://github.com/r-dbi/DBI/blob/97934c885749dd87a6beb10e8ccb6a5ebea3675e/R/dbGetQuery.R#L62-L64
> >
> > __
> > R-devel@r-project.org mailing list
> > https://stat.ethz.ch/mailman/listinfo/r-devel
>
>
>
> --
> http://hadley.nz

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


Re: [Rd] Improving user-friendliness of S4 dispatch failure when mis-naming arguments?

2023-08-10 Thread Gabriel Becker
I just want to add my 2 cents that I think it would be very useful and
beneficial to improve S4 to surface that information as well.

More information about the way that the dispatch failed would be of great
help in situations like the one Michael pointed out.

~G

On Thu, Aug 10, 2023 at 9:59 AM Michael Chirico via R-devel <
r-devel@r-project.org> wrote:

> I forwarded that along to the original reporter with positive feedback
> -- including the argument names is definitely a big help for cuing
> what exactly is missing.
>
> Would a patch to do something similar for S4 be useful?
>
> On Thu, Aug 10, 2023 at 6:46 AM Hadley Wickham 
> wrote:
> >
> > Hi Michael,
> >
> > I can't help with S4, but I can help to make sure this isn't a problem
> > with S7. What do you think of the current error message? Do you see
> > anything obvious we could do to improve?
> >
> > library(S7)
> >
> > dbGetQuery <- new_generic("dbGetQuery", c("conn", "statement"))
> > dbGetQuery(connection = NULL, query = NULL)
> > #> Error: Can't find method for generic `dbGetQuery(conn, statement)`:
> > #> - conn : MISSING
> > #> - statement: MISSING
> >
> > Hadley
> >
> > On Wed, Aug 9, 2023 at 10:02 PM Michael Chirico via R-devel
> >  wrote:
> > >
> > > I fielded a debugging request from a non-expert user today. At root
> > > was running the following:
> > >
> > > dbGetQuery(connection = conn, query = query)
> > >
> > > The problem is that they've named the arguments incorrectly -- it
> > > should have been [1]:
> > >
> > > dbGetQuery(conn = conn, statement = query)
> > >
> > > The problem is that the error message "looks" highly confusing to the
> > > untrained eye:
> > >
> > > Error in (function (classes, fdef, mtable)  :   unable to find an
> > > inherited method for function ‘dbGetQuery’ for signature ‘"missing",
> > > "missing"’
> > >
> > > In retrospect, of course, this makes sense -- the mis-named arguments
> > > are getting picked up by '...', leaving the required arguments
> > > missing.
> > >
> > > But I was left wondering how we could help users right their own ship
> here.
> > >
> > > Would it help to mention the argument names? To include some code
> > > checking for weird combinations of missing arguments? Any other
> > > suggestions?
> > >
> > > Mike C
> > >
> > > [1]
> https://github.com/r-dbi/DBI/blob/97934c885749dd87a6beb10e8ccb6a5ebea3675e/R/dbGetQuery.R#L62-L64
> > >
> > > __
> > > R-devel@r-project.org mailing list
> > > https://stat.ethz.ch/mailman/listinfo/r-devel
> >
> >
> >
> > --
> > http://hadley.nz
>
> __
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
>

[[alternative HTML version deleted]]

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


[Rd] as.matrix.dist patch (performance)

2023-08-10 Thread Tim Taylor
Please find attached a small patch to improve the performance of 
as.matrix.dist().  It's a tiny bit more involved than the current code 
but does bring a reasonable speed improvement for larger  objects 
(remaining comparable for smaller ones).


Example:

set.seed(1)
dat <- matrix(rnorm(2), ncol = 2);
system.time(as.matrix(dist(dat)))

As of r84931:

   user  system elapsed
  3.370   1.154   4.535

With this patch:

   user  system elapsed
  1.925   0.754   2.685

Submitting here in the first instance but happy to move to Bugzilla if 
more appropriate.


Cheers

Tim
Index: src/library/stats/R/dist.R
===
--- src/library/stats/R/dist.R	(revision 84931)
+++ src/library/stats/R/dist.R	(working copy)
@@ -49,10 +49,13 @@
 {
 size <- attr(x, "Size")
 df <- matrix(0, size, size)
-lower <- row(df) > col(df)
+idx <- seq_len(size)
+d1 <- unlist(lapply(idx[-1L], seq.int, to = size, by = 1L))
+d2 <- rep.int(idx[-size], times = rev(idx[-size]))
+lower <- cbind(d1,d2)
+upper <- cbind(d2,d1)
 df[lower] <- x ## preserving NAs in x
-df <- t(df)
-df[lower] <- x
+df[upper] <- x
 labels <- attr(x, "Labels")
 dimnames(df) <-
 	if(is.null(labels)) list(seq_len(size), seq_len(size)) else list(labels,labels)
__
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


Re: [Rd] feature request: optim() iteration of functions that return multiple values

2023-08-10 Thread Greg Snow
Another option that is similar to Enrico's is to use object oriented
programming with R6 or reference objects.  I prefer the R6 package
(which will still use an environment like Enrico, but with some
different syntax and a little easier if you want to do this multiple
times.

Here is some example code (this grows the vectors inefficiently, which
could be improved, but it is fast as is):

library(R6)

RB <- R6Class("RB",
public=list(
  x = numeric(0),
  y = numeric(0),
  val=numeric(0),
  fun = function(x) {
x1 <- x[1]
x2 <- x[2]
self$x <- c(self$x, x1)
self$y <- c(self$y, x2)
ans <- 100*(x2-x1*x1)^2 + (1-x1)^2
self$val <- c(self$val, ans)
ans
  }
)
)

rb1 <- RB$new()
optim(c(-1.2, 1), rb1$fun)
plot(rb1$x, rb1$y, type='l')

rb2 <- RB$new()
optim(c(0,1), rb2$fun)
lines(rb2$x, rb2$y, col='blue')

library(optimx)

rb3 <- RB$new()
optimr(c(-1.2,1), rb3$fun)
lines(rb3$x, rb3$y, col='red')

rb4 <- RB$new()
optimr(c(-1.2,1), rb4$fun, method='hjn')
lines(rb4$x, rb4$y, col='forestgreen')

On Fri, Aug 4, 2023 at 2:22 AM Enrico Schumann  wrote:
>
> On Thu, 03 Aug 2023, Sami Tuomivaara writes:
>
> > Dear all,
> >
> > I have used optim a lot in contexts where it would
> > useful to be able to iterate function myfun that, in
> > addition to the primary objective to be minimized
> > ('minimize.me'), could return other values such as
> > alternative metrics of the minimization, informative
> > intermediate values from the calculations, etc.
> >
> > myfun  <- function()
> > {
> > ...
> > return(list(minimize.me = minimize.me, R2 = R2, pval = pval, etc.))
> > }
> >
> > During the iteration, optim could utilize just the first value from the 
> > myfun return list; all the other values calculated and returned by myfun 
> > could be ignored by optim.
> > After convergence, the other return values of myfun
> > could be finally extracted and appended into the optim
> > return value (which is a list) as additional entry
> > e.g.: $aux <- list(R2, pval, etc.), (without
> > 'minimize.me' as it is already returned as $value).
> >
> > The usual ways for accessing optim return values, e.g.,
> > $par, $value, etc. are not affected.  Computational
> > cost may not be prohibitive either.  Is this feasible
> > to consider?
> >
>
> If you only wish to store additional information, you could do
> so with an environment, without changing optim.  For instance,
> like so (using the first example from ?optim):
>
> data <- new.env()
> data$i <- 0
> data$fun.value <- numeric(1000)
>
> fr <- function(x, data) {   ## Rosenbrock Banana function
> x1 <- x[1]
> x2 <- x[2]
> ans <- 100 * (x2 - x1 * x1)^2 + (1 - x1)^2
> data$i <- data$i + 1
> data$fun.value[data$i] <- ans
> ans
> }
> optim(c(-1.2,1), fr, data = data)
> ## $par
> ## [1] 1.000260 1.000506
> ##
> ## $value
> ## [1] 8.825241e-08
> ##
> ## $counts
> ## function gradient
> ##  195   NA
> ##
> ## 
>
> data$i
> ## 195
>
> plot(data$fun.value[1:data$i])
>
>
>
>
> --
> Enrico Schumann
> Lucerne, Switzerland
> http://enricoschumann.net
>
> __
> R-devel@r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel



-- 
Gregory (Greg) L. Snow Ph.D.
538...@gmail.com

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


Re: [Rd] Improving user-friendliness of S4 dispatch failure when mis-naming arguments?

2023-08-10 Thread Michael Chirico via R-devel
Here's a trivial patch that offers some improvement:

Index: src/library/methods/R/methodsTable.R
===
--- src/library/methods/R/methodsTable.R (revision 84931)
+++ src/library/methods/R/methodsTable.R (working copy)
@@ -752,11 +752,12 @@
   if(length(methods) == 1L)
 return(methods[[1L]]) # the method
   else if(length(methods) == 0L) {
-cnames <- paste0("\"", vapply(classes, as.character, ""), "\"",
+cnames <- paste0(head(fdef@signature, length(classes)), "=\"",
vapply(classes, as.character, ""), "\"",
  collapse = ", ")
 stop(gettextf("unable to find an inherited method for function %s
for signature %s",
   sQuote(fdef@generic),
   sQuote(cnames)),
+ call. = FALSE,
  domain = NA)
   }
   else

Here's the upshot for the example on DBI:

dbGetQuery(connection = conn, query = query)
Error: unable to find an inherited method for function ‘dbGetQuery’
for signature ‘conn="missing", statement="missing"’

I don't have any confidence about edge cases / robustness of this
patch for generic S4 use cases (make check-all seems fine), but I
don't suppose a full patch would be dramatically different from the
above.

Mike C

On Thu, Aug 10, 2023 at 12:39 PM Gabriel Becker  wrote:
>
> I just want to add my 2 cents that I think it would be very useful and 
> beneficial to improve S4 to surface that information as well.
>
> More information about the way that the dispatch failed would be of great 
> help in situations like the one Michael pointed out.
>
> ~G
>
> On Thu, Aug 10, 2023 at 9:59 AM Michael Chirico via R-devel 
>  wrote:
>>
>> I forwarded that along to the original reporter with positive feedback
>> -- including the argument names is definitely a big help for cuing
>> what exactly is missing.
>>
>> Would a patch to do something similar for S4 be useful?
>>
>> On Thu, Aug 10, 2023 at 6:46 AM Hadley Wickham  wrote:
>> >
>> > Hi Michael,
>> >
>> > I can't help with S4, but I can help to make sure this isn't a problem
>> > with S7. What do you think of the current error message? Do you see
>> > anything obvious we could do to improve?
>> >
>> > library(S7)
>> >
>> > dbGetQuery <- new_generic("dbGetQuery", c("conn", "statement"))
>> > dbGetQuery(connection = NULL, query = NULL)
>> > #> Error: Can't find method for generic `dbGetQuery(conn, statement)`:
>> > #> - conn : MISSING
>> > #> - statement: MISSING
>> >
>> > Hadley
>> >
>> > On Wed, Aug 9, 2023 at 10:02 PM Michael Chirico via R-devel
>> >  wrote:
>> > >
>> > > I fielded a debugging request from a non-expert user today. At root
>> > > was running the following:
>> > >
>> > > dbGetQuery(connection = conn, query = query)
>> > >
>> > > The problem is that they've named the arguments incorrectly -- it
>> > > should have been [1]:
>> > >
>> > > dbGetQuery(conn = conn, statement = query)
>> > >
>> > > The problem is that the error message "looks" highly confusing to the
>> > > untrained eye:
>> > >
>> > > Error in (function (classes, fdef, mtable)  :   unable to find an
>> > > inherited method for function ‘dbGetQuery’ for signature ‘"missing",
>> > > "missing"’
>> > >
>> > > In retrospect, of course, this makes sense -- the mis-named arguments
>> > > are getting picked up by '...', leaving the required arguments
>> > > missing.
>> > >
>> > > But I was left wondering how we could help users right their own ship 
>> > > here.
>> > >
>> > > Would it help to mention the argument names? To include some code
>> > > checking for weird combinations of missing arguments? Any other
>> > > suggestions?
>> > >
>> > > Mike C
>> > >
>> > > [1] 
>> > > https://github.com/r-dbi/DBI/blob/97934c885749dd87a6beb10e8ccb6a5ebea3675e/R/dbGetQuery.R#L62-L64
>> > >
>> > > __
>> > > R-devel@r-project.org mailing list
>> > > https://stat.ethz.ch/mailman/listinfo/r-devel
>> >
>> >
>> >
>> > --
>> > http://hadley.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