12

I have a function such as this one :

fun <- function() {
  browser()
  is_browsing()
} 

I would like to know what the code of is_browsing() should be so it returns TRUE if the function is currently being browsed, so the console would look like this:

> fun()
Called from: fun()
Browse[1]> 
debug at #3: is_browsing()
Browse[2]> 
TRUE

However if I comment out the browser() line, or stop the browsing by pressing c, is_browsing() should return FALSE, like this:

> fun()
Called from: fun()
Browse[1]> c
FALSE

I have read about debuggingState() and isdebugged() but they don't seem to be of much help in my situation.

The real case FYI is about updating a plot or view as we browse, but only if we're browsing, if we're not I just want to plot/view once in the end, to spare resources.

moodymudskipper
  • 46,417
  • 11
  • 121
  • 167
  • 3
    I think you could get that information if you could examine the current `RCNTXT` structure `R_GlobalContext` (or some recent entry further up the context stack). I don't know if there are any user-level functions that have access to it, but if you can figure out a way to evaluate `R_GlobalContext->browserfinish` I think it would give you your answer. – user2554330 Aug 24 '20 at 00:10
  • Thanks to you, I've found some references relative to how to dig up R_GlobalContext, though I still have to understand what to do with them. Here's C code by Romain François : https://gist.github.com/romainfrancois/a5c078bbddfbac8533ae . And some Rcpp code by SO user eddi : https://stackoverflow.com/questions/19686892/passing-unevaluated-expressions-to-c-c – moodymudskipper Aug 24 '20 at 00:31

4 Answers4

7

Starting with the ideas in Romain's code, then copying across the RCNTXT struct (plus a couple of other structs it uses internally), I managed to get the C++ code to return the contents of R_GlobalContext.

The C++ code looks like this:

#include <Rcpp.h>
#include <Rinternals.h>
#include <setjmp.h>

extern void* R_GlobalContext ;

typedef struct {int tag, flags; union {int ival; double dval; SEXP sxpval;} u;
} R_bcstack_t;

typedef struct{jmp_buf jmpbuf; int mask_was_saved, saved_mask;} sigjmp_buf[1];

typedef struct RCNTXT {
    struct RCNTXT *nextcontext;
    int callflag;
    sigjmp_buf cjmpbuf;
    int cstacktop, evaldepth;
    SEXP promargs, callfun, sysparent, call, cloenv, conexit;
    void (*cend)(void *);
    void *cenddata;
    void *vmax;
    int intsusp, gcenabled, bcintactive;
    SEXP bcbody;
    void* bcpc;
    SEXP handlerstack, restartstack;
    struct RPRSTACK *prstack;
    R_bcstack_t *nodestack;
    R_bcstack_t *bcprottop;
    SEXP srcref;
    int browserfinish;
    SEXP returnValue;
    struct RCNTXT *jumptarget;
    int jumpmask;
} RCNTXT, *context;

// [[Rcpp::export]]
Rcpp::List get_RCNTXT(int level){
  RCNTXT* res = (RCNTXT*)R_GlobalContext;
  if (level > 1) res = res->nextcontext;
  return Rcpp::List::create(Rcpp::Named("call_flag") = res->callflag,
                            Rcpp::Named("c_stack_top") = res->cstacktop,
                            Rcpp::Named("call_depth") = res->evaldepth,
                            Rcpp::Named("call_fun") = res->callfun,
                            Rcpp::Named("sys_parent") = res->sysparent,
                            Rcpp::Named("call") = res->call,
                            Rcpp::Named("cloenv") = res->cloenv,
                            Rcpp::Named("conexit") = res->conexit,
                            Rcpp::Named("promargs") = res->promargs,
                            Rcpp::Named("intsusp") = res->intsusp,
                            Rcpp::Named("gcenabled") = res->gcenabled,
                            Rcpp::Named("bcintactive") = res->bcintactive,
                            Rcpp::Named("handlerstack") = res->handlerstack,
                            Rcpp::Named("restartstack") = res->restartstack,
                            Rcpp::Named("srcref") = res->srcref,
                            Rcpp::Named("browserfinish") = res->browserfinish);
}

That allows us to review the contents of R_Globalcontext:

get_RCNTXT(1)
#> $call_flag
#> [1] 12
#> 
#> $c_stack_top
#> [1] 4
#> 
#> $call_depth
#> [1] 1
#> 
#> $call_fun
#> function (level) 
#> .Call(<pointer: 0x0000000071282ff0>, level)
#> <bytecode: 0x00000174169448d0>
#> 
#> $sys_parent
#> <environment: R_GlobalEnv>
#> 
#> $call
#> get_RCNTXT(1)
#> 
#> $cloenv
#> <environment: 0x0000017416c52a08>
#> 
#> $conexit
#> NULL
#> 
#> $promargs
#> $promargs[[1]]
#> NULL
#> 
#> 
#> $intsusp
#> [1] 0
#> 
#> $gcenabled
#> [1] 1
#> 
#> $bcintactive
#> [1] 0
#> 
#> $handlerstack
#> NULL
#> 
#> $restartstack
#> NULL
#> 
#> $srcref
#> NULL
#> 
#> $browserfinish
#> [1] 0

Unfortunately, the browserfinish field just returns a 0 whether called from browser or not. However, if the get_RCNTXT function is called from the browser prompt, the restartstack shows that it has been called from browser. This allows the following R function to be defined once the C++ code has been sourced:

is_browser <- function()
{
  R <- get_RCNTXT(1)$restartstack
  if(is.null(R)) return(FALSE)
  class(R[[1]]) == "restart"
}

This allows the browser state to be queried from the command prompt:

is_browser()
#> [1] FALSE

> browser()
#> Called from: top level 
Browse[1]> is_browser()
#> [1] TRUE

However, this is not as useful as it seems. Firstly, it has the same effect as the following code in base R:

is_browser <- function() {
  !is.null(findRestart("browser"))
}

Secondly, when browser is called from inside a function, the code it runs is evaluated in its own context rather than the browser context, meaning is_browser will return FALSE. The C code for browser, (the actual function is called do_browser in main.c) writes a new context which is removed after the function exits, and this context is apparently not pointed at by any other structure for the duration of the function, so it is difficult to see how is_browser could be written to allow access to this context.

It therefore seems you would need to write a new implementation of browser to allow the browsed context to know that it was being browsed, and we really don't want to go there.

On the other hand, the browser context has full access to the browsed context, and since your end goal is to allow conditional code like plots to run only when in browser mode, I think the best solution is to use the browser itself to tell the browsed context that it is being browsed.

So for example, if you do:

browser_on <- function() {
  options(I_am_browsing = TRUE)
}

browser_off <- function() {
  options(I_am_browsing = FALSE)
}

is_browser <- function() {
  b <- getOption("I_am_browsing")
  if(is.null(b)) FALSE else b
}

You now have the option while browsing to conditionally run code that is protected by if(is_browser()).

Then if you have fun like this (with browser() commented out):

fun <- function() {
  #browser()
  if(is_browser()) plot(1:10)
  if(!is_browser()) "I didn't plot anything"
}

You will get:

fun()
#> [1] "I didn't plot anything"

But, if you run fun() from inside a browser, you get:

browser()
Called from: top level 
Browse[1]> browser_on()
Browse[1]> fun()

enter image description here

And it still works if browser is called inside fun:

fun <- function() {
  browser()
  if(is_browser()) plot(1:10)
  if(!is_browser()) "I didn't plot anything"
}

fun()
#> Called from: fun()
Browse[1]> browser_on()
Browse[1]> 
#> debug at #3: if (is_browser()) plot(1:10)
Browse[2]> 
#> debug at #3: plot(1:10)
Browse[2]> 
#> debug at #4: if (!is_browser()) "I didn't plot anything"
Browse[2]>

It's not a perfect solution because it requires an extra command while running in the browser, and it saves state via options. You will need to keep track of this if you call browser multiple times from the same scope. In particular, you shoud be careful to call browser_off() before exiting the browser if you are calling browser from the global environment.

Allan Cameron
  • 147,086
  • 7
  • 49
  • 87
  • 1
    Thanks Allan, I'd be happy to take a look at your C code. Your second solution won't cut it though, because I need this to work also when I call `browser()` and then leave the browser by calling `c` or pushing on the play button in RStudio. In that case I go through the browser call but `is_browing()` will return `FALSE` – moodymudskipper Aug 26 '20 at 17:50
  • 1
    @Moody_Mudskipper see my update. This hopefully gets you a bit closer. I'll continue to look for a complete solution – Allan Cameron Aug 26 '20 at 21:47
  • @Moody_Mudskipper I think I have a different low-tech solution that should work for your use case now. – Allan Cameron Aug 27 '20 at 12:19
  • Thanks Allan, but my main issue is really to be able to leave the browser by calling `c`, and having `is_browser()` change behavior right at this time, this doesn't work here – moodymudskipper Aug 27 '20 at 12:36
  • If we could hack the "c" shortcut so it has a side effect before execution is resumed we might make this work. I know when doing exotic experimentation with eval.parent(quote(browser()) I once displayed by accident the definition of `c` in the browser, but I don't remember how, if this "c" could be an active binding with a side effect at this point we could make it work. – moodymudskipper Aug 27 '20 at 12:40
  • @Moody_Mudskipper is there a particular reason why you can't do `browser_off()` before using `c`, or is it just too irritating? (If it is, that's a perfectly good reason - just want to know if it's more complicated than that) – Allan Cameron Aug 27 '20 at 12:43
  • It's my current workaround basically, but if the user forgets to do it their session might go bananas, and it's conceptually redundant so would be nice not to need it. – moodymudskipper Aug 27 '20 at 12:49
  • I think BrodieG made his own browser there for his package {unitizer}: https://github.com/brodieG/unitizer/blob/master/R/browse.R but it's not for the faint of heart ! – moodymudskipper Aug 27 '20 at 12:53
  • @Moody_Mudskipper the `c` in browser isn't a call. If you look at `ParseBrowser` in [main.c](https://github.com/wch/r-source/blob/a48c6bea1353ce9b79beee0022a19ceeae822162/src/main/main.c#L1159) you'll see that the browser input is simply screened for string literals including `c` and `cont` before being sent for evaluation. It's not really feasible to rewrite this. Would a single command to turn browser detection on from the browser be acceptable as long as it turned itself off automatically on browser exit? I think that may be possible. – Allan Cameron Aug 27 '20 at 14:58
  • If we find out what SET_RDEBUG(rho, 0) does, can't we just fetch whatever global value it changes? – moodymudskipper Aug 28 '20 at 10:17
  • @Moody_Mudskipper SET_RDEBUG(rho, 0) doesn't change a global value. It takes a SEXP object and writes 0 to that object's debug flag – Allan Cameron Aug 28 '20 at 12:34
  • @Moody_Mudskipper I have looked at this from every angle, and have even managed to be able to pass context pointers around so that existing contexts can be switched, but there's still nothing that actually sends a message when the browser closes. I have tried wrapping browser in a function with an `on.exit` declaration, but that alters the browser's behaviour. The only thing that kinda works is getting a pointer to the browsing context and testing to see if it has been overwritten with garbage after `gc` has picked it up, but of course this is error prone and very buggy. – Allan Cameron Aug 28 '20 at 15:01
  • @Moody_Mudskipper so I think the only possibility is telling the evaluated environment when you start browsing it and tell it again when you stop. Writing another browser that has general access to all R contexts and environments but that allows for messaging when it stops would be a huge undertaking. On the other hand, I think it would be a straightforward addition to make to R itself: a static flag that is turned on at the start of `do_browser` and turned off afterwards, plus an exported function that checks this flag. One for the R core team perhaps? – Allan Cameron Aug 28 '20 at 15:09
4

When you use the browser, the prompt shows you the browse level :
Browse[1], Browse[2],...

> browser()
Called from: top level 
Browse[1]> browser()
Called from: top level 
Browse[2]> 

This browse level is calculated in main.C by :

browselevel = countContexts(CTXT_BROWSER, 1);

Where CTXT_BROWSER is a constant defined in defn.h:

CTXT_BROWSER  = 16

You could use this internal countContexts function to get the is_browsing information you're looking for :

is_browsing.cpp

#include <Rcpp.h>
#include <R.h>
#include <Rinternals.h>
using namespace Rcpp;


// [[Rcpp::export]]
int is_browsing() {
  return Rf_countContexts(16,1);
}

Test :

library(Rcpp)
sourceCpp('is_browsing.cpp')
test <- function() {
  is_browsing()
}

test()
#> [1] 0

browser()
#> Called from: eval(expr, envir, enclos)

test()
#> [1] 1

Created on 2020-08-29 by the reprex package (v0.3.0)

Also working if browser is called within function :

test2 <- function() {
  browser()
   is_browsing()
 }
test2()
Called from: test2()
Browse[1]> n
debug à #3 :is_browsing()
Browse[2]> n
[1] 1

If you wanted a TRUE / FALSE return, the Rcpp code would be:

#include <Rcpp.h>
#include <R.h>
#include <Rinternals.h>

// [[Rcpp::export]]
Rcpp::LogicalVector is_browsing() { 
  return Rf_countContexts(16,1) > 0;
}
moodymudskipper
  • 46,417
  • 11
  • 121
  • 167
Waldi
  • 39,242
  • 6
  • 30
  • 78
  • @Allan, thanks for your feedback, I tested & understand your comment... doesn't work if browser() is called from within the function... – Waldi Aug 29 '20 at 12:07
  • @Allan, actually, I thinks it works as expected : I got a 0 back because I pressed 'continue', ie cancelled the browser... Could you elaborate on what the problem is? Thanks for your feedback – Waldi Aug 29 '20 at 13:28
  • 2
    Actually @Waldi, having tested this now I think that you've got this. I'm surprised that the browser context is detected when called from inside the function. This has been driving me nuts for days - very impressed you found this. Might I suggest for completeness you get your Rcpp code to return a `LogicalVector` - I have taken the liberty of appending this to your answer, but feel free to remove it. – Allan Cameron Aug 29 '20 at 15:55
  • 2
    Thanks @Allan for the edit : boolean answers exactly the question for `is_browsing`, but I left browserlevel as output because it might be an useful extra information. – Waldi Aug 29 '20 at 17:56
  • 1
    This seems to work indeed! I've implemented it in my package and I only encountered expected behaviour. It also works, unsurprisingly, if debugonce is called on the function. Thanks a bunch Waldi, and you too Allan for all the effort, I hope we all learnt new things. I'll award the bounty in the end, to give more exposure. – moodymudskipper Aug 30 '20 at 15:43
  • 1
    Congratulations on the big bounty Waldi - Richly deserved. And thanks for the question @Moody_Mudskipper - a great learning opportunity for me too. – Allan Cameron Aug 31 '20 at 21:22
  • 1
    I changed RInternals to Rinternals (no capital I), some systems are case sensitive and it was quite hard to debug! – moodymudskipper Sep 01 '20 at 01:41
  • 1
    Thanks Moody_Mudskipper for spotting this tricky last bit and for the addictive question, glad I could help. Thanks also to @Allan for his insights in R wizardry : his thoughts were an excellent starting point for lateral thinking and a bit of luck ;) – Waldi Sep 01 '20 at 04:55
2

It is described in the documentation for browser, browseText and browseCondition:

Instead of just calling browser(), call it and set the argument for browseText or browseCondition.

browser(text="foo")

Then you can check for the condition to determine if browser is running:

is_browsing<-function(n)
{
    result = FALSE
 result = tryCatch({
    browserText(n=1)
     result = TRUE
}, warning = function(w) {
    #warning-handler-code
}, error = function(e) {
   # error-handler-code
}, finally = {

    #code you always want to execute
 })
   return (result)
}

The n=1 in browseText refers to which context to retrieve the value from.

If you are not browsing, then the call to browseText() throws an error - > This is why we wrapped it in a try catch. So if an error is thrown we know that browser is not running. If no error is thrown, result is set to true, and you can run your own custom logic.

To test, try:

browser(text="foo")
if(isTRUE(is_browsing())){
    print("is browsing!!!")
}else{
    print("is not browsing!!!");
}

Then comment out the call to browser(text="foo"), and see the difference.

EDIT: If you cannot pass an argument to browser() for any reason, you can use debug instead:

https://www.rdocumentation.org/packages/base/versions/3.6.2/topics/debug

Or you can set the value using some other external debugger.

Rahul Iyer
  • 19,924
  • 21
  • 96
  • 190
  • I can reproduce your last result but I can't wrap it into a function and get the expected output using my code (replacing `bowser()`by `browser("foo")`) – moodymudskipper Aug 26 '20 at 14:26
  • @Moody_Mudskipper can you explain in more detail what the problem is? – Rahul Iyer Aug 26 '20 at 15:54
  • Do you mean that you don't understand the example in my question ? Or do you want more details about my real life usecase ? – moodymudskipper Aug 26 '20 at 17:53
  • @Moody_Mudskipper I would like to understand why you are unable to use the solution I described. Can you provide details why you are unable to do so ? – Rahul Iyer Aug 26 '20 at 17:57
  • Your second call will return "is browing" only if it's typed in the debugger. If you wrap your solution in a function, or even between `{}`, it won't work anymore. I need a definition of `is_browsing()` that work as described when I call `fun()` as defined in my question. – moodymudskipper Aug 26 '20 at 18:16
  • 1
    @Moody_Mudskipper ok, I now I understand – Rahul Iyer Aug 26 '20 at 18:38
0

This is not 100% what you are looking for, but perhaps you get an idea how to solve your problem? I am not familiar with C / C++ R-basics, but perhaps you can kind of overload base::browser()?

I hope this helps:

list.parent_env <- function() {
  ll <- list()
  n <- 1
  while (!environmentName(.GlobalEnv) %in% 
         environmentName(parent.frame(n))) {
    ll <- c(ll, parent.frame(n))
    n <- n + 1
  }
  return(ll)
}

listofenv2names <- function(env_list) {
  names <- unlist(lapply(c(1:length(env_list)), function(i) {
    attributes(env_list[[i]])$name
  }))
  return(names)
}

# https://stackoverflow.com/a/23891089/5784831
mybrowser <- function() {
  e <- parent.frame()
  attr(e, "name") <- "mybrowser_env"
  assign("mybrowser_env", 1,
         envir = parent.frame(),
         inherits = FALSE, immediate = TRUE)
  return(eval(quote(browser()), parent.frame()))
}

is_browsing <- function() {
  env_list <- list.parent_env()
  r <- "mybrowser_env" %in% listofenv2names(env_list)
  print(r)
  return(r)
}

subsubfun <- function() {
  print("subsubfun")
  b <- 2
  is_browsing()
  return(NULL)
}

subfun <- function() {
  print("subfun")
  a <- 1
  is_browsing()
  subsubfun()
  return(NULL)
}

fun1 <- function() {
  print("fun1")
  is_browsing()
  mybrowser()
  for (i in 1:10) {
    is_browsing()
  }
  is_browsing()
  subfun()
  
  return(NULL)
} 

fun2 <- function() {
  print("fun2")
  is_browsing()
  return(NULL)
}

fun1()
fun2()

Output looks good:

[1] "fun1"
[1] FALSE
Called from: eval(quote(browser()), parent.frame())
Browse[1]> c
[1] TRUE
[1] "subfun"
[1] TRUE
[1] "subsubfun"
[1] TRUE
[1] "fun2"
[1] FALSE
Christoph
  • 6,841
  • 4
  • 37
  • 89
  • Thanks Christoph, but when I call f1(), and type "c", it messages TRUE, while I've quitted the browser – moodymudskipper Aug 28 '20 at 18:48
  • 1
    additionally, there is a strange issue when calling browser this way, I've tried it not long ago, and you cannot browse more than 1 call if the body contains loops : https://r.789695.n4.nabble.com/browser-cannot-be-called-consistently-from-another-environment-td4765348.html – moodymudskipper Aug 28 '20 at 18:50
  • @Moody_Mudskipper To your first point: I could not figure out, how the console and "c" interacts with R. Do you know this? To me it is clear, that my approach does not work in combination with "c" because my environemt variable (set by `mybrowser()`) which I use to detect the active browser is not removed by "c". – Christoph Aug 30 '20 at 13:00
  • @Moody_Mudskipper To your second point: I can reproduce the error, really strange. To me this looks like a bug and it looks like there is no answer yet... Perhaps this was a good question for SO to attract some attention? (Perhaps this has something to with `showClass("for")` resulting in `Class "for" [package "methods"], No Slots, prototype of class "for", Extends: "language"`. Perhaps this has an impact on the environment?) – Christoph Aug 30 '20 at 13:13
  • 1
    "Do you know this?" You can find the C code here: https://github.com/wch/r-source/blob/a48c6bea1353ce9b79beee0022a19ceeae822162/src/main/main.c#L1159, as dug out by Allan – moodymudskipper Aug 30 '20 at 14:11
  • 1
    I don't know if asking on SO will do much, I've asked r-devel, hence my nabble link, but I'm not sure if it's a bug or if it's our hack that is on undocumented territory. If I have no answer in some time I'll ask back. – moodymudskipper Aug 30 '20 at 14:13