Skip to content

Commit

Permalink
execute() R function don't always return success (#66)
Browse files Browse the repository at this point in the history
* execute return error_reply when error happens

* execute also sending "execution_result" structures
  • Loading branch information
romainfrancois authored Dec 7, 2023
1 parent 0dd152e commit 34547a8
Show file tree
Hide file tree
Showing 5 changed files with 44 additions and 48 deletions.
23 changes: 15 additions & 8 deletions share/jupyter/kernels/xr/resources/execute.R
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
last_plot <- NULL
last_visible <- TRUE
last_error <- NULL

handle_message <- function(msg) {
publish_stream("stderr", conditionMessage(msg))
Expand Down Expand Up @@ -55,7 +56,7 @@ handle_error <- function(e) {
cli::col_red("--- Traceback"),
format(e$trace)
)
publish_execution_error(ename = "ERROR", evalue = "", trace_back)
last_error <<- structure(list(ename = "ERROR", evalue = "", trace_back), class = "error_reply")
} else {
sys_calls <- sys.calls()
sys_calls <- head(tail(sys_calls, -16), -3)
Expand All @@ -69,7 +70,7 @@ handle_error <- function(e) {
cli::col_red("--- Traceback (most recent call last)"),
stack
)
publish_execution_error(ename = "ERROR", evalue = evalue, trace_back)
last_error <<- structure(list(ename = "ERROR", evalue = evalue, trace_back), class = "error_reply")
}
}

Expand Down Expand Up @@ -125,16 +126,17 @@ send_plot <- function(plot) {
}

execute <- function(code, execution_counter, silent = FALSE) {
last_error <<- NULL

parsed <- tryCatch(
parse(text = code),
error = function(e) {
msg <- paste(conditionMessage(e), collapse = "\n")
publish_execution_error("PARSE ERROR", msg)
e
last_error <<- structure(list(ename = "PARSE ERROR", evalue = msg), class = "error_reply")
}
)
if (inherits(parsed, "error")) return()

if (!is.null(last_error)) return(last_error)
output_handler <- if (silent) {
evaluate::new_output_handler()
} else {
Expand All @@ -147,7 +149,7 @@ execute <- function(code, execution_counter, silent = FALSE) {
value = handle_value(execution_counter)
)
}

last_plot <<- NULL
last_visible <<- FALSE

Expand All @@ -159,10 +161,12 @@ execute <- function(code, execution_counter, silent = FALSE) {
stop_on_error = 1L,
filename = filename
)
if (!is.null(last_error)) return(last_error)

if (!silent && !is.null(last_plot)) {
tryCatch(send_plot(last_plot), error = handle_error)
}
if (!is.null(last_error)) return(last_error)

if (isTRUE(last_visible)) {
obj <- .Last.value
Expand All @@ -175,7 +179,10 @@ execute <- function(code, execution_counter, silent = FALSE) {
}

bundle <- IRdisplay::prepare_mimebundle(obj, mimetypes = mimetypes)
publish_execution_result(execution_counter, bundle$data, bundle$metadata)

structure(class = "execution_result",
list(toJSON(bundle$data), toJSON(bundle$metadata))
)
}

}
9 changes: 0 additions & 9 deletions share/jupyter/kernels/xr/resources/routines.R
Original file line number Diff line number Diff line change
@@ -1,12 +1,3 @@

publish_execution_error <- function(ename, evalue, trace_back = character()) {
.Call("xeusr_publish_execution_error", ename, evalue, trace_back, PACKAGE = "(embedding)")
}

publish_execution_result <- function(execution_count, data, metadata = NULL) {
.Call("xeusr_publish_execution_result", as.integer(execution_count), jsonlite::toJSON(data), jsonlite::toJSON(metadata), PACKAGE = "(embedding)")
}

publish_stream <- function(name, text) {
.Call("xeusr_publish_stream", name, text, PACKAGE = "(embedding)")
}
Expand Down
29 changes: 0 additions & 29 deletions src/routines.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -26,33 +26,6 @@ SEXP publish_stream(SEXP name_, SEXP text_) {
return R_NilValue;
}

SEXP publish_execution_error(SEXP ename_, SEXP evalue_, SEXP trace_back_) {
auto ename = CHAR(STRING_ELT(ename_, 0));
auto evalue = CHAR(STRING_ELT(evalue_, 0));

auto n = XLENGTH(trace_back_);
std::vector<std::string> trace_back(n);
for (decltype(n) i = 0; i < n; i++) {
trace_back[i] = CHAR(STRING_ELT(trace_back_, i));
}

xeus_r::get_interpreter()->publish_execution_error(ename, evalue, std::move(trace_back));

return R_NilValue;
}

SEXP publish_execution_result(SEXP execution_count_, SEXP data_, SEXP metadata_) {
int execution_count = INTEGER_ELT(execution_count_, 0);
auto data = nl::json::parse(CHAR(STRING_ELT(data_, 0)));
auto metadata = nl::json::parse(CHAR(STRING_ELT(metadata_, 0)));

xeus_r::get_interpreter()->publish_execution_result(
execution_count, std::move(data), std::move(metadata)
);

return R_NilValue;
}

SEXP display_data(SEXP js_data, SEXP js_metadata){
auto data = nl::json::parse(CHAR(STRING_ELT(js_data, 0)));
auto metadata = nl::json::parse(CHAR(STRING_ELT(js_metadata, 0)));
Expand Down Expand Up @@ -107,8 +80,6 @@ void register_r_routines() {
static const R_CallMethodDef callMethods[] = {
{"xeusr_kernel_info_request" , (DL_FUNC) &routines::kernel_info_request , 0},
{"xeusr_publish_stream" , (DL_FUNC) &routines::publish_stream , 2},
{"xeusr_publish_execution_error" , (DL_FUNC) &routines::publish_execution_error , 3},
{"xeusr_publish_execution_result", (DL_FUNC) &routines::publish_execution_result, 3},
{"xeusr_display_data" , (DL_FUNC) &routines::display_data , 2},
{"xeusr_update_display_data" , (DL_FUNC) &routines::update_display_data , 2},
{"xeusr_clear_output" , (DL_FUNC) &routines::clear_output , 1},
Expand Down
29 changes: 28 additions & 1 deletion src/xinterpreter.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -89,8 +89,35 @@ nl::json interpreter::execute_request_impl(int execution_counter, // Typicall
SEXP silent_ = PROTECT(Rf_ScalarLogical(silent));

SEXP result = r::invoke_xeusr_fn("execute", code_, execution_counter_, silent_);
UNPROTECT(3);

if (Rf_inherits(result, "error_reply")) {
std::string evalue = CHAR(STRING_ELT(VECTOR_ELT(result, 0), 0));
std::string ename = CHAR(STRING_ELT(VECTOR_ELT(result, 1), 0));

std::vector<std::string> trace_back;
if (XLENGTH(result) > 2) {
SEXP trace_back_ = VECTOR_ELT(result, 2);
auto n = XLENGTH(trace_back_);
for (decltype(n) i = 0; i < n; i++) {
trace_back.push_back(CHAR(STRING_ELT(trace_back_, i)));
}
}

publish_execution_error(evalue, ename, trace_back);

UNPROTECT(3);
return xeus::create_error_reply(evalue, ename, std::move(trace_back));
}

if (Rf_inherits(result, "execution_result")) {
SEXP data_ = VECTOR_ELT(result, 0);
SEXP metadata_ = VECTOR_ELT(result, 1);
auto data = nl::json::parse(CHAR(STRING_ELT(data_, 0)));
auto metadata = nl::json::parse(CHAR(STRING_ELT(metadata_, 0)));
publish_execution_result(execution_counter, data, metadata);
}

UNPROTECT(3);
return xeus::create_successful_reply(/*payload, user_expressions*/);
}

Expand Down
2 changes: 1 addition & 1 deletion test/test_xr_kernel.py
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ class KernelTests(jupyter_kernel_test.KernelTests):

# code_page_something = "?cat"
# code_clear_output = "clear_output()"

code_generate_error = "stop('ouch')"
code_inspect_sample = "print"

complete_code_samples = ["fun()", "1 + 2", "a %>% b", "a |> b()", "a |> b(c = _)"]
Expand Down

0 comments on commit 34547a8

Please sign in to comment.