[Rd] work-around for debugger broken (by changed behaviour of get under R 2.8?) when functions have ... arguments

Keith Ponting k.ponting at aurix.com
Tue Jan 20 14:02:47 CET 2009


Hello all,

Sorry to trouble you, but this is a follow-up with a work-around to the
problem I posted on R-help
(http://article.gmane.org/gmane.comp.lang.r.general/136515). Is it
possible to add the work-around or some equivalent to the utils package,
please? 

I think this may be related to the changed behaviour of get under R 2.8
referred to in:
http://www.nabble.com/changed-behaviour-of-%27get%27-in-2.8.0:-request-f
or-unchange-td20143510.html

I am trying to use the debugger (to resolve a bug when running with
Rscript) and have a secondary problem when functions have unused ... 
Arguments which can be reduced to the following sequence:

  # A script with a bug in it
  options(error=quote({dump.frames("debug.dump",to.file=TRUE)}))
  silly <- function(x,...){
    z <- list(...)
    NONEXISTENT.FUNCTION()
  }
  silly(1)

  # and to debug it:
  load("debug.dump.rda")
  debugger(debug.dump)

However when I execute the debugger as follows, I cannot actually debug
the stack:

  > load("debug.dump.rda")
  > debugger(debug.dump)
  Message:  Error in silly(1) : could not find function
  "NONEXISTENT.FUNCTION"
  Available environments had calls:
  1: silly(1)

  Enter an environment number, or 0 to exit  Selection: 1
  Error in get(.obj, envir = dump[[.selection]]) :
    argument "..." is missing, with no default

get flags this error whether I enter the code to invoke silly directly,
source a .R file or invoke with Rscript, all under SuSe linux 10.3
(sessionInfo below). I also get it if I try the debugger under Windows
Vista with R version 2.8.1. 

It all works perfectly happily under any of the following conditions:
1) I rewrite the function without the "..."
2) I execute the debugger lines under R 2.7.0 (linux)
3) I actually pass a value through "..."

Unfortunately 1 and 3 are not feasible for my real code - would it be
possible to add the try fix below (or some equivalent) to debugger in
the utils package? 

> sessionInfo()
R version 2.8.1 (2008-12-22)
i686-pc-linux-gnu

locale:
LC_CTYPE=en_GB.UTF-8;LC_NUMERIC=C;LC_TIME=en_GB.UTF-8;LC_COLLATE=en_GB.U
TF-8;LC_MONETARY=C;LC_MESSAGES=en_GB.UTF-8;LC_PAPER=en_GB.UTF-8;LC_NAME=
C;LC_ADDRESS=C;LC_TELEPHONE=C;LC_MEASUREMENT=en_GB.UTF-8;LC_IDENTIFICATI
ON=C

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


Thankyou,

Keith Ponting

Keith Ponting
Aurix Ltd, Malvern WR14 3SZ  UK

P.S. Wrapping a try around the offending assign in debugger.look means
that I still get the error message, but am able to browse the function
calls. 

I would prefer not to blank out the error message completely, to avoid
surprises when I try to access ... in the debugger via list(...), which
works when a value was passed to ... but when nothing was passed to ...
gives the message "Error: '...' used in an incorrect context", which may
be true but initially led me to conclude that I could not see ...
contents via the debugger.

debug.kmp<-function (dump = last.dump)
{
    debugger.look <- function(.selection) {
        for (.obj in ls(envir = dump[[.selection]], all.names = TRUE))
try(assign(.obj, 
            get(.obj, envir = dump[[.selection]])))
        cat(gettext("Browsing in the environment with call:\n   "), 
            calls[.selection], "\n", sep = "")
        rm(.obj, .selection)
        browser()
    }
    if (class(dump) != "dump.frames") {
        cat(gettext("'dump' is not an object of class 'dump.frames'\n"))
        return(invisible())
    }
    err.action <- getOption("error")
    on.exit(options(error = err.action))
    if (length(msg <- attr(dump, "error.message"))) 
        cat(gettext("Message: "), msg)
    n <- length(dump)
    calls <- names(dump)
    repeat {
        cat(gettext("Available environments had calls:\n"))
        cat(paste(1:n, ": ", calls, sep = ""), sep = "\n")
        cat(gettext("\nEnter an environment number, or 0 to exit  "))
        repeat {
            ind <- .Internal(menu(as.character(calls)))
            if (ind <= n) 
                break
        }
        if (ind == 0) 
            return(invisible())
        debugger.look(ind)
    }
}



More information about the R-devel mailing list