32

Consider we have called debug() for several functions to make a breakpoint on them. When we find and solve the bug, is there anyway to undebug() all functions already marked by debug() by a single command?

Here is a good benchmark to see if your proposed method really works perfectly:

> library(limma) # bioconductor
> debug(read.ilmn)
> read.ilmn("a.txt") # No problem if this file does not exist
Browse[2]> debug(.read.oneilmnfile) # This is the debug browser for read.ilmn()
Browse[2]> Q # To exit debug browser
> undebug.all() # Here run your proposed function to undebug everything!
> read.ilmn("a.txt")
# Now if the debug browser is not started, you are lucky to pass this test!

You may see the accepted answer below. Any case for which this answer does not work, or cleaner versions, are more than welcome.

Ben Bolker
  • 211,554
  • 25
  • 370
  • 453
Ali
  • 9,440
  • 12
  • 62
  • 92
  • never tried this, but seems like the sort of thing that `lapply(yourListOfFunctions, undebug)` could do. Not sure if you need to reassign it or not... – Chase Oct 09 '12 at 19:42
  • Do we know anything more about the functions? Are these in your own package (so we can assume a particular environment or namespace), or just functions in the workspace/global environment? – Gavin Simpson Oct 09 '12 at 19:53
  • `eapply(.GlobalEnv,function(x) if(is.function(x)) undebug(x))`? – James Oct 09 '12 at 19:53
  • @GavinSimpson Edited it with `is.function` – James Oct 09 '12 at 19:57
  • 3
    +1 -- This is a great question, and I wish there was a straightforward way to do it... – Josh O'Brien Oct 09 '12 at 20:07
  • I modified my answer so that it now appears to work with your example. It's really not very surprising that undebugging a *hidden* function (i.e. one whose name starts with `.`) would fail, although there is a workaround in this case (add `all.names=TRUE` to the `ls()` call) – Ben Bolker Oct 09 '12 at 20:59
  • @BenBolker, Have you checked with the benchmark I provided in my question? I tested, and it is still not killing the debug – Ali Oct 09 '12 at 21:05
  • it works for me. did you update your code? – Ben Bolker Oct 09 '12 at 21:07
  • @BenBolker Yes I did. Let me restart my R – Ali Oct 09 '12 at 21:08
  • note that my function is called `undebug_all`, you renamed it to `undebug.all`. Are you **sure** you modified the function definition for the update? I have posted the code at http://www.math.mcmaster.ca/bolker/R/misc/undebug_all.R ... – Ben Bolker Oct 09 '12 at 21:19
  • @BenBolker Please see https://gist.github.com/3861959 – Ali Oct 09 '12 at 22:54
  • apparently it matters whether one calls `read.ilmn()` or `read.ilmn("a.txt")`, although I don't see why at the moment ... – Ben Bolker Oct 09 '12 at 23:29
  • I'm still working on this. Digging unexported functions out of namespaces is a pain in the butt. – Ben Bolker Oct 09 '12 at 23:53
  • @BenBolker It would be a great news of you if you can completely solve the problem and publish a function we can rely on! I think this is the first trial of this kind. – Ali Oct 10 '12 at 08:58
  • so -- does the current version work for you? – Ben Bolker Oct 10 '12 at 18:18
  • @BenBolker: Perfect, finally the answer is found. Well done! – Ali Oct 10 '12 at 18:38

3 Answers3

16

No, there is no completely reliable way to undebug() all functions. (I only say this because I've seen it discussed several times on R-devel and R-help.)

In this discussion, Brian Ripley weighed in, noting that:

Debugging is a property of a function object (a bit in the sxpinfo) and so you would have to traverse all reachable objects (as gc does) to find them all.

Here's a snippet in which Robert Gentleman answers (in the negative) a question about whether "there is a convenient way to know at any time which are the function flagged with debug() or trace() in a R session":

You probably didn't get an answer because the answer is no, there is no easy way.

Josh O'Brien
  • 159,210
  • 26
  • 366
  • 455
  • 1
    BTW, this is one reason to use `debugonce()` when you can get away with it. – Josh O'Brien Oct 09 '12 at 20:11
  • Indeed - `debugonce()` doesn't seem to set the information that `isdebugged()` recognises. – Gavin Simpson Oct 09 '12 at 20:13
  • @GavinSimpson -- Interesting. I have never thought of *how* `debugonce()` works, and would be interested to learn (if someone knows, or cares to dive into the sources). – Josh O'Brien Oct 09 '12 at 20:16
  • +1 Good Answer, well researched. As the OP has described the problem your point is well made and the only reasonable response to provide. If we can relax the scope of where functions are looked for then there are options as Ben Bolker and I suggest. – Gavin Simpson Oct 09 '12 at 20:17
  • @GavinSimpson -- Good point. The operative word in my answer really is "completely reliable". In the best R-help/R-devel discussion of this (which I'm not being able to put my finger on), there was a decent amount of back-and-forth, with a couple of the core members always countering proposed solutions with some one pathological/corner case or another. – Josh O'Brien Oct 09 '12 at 20:29
  • 1
    For what it's worth, I think `isdebugged()` was probably added to R sometime after the discussion in which Robert Gentleman weighed in ... – Ben Bolker Oct 09 '12 at 21:02
  • @BenBolker -- Yeah, it's killing me that I can't find the more recent discussion, since the threads I linked to are 11 and 7 years old, resp. Among the places you'd have to search to root out all functions are namespaces, and environments (perhaps nested a la **proto**) not directly on the search path. I'll ping you and Gavin in rchat if I ever find that thread (and if it's still interesting ;). – Josh O'Brien Oct 09 '12 at 21:13
  • I am very hopeful that BenBolker or any other people ideas will solve this problem completely and we will have soon a reliable undebug.all() function – Ali Oct 10 '12 at 08:59
  • @JoshO'Brien Is it possible to define a new debug() function that gets track of all functions that are set for debug (i.e. adding them to a list)? Then undebug_all() function can simply use that list. I am not perfect with namespaces otherwise I would try to write such a function – Ali Mar 07 '14 at 18:35
  • 1
    @Ali Then I'd suggest first fully reading both discussions linked in my answer. From one of those discussions, [here is a first draft implementation](https://stat.ethz.ch/pipermail/r-help/2001-October/015808.html) of what you're suggesting. – Josh O'Brien Mar 07 '14 at 18:43
16

This was my solution ...

edit: revised to deal with finding objects in namespaces. The code is already getting a little bit crufty, since I don't really understand the methods for manipulating/querying namespaces all that well, and since I was working by trial and error. Cleaner versions would be welcome. There are almost certainly other corner cases that will fail.

## return the names of the objects (from a vector of list of
## names of objects) that are functions and have debug flag set
isdebugged_safe <- function(x,ns=NULL)  {
    g <- if (is.null(ns)) get(x) else getFromNamespace(x,ns)
    is.function(g) && isdebugged(g)
}

which_debugged <- function(objnames,ns=NULL) {
    if (!length(objnames)) return(character(0))
    objnames[sapply(objnames,isdebugged_safe,ns=ns)]
}

all_debugged <- function(where=search(), show_empty=FALSE) {
    ss <- setNames(lapply(where,function(x) {
        which_debugged(ls(x,all.names=TRUE))
        }),gsub("package:","",where))
    ## find attached namespaces
    ## (is there a better way to test whether a 
    ##    namespace exists with a given name??)
    ns <- unlist(sapply(gsub("package:","",where),
                 function(x) {
                     if (inherits({n <- try(getNamespace(x),silent=TRUE)},
                         "try-error")) NULL else x
                 }))
    ss_ns <- setNames(lapply(ns,function(x) {
        objects <- ls(getNamespace(x),all.names=TRUE)
        which_debugged(objects,ns=x)
        }),ns)
    if (!show_empty) {
        ss <- ss[sapply(ss,length)>0]
        ss_ns <- ss_ns[sapply(ss_ns,length)>0]
    }
    ## drop overlaps
    for (i in names(ss))
        ss_ns[[i]] <- setdiff(ss_ns[[i]],ss[[i]])
    list(env=ss,ns=ss_ns)
}

undebug_all <- function(where=search()) {
    aa <- all_debugged(where)
    lapply(aa$env,undebug)
    ## now debug namespaces
    invisible(mapply(function(ns,fun) {
        undebug(getFromNamespace(fun,ns))
    },names(aa$ns),aa$ns))
}

The code is also posted at http://www.math.mcmaster.ca/bolker/R/misc/undebug_all.R

Example:

library(nlme)
debug(lme)
## define functions
source(url("http://www.math.mcmaster.ca/bolker/R/misc/undebug_all.R"))
undebug_all()
fm1 <- lme(distance ~ age, data = Orthodont) # from ?lme

In this case lme runs without entering the debugger.

Another, harder example:

library(limma)
source(url("http://www.math.mcmaster.ca/bolker/R/misc/undebug_all.R"))
debug(read.ilmn)
debug(limma:::.read.oneilmnfile)
all_debugged()
undebug_all()
read.ilmn()
read.ilmn("a.txt")

Note that read.ilmn() and read.ilmn("a.txt") appear to behave differently from a debugging standpoint (I don't understand why ...)

Ben Bolker
  • 211,554
  • 25
  • 370
  • 453
  • Thanks. I set a debug() on a function defined in a package, and run this code, but it did not undebug() that function. Could you please check and modify? – Ali Oct 09 '12 at 20:24
  • if you give me a reproducible example, I'll try to figure it out. I've added an example that *does* work to my answer above. – Ben Bolker Oct 09 '12 at 20:37
  • library(limma); debug(read.ilmn); Then run your program and run read.ilmn(someFile) – Ali Oct 09 '12 at 20:43
  • I modified the question and added a benchmark for your method. Please test it. – Ali Oct 09 '12 at 20:53
  • 1
    @BenBolker: The above mcmaster link to undebug_all does not work for me. – Dieter Menne Oct 10 '12 at 06:19
  • oops, fixed now. (Still haven't gotten through all the namespace issues, will update if/when I figure it out ...) – Ben Bolker Oct 10 '12 at 12:25
  • @BenBolker I have added your function in my .Rprofile. Today I got the following error while running it, with no arguments: Error in get(x, envir = ns, inherits = FALSE) : invalid first argument. Could you please resolve it? – Ali Oct 27 '12 at 18:35
  • How can I possibly resolve it without a reproducible example? Have you used `traceback()`, `options(error=recover)`, etc., to try to debug it yourself? – Ben Bolker Oct 28 '12 at 13:19
  • @BenBolker In some situation I should run the function two times to work. Running only one time remains some functions on debug mode, while the second run voids every debug. Do you have any idea? – Ali Nov 06 '12 at 11:24
  • It's really nearly impossible to debug these things without a reproducible example: sorry. – Ben Bolker Nov 06 '12 at 12:59
8

Here is one option, assuming that the functions you are debugging are in the workspace or global environment. Any particular environment can be specified so it is adaptable but this isn't going to be something that works for any function in all loaded packages in a single go.

First illustrate via a couple of functions in the global environment:

> bar <- function() {}
> foo <- function() {}

Use lsf.str() to return the functions in the workspace (for use later we unclass() this and convert it to a list):

> funlist <- as.list(unclass(lsf.str()))
> funlist
[[1]]
[1] "bar"

[[2]]
[1] "foo"

Next, produce an indicator for these functions as to whether they are debugged:

> debugged <- sapply(funlist, isdebugged)
> debugged
[1] FALSE FALSE

OK, so debug() one of the functions and rerun:

> debug(bar)
> 
> debugged <- sapply(funlist, isdebugged)
> debugged
[1]  TRUE FALSE

Finally sapply() over funlist functions that are debugged applying undebug() to them:

> sapply(funlist[debugged], undebug)
[[1]]
NULL

This of course could be encapsulated into a function

undebugFuns <- function() {
    funs <- unclass(lsf.str())
    dbg <- sapply(funs, isdebugged)
    if(isTRUE(any(dbg))) {
        writeLines(paste("Un-debugging:", funs[dbg]))
        sapply(funs[dbg], undebug)
    } else {
        writeLines(paste("Nothing to debug"))
    }
    invisible()
}

> debug(bar)
> undebugFuns()
Un-debugging: bar

One type of debugging not picked up by isdebugged() is that enacted via debugonce():

> debug(bar)
> isdebugged(bar)
[1] TRUE
> undebugFuns()
Un-debugging: bar
> debugonce(bar)
> isdebugged(bar)
[1] FALSE

Which just goes to make Josh's point in his Answer again.

Gavin Simpson
  • 170,508
  • 25
  • 396
  • 453
  • Thanks. I put a debug() on a function I was debugging defined in a package, and then run your undebugFuns(), but it printed "Nothing to debug". Could you please modify it to work for package functions as well? – Ali Oct 09 '12 at 20:26
  • 1
    See my comment below. It might have trouble working if you debug a hidden function ... – Ben Bolker Oct 09 '12 at 20:38
  • Nope, but you can. Read `?lsf.str` and work out how you pass the appropriate object to the `envir` argument of the function. I **did** say this would only work currently for the global environment, but tweaked the function to allow *you* to specify the environment looked in. – Gavin Simpson Oct 09 '12 at 20:38
  • library(limma); debug(read.ilmn); Then run your program and run read.ilmn(someFile) – Ali Oct 09 '12 at 20:44
  • Sorry for not answering earlier, I was doing some job. I have modified the question and added a benchmark. If you are interested, you are more than welcome to challenge it! – Ali Oct 09 '12 at 20:54
  • @AliSharifi Thanks for the update to the Question as that gives a concrete illustration of what you want to do. As you can see, whilst it might not have been important at the time, the extra information is crucial to understanding the problem and testing solutions to your interesting question. And welcome to SO by the way; I hadn't got round to saying that yet. – Gavin Simpson Oct 10 '12 at 08:20
  • @GavinSimpson Thanks for your kindest message. I am very hopeful that the first reliable undebug.all() function will be published soon here – Ali Oct 10 '12 at 09:00