diff --git a/NEWS.md b/NEWS.md index c56e753d3..0648afa1d 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # reticulate (development version) +- Python background threads can now run in parallel with + the R session (#1641). + - Fixed error when importing a module named `config` (#1628) - `conda_run2()` is now exported (#1637, contributed by @dramanica) @@ -9,14 +12,14 @@ - Python Exceptions converted to R conditions are now R lists instead of R environments, for compatability with {rlang} and {purrr}. (tidyverse/purrr#1104, r-lib/rlang#1664, #1617) - + - Internal updates for NumPy 2.0 (#1621) - Added support for converting NumPy StringDType arrays to R character arrays. (#1623) - Internal updates for compliance with R's upcoming formalized C API. (#1625) -- Fixed an issue where attempting to convert a NumPy array with a non-simple +- Fixed an issue where attempting to convert a NumPy array with a non-simple dtype to R would signal an error. (#1613, fixed in #1614). # reticulate 1.37.0 diff --git a/R/RcppExports.R b/R/RcppExports.R index e6eb3dbaf..6c32be5f3 100644 --- a/R/RcppExports.R +++ b/R/RcppExports.R @@ -365,6 +365,10 @@ py_iterate <- function(x, f, simplify = TRUE) { .Call(`_reticulate_py_iterate`, x, f, simplify) } +py_allow_threads_impl <- function(allow = TRUE) { + .Call(`_reticulate_py_allow_threads_impl`, allow) +} + readline <- function(prompt) { .Call(`_reticulate_readline`, prompt) } diff --git a/R/package.R b/R/package.R index 7e501ef86..dc6c3cb60 100644 --- a/R/package.R +++ b/R/package.R @@ -255,6 +255,14 @@ initialize_python <- function(required_module = NULL, use_environment = NULL) { # https://github.com/rstudio/reticulate/issues/586 py_set_qt_qpa_platform_plugin_path(config) + if (was_python_initialized_by_reticulate()) { + allow_threads <- Sys.getenv("RETICULATE_ALLOW_THREADS", "true") + allow_threads <- tolower(allow_threads) %in% c("true", "1", "yes") + if (allow_threads) { + py_allow_threads_impl(TRUE) + } + } + # return config config } diff --git a/R/threads.R b/R/threads.R new file mode 100644 index 000000000..60f2bac2c --- /dev/null +++ b/R/threads.R @@ -0,0 +1,19 @@ + + +py_allow_threads <- function(allow = TRUE) { + if (allow) { + reticulate_ns <- environment(sys.function()) + for (f in sys.frames()) { + if (identical(parent.env(f), reticulate_ns) && + !identical(f, environment())) + # Can't release the gil as unlocked while we're holding it + # elsewhere on the callstack. + stop("Python threads can only be unblocked from a top-level reticulate call") + } + } + + if (!was_python_initialized_by_reticulate()) + stop("Can't safely unblock threads when R is running embedded") + + invisible(py_allow_threads_impl(allow)) +} diff --git a/inst/python/rpytools/run.py b/inst/python/rpytools/run.py new file mode 100644 index 000000000..318352539 --- /dev/null +++ b/inst/python/rpytools/run.py @@ -0,0 +1,50 @@ +import sys +import os + + +def run_file(path): + with open(path, "r") as file: + file_content = file.read() + + d = sys.modules["__main__"].__dict__ + + exec(file_content, d, d) + + +class RunMainScriptContext: + def __init__(self, path, args): + self.path = path + self.args = tuple(args) + + def __enter__(self): + sys.path.insert(0, os.path.dirname(self.path)) + + self._orig_sys_argv = sys.argv + sys.argv = [self.path] + list(self.args) + + def __exit__(self, *_): + # try restore sys.path + try: + sys.path.remove(os.path.dirname(self.path)) + except ValueError: + pass + # restore sys.argv if it's been unmodified + # otherwise, leave it as-is. + set_argv = [self.path] + list(self.args) + if sys.argv == set_argv: + sys.argv = self._orig_sys_argv + + +def _run_file_on_thread(path, args=None): + + import _thread + + _thread.start_new_thread(run_file, (path, )) + + +def _launch_lsp_server_on_thread(path, args): + # for now, leave sys.argv and sys.path permanently modified. + # Later, revisit if it's desirable/safe to restore after the initial + # lsp event loop startup. + RunMainScriptContext(path, args).__enter__() + _run_file_on_thread(path) diff --git a/src/RcppExports.cpp b/src/RcppExports.cpp index 3750cd3c1..7c1affef1 100644 --- a/src/RcppExports.cpp +++ b/src/RcppExports.cpp @@ -812,6 +812,17 @@ BEGIN_RCPP return rcpp_result_gen; END_RCPP } +// py_allow_threads_impl +bool py_allow_threads_impl(bool allow); +RcppExport SEXP _reticulate_py_allow_threads_impl(SEXP allowSEXP) { +BEGIN_RCPP + Rcpp::RObject rcpp_result_gen; + Rcpp::RNGScope rcpp_rngScope_gen; + Rcpp::traits::input_parameter< bool >::type allow(allowSEXP); + rcpp_result_gen = Rcpp::wrap(py_allow_threads_impl(allow)); + return rcpp_result_gen; +END_RCPP +} // readline SEXP readline(const std::string& prompt); RcppExport SEXP _reticulate_readline(SEXP promptSEXP) { @@ -895,6 +906,7 @@ static const R_CallMethodDef CallEntries[] = { {"_reticulate_as_iterator", (DL_FUNC) &_reticulate_as_iterator, 1}, {"_reticulate_py_iter_next", (DL_FUNC) &_reticulate_py_iter_next, 2}, {"_reticulate_py_iterate", (DL_FUNC) &_reticulate_py_iterate, 3}, + {"_reticulate_py_allow_threads_impl", (DL_FUNC) &_reticulate_py_allow_threads_impl, 1}, {"_reticulate_readline", (DL_FUNC) &_reticulate_readline, 1}, {NULL, NULL, 0} }; diff --git a/src/libpython.cpp b/src/libpython.cpp index 1da7d044a..92d2c421a 100644 --- a/src/libpython.cpp +++ b/src/libpython.cpp @@ -293,6 +293,8 @@ bool LibPython::loadSymbols(bool python3, std::string* pError) LOAD_PYTHON_SYMBOL(PyGILState_Ensure) LOAD_PYTHON_SYMBOL(PyGILState_Release) LOAD_PYTHON_SYMBOL(PyThreadState_Next) + LOAD_PYTHON_SYMBOL(PyEval_SaveThread) + LOAD_PYTHON_SYMBOL(PyEval_RestoreThread) LOAD_PYTHON_SYMBOL(PyObject_CallMethod) LOAD_PYTHON_SYMBOL(PySequence_GetItem) LOAD_PYTHON_SYMBOL(PyObject_IsTrue) diff --git a/src/libpython.h b/src/libpython.h index b162c3af3..812ec5d3b 100644 --- a/src/libpython.h +++ b/src/libpython.h @@ -790,6 +790,8 @@ LIBPYTHON_EXTERN PyThreadState* (*PyGILState_GetThisThreadState)(void); LIBPYTHON_EXTERN PyGILState_STATE (*PyGILState_Ensure)(void); LIBPYTHON_EXTERN void (*PyGILState_Release)(PyGILState_STATE); LIBPYTHON_EXTERN PyThreadState* (*PyThreadState_Next)(PyThreadState*); +LIBPYTHON_EXTERN PyThreadState* (*PyEval_SaveThread)(); +LIBPYTHON_EXTERN void (*PyEval_RestoreThread)(PyThreadState*); /* End PyFrameObject */ diff --git a/src/python.cpp b/src/python.cpp index 1c00d4ed0..bc97ebaa6 100644 --- a/src/python.cpp +++ b/src/python.cpp @@ -31,6 +31,13 @@ int _Py_Check(PyObject* o) { return 0; } + +PyGILState_STATE _initialize_python_and_PyGILState_Ensure() { + Function initialize_python = Environment::namespace_env("reticulate")["ensure_python_initialized"]; + initialize_python(); + return PyGILState_Ensure(); +} + SEXP sym_pyobj; SEXP sym_py_object; SEXP sym_simple; @@ -50,6 +57,7 @@ void reticulate_init(DllInfo *dll) { // before python is initialized, make these symbols safe to call (always return false) PyIter_Check = &_Py_Check; PyCallable_Check = &_Py_Check; + PyGILState_Ensure = &_initialize_python_and_PyGILState_Ensure; sym_py_object = Rf_install("py_object"); sym_simple = Rf_install("simple"); @@ -564,12 +572,6 @@ bool was_python_initialized_by_reticulate() { return s_was_python_initialized_by_reticulate; } -static inline -void ensure_python_initialized() { - if (s_is_python_initialized) return; - Function initialize = Environment::namespace_env("reticulate")["ensure_python_initialized"]; - initialize(); -} @@ -938,8 +940,10 @@ SEXP py_fetch_error(bool maybe_reuse_cached_r_trace) { // [[Rcpp::export]] SEXP py_flush_output() { - if(s_is_python_initialized) + if(s_is_python_initialized) { + GILScope _gil; flush_std_buffers(); + } return R_NilValue; } @@ -1035,6 +1039,7 @@ std::string conditionMessage_from_py_exception(PyObject* exc) { // [[Rcpp::export]] std::string conditionMessage_from_py_exception(PyObjectRef exc) { + GILScope _gil; return conditionMessage_from_py_exception(exc.get()); } @@ -1174,7 +1179,7 @@ bool py_is_callable(PyObject* x) { // [[Rcpp::export]] PyObjectRef py_none_impl() { - ensure_python_initialized(); + GILScope _gil; Py_IncRef(Py_None); return py_ref(Py_None, false); } @@ -1183,8 +1188,8 @@ PyObjectRef py_none_impl() { bool py_is_callable(PyObjectRef x) { if (x.is_null_xptr()) return false; - else - return py_is_callable(x.get()); + GILScope _gil; + return py_is_callable(x.get()); } // caches np.nditer function so we don't need to obtain it everytime we want to @@ -1262,6 +1267,7 @@ bool is_py_object(SEXP x) { // if we fail to convert, this creates a new reference to x // (i.e, caller should call Py_DecRef() / PyObjectPtr.detach() for any refs caller created) SEXP py_to_r(PyObject* x, bool convert) { + GILScope _gil; if(!convert) { Py_IncRef(x); return py_ref(x, convert); @@ -1291,6 +1297,7 @@ SEXP py_to_r_cpp(SEXP x) { // return x unmodified if(!simple && ref.convert()) return x; + GILScope _gil; // if simple = true, call py_to_r_cpp(PyObject) to (try to) simplify // if convert = false, call py_to_r_cpp(PyObject) to get a new ref with convert = true SEXP ret = py_to_r_cpp(ref.get(), /*convert =*/ true, simple); @@ -1755,7 +1762,7 @@ void GrowList(SEXP args_list, SEXP tag, SEXP dflt) { // [[Rcpp::export]] SEXP py_get_formals(PyObjectRef callable) { - + GILScope _gil; PyObject* callable_ = callable.get(); static PyObject *inspect_module = NULL; @@ -2037,7 +2044,7 @@ PyObject* r_to_py(RObject x, bool convert) { // will have an active reference count on it) // the convert arg is only applicable to R functions that will being wrapped in python functions. PyObject* r_to_py_cpp(RObject x, bool convert) { - ensure_python_initialized(); + GILScope _gil; int type = x.sexp_type(); SEXP sexp = x.get__(); @@ -2263,9 +2270,25 @@ PyObject* r_to_py_cpp(RObject x, bool convert) { // [[Rcpp::export]] PyObjectRef r_to_py_impl(RObject object, bool convert) { + GILScope _gil; return py_ref(r_to_py_cpp(object, convert), convert); } +class AllowPyThreadsScope +{ +private: + PyThreadState *_save; + +public: + AllowPyThreadsScope() { + _save = PyEval_SaveThread(); + } + + ~AllowPyThreadsScope() { + PyEval_RestoreThread(_save); + } +}; + // custom module used for calling R functions from python wrappers extern "C" PyObject* call_r_function(PyObject *self, PyObject* args, PyObject* keywords) @@ -2345,7 +2368,11 @@ extern "C" PyObject* call_r_function(PyObject *self, PyObject* args, PyObject* k // it would already be protected by it's inclusion in the R callstack frames, // but rchk flags it anyway, and so ... RObject env(current_env()); - Rcpp::List result(Rf_eval(call_r_func_call, env)); + Rcpp::List result; + { + AllowPyThreadsScope _allow_threads; + result = Rf_eval(call_r_func_call, env); + } // result is either // (return_value, NULL) or @@ -2726,7 +2753,7 @@ SEXP main_process_python_info_unix() { if (PyGILState_Release == NULL) loadSymbol(pLib, "PyGILState_Release", (void**)&PyGILState_Release); - GILScope scope(true); + GILScope scope; // read Python program path std::string python_path; @@ -2774,6 +2801,7 @@ SEXP main_process_python_info() { // [[Rcpp::export]] void py_clear_error() { + GILScope _gil; DBG("Clearing Python errors."); PyErr_Clear(); } @@ -2804,7 +2832,7 @@ void py_initialize(const std::string& python, if (Py_IsInitialized()) { // if R is embedded in a python environment, rpycall has to be loaded as a regular // module. - GILScope scope(true); + GILScope scope; PyImport_AddModule("rpycall"); PyDict_SetItemString(PyImport_GetModuleDict(), "rpycall", initializeRPYCall()); @@ -2859,7 +2887,7 @@ void py_initialize(const std::string& python, s_main_thread = tthread::this_thread::get_id(); s_is_python_initialized = true; - GILScope scope; + GILScope _gil; // initialize type objects initialize_type_objects(is_python3()); @@ -2900,12 +2928,14 @@ void py_finalize() { // [[Rcpp::export]] bool py_is_none(PyObjectRef x) { + GILScope _gil; return py_is_none(x.get()); } // [[Rcpp::export]] bool py_compare_impl(PyObjectRef a, PyObjectRef b, const std::string& op) { + GILScope _gil; int opcode; if (op == "==") opcode = Py_EQ; @@ -2932,7 +2962,7 @@ bool py_compare_impl(PyObjectRef a, PyObjectRef b, const std::string& op) { // [[Rcpp::export]] CharacterVector py_str_impl(PyObjectRef x) { - + GILScope _gil; if (!is_python_str(x)) { PyObjectPtr str(PyObject_Str(x)); @@ -2952,6 +2982,7 @@ CharacterVector py_str_impl(PyObjectRef x) { //' @rdname py_str // [[Rcpp::export]] SEXP py_repr(PyObjectRef object) { + GILScope _gil; if(py_is_null_xptr(object)) return CharacterVector::create(String("")); @@ -2974,6 +3005,7 @@ void py_print(PyObjectRef x) { // [[Rcpp::export]] bool py_is_function(PyObjectRef x) { + GILScope _gil; return PyFunction_Check(x) == 1; } @@ -2988,6 +3020,7 @@ bool py_numpy_available_impl() { // [[Rcpp::export]] std::vector py_list_attributes_impl(PyObjectRef x) { + GILScope _gil; PyObject* x_ = x.get(); // ensure python initialized, module proxy resolved std::vector attributes; PyObjectPtr attrs(PyObject_Dir(x_)); @@ -3022,6 +3055,7 @@ PyObjectRef py_new_ref(PyObjectRef x, SEXP convert) { ? x.convert() : ((bool) Rf_asLogical(convert)); + GILScope _gil; PyObject* pyobj = x.get(); Py_IncRef(pyobj); return py_ref(pyobj, convert_); @@ -3041,6 +3075,7 @@ PyObjectRef py_new_ref(PyObjectRef x, SEXP convert) { //' @export // [[Rcpp::export]] bool py_has_attr(PyObjectRef x, const std::string& name) { + GILScope _gil; PyObject* x_ = x.get(); // ensure python initialized, module proxy resolved return PyObject_HasAttrString(x_, name.c_str()); } @@ -3060,6 +3095,7 @@ PyObjectRef py_get_attr(PyObjectRef x, const std::string& name, bool silent = false) { + GILScope _gil; PyObject* x_ = x.get(); // ensure python initialized, module proxy resolved PyObject *attr = PyObject_GetAttrString(x_, name.c_str()); // new ref @@ -3088,6 +3124,7 @@ PyObjectRef py_set_attr(PyObjectRef x, const std::string& name, RObject value) { + GILScope _gil; PyObject* x_ = x.get(); // ensure python initialized, module proxy resolved PyObjectPtr value_(r_to_py(value, x.convert())); int res = PyObject_SetAttrString(x_, name.c_str(), value_); @@ -3105,6 +3142,7 @@ PyObjectRef py_set_attr(PyObjectRef x, // [[Rcpp::export(invisible = true)]] PyObjectRef py_del_attr(PyObjectRef x, const std::string& name) { + GILScope _gil; PyObject* x_ = x.get(); // ensure python initialized, module proxy resolved int res = PyObject_SetAttrString(x_, name.c_str(), NULL); if (res != 0) @@ -3117,6 +3155,7 @@ PyObjectRef py_del_attr(PyObjectRef x, const std::string& name) // [[Rcpp::export]] PyObjectRef py_get_item(PyObjectRef x, RObject key, bool silent = false) { + GILScope _gil; PyObject* x_ = x.get(); // ensure python initialized, module proxy resolved PyObjectPtr py_key(r_to_py(key, false)); PyObject *item = PyObject_GetItem(x_, py_key); @@ -3135,6 +3174,7 @@ PyObjectRef py_get_item(PyObjectRef x, RObject key, bool silent = false) // [[Rcpp::export(invisible = true)]] PyObjectRef py_set_item(PyObjectRef x, RObject key, RObject value) { + GILScope _gil; PyObject* x_ = x.get(); // ensure python initialized, module proxy resolved PyObjectPtr py_key(r_to_py(key, true)); PyObjectPtr py_val(r_to_py(value, true)); @@ -3149,6 +3189,7 @@ PyObjectRef py_set_item(PyObjectRef x, RObject key, RObject value) //' @export // [[Rcpp::export(invisible = true)]] PyObjectRef py_del_item(PyObjectRef x, RObject key) { + GILScope _gil; PyObject* x_ = x.get(); // ensure python initialized, module proxy resolved PyObjectPtr pyKey(r_to_py(key, true)); int res = PyObject_DelItem(x_, pyKey.get()); @@ -3164,6 +3205,7 @@ IntegerVector py_get_attr_types( const std::vector& attrs, bool resolve_properties = false) { + GILScope _gil; PyObject* x_ = x.get(); // ensure python initialized, module proxy resolved const int UNKNOWN = 0; const int VECTOR = 1; @@ -3242,7 +3284,7 @@ SEXP py_ref_to_r(PyObjectRef x) { // [[Rcpp::export]] SEXP py_call_impl(PyObjectRef x, List args = R_NilValue, List keywords = R_NilValue) { - ensure_python_initialized(); + GILScope _gil; bool convert = x.convert(); // unnamed arguments @@ -3284,7 +3326,7 @@ SEXP py_call_impl(PyObjectRef x, List args = R_NilValue, List keywords = R_NilVa // [[Rcpp::export]] PyObjectRef py_dict_impl(const List& keys, const List& items, bool convert) { - ensure_python_initialized(); + GILScope _gil; PyObject* dict = PyDict_New(); @@ -3301,6 +3343,7 @@ PyObjectRef py_dict_impl(const List& keys, const List& items, bool convert) { // [[Rcpp::export]] SEXP py_dict_get_item(PyObjectRef dict, RObject key) { + GILScope _gil; PyObject* dict_ = dict.get(); // ensure python initialized, module proxy resolved if (!PyDict_CheckExact(dict_)) { @@ -3328,6 +3371,7 @@ SEXP py_dict_get_item(PyObjectRef dict, RObject key) { // [[Rcpp::export]] void py_dict_set_item(PyObjectRef dict, RObject key, RObject val) { + GILScope _gil; PyObject* dict_ = dict.get(); // ensure python initialized, module proxy resolved if (!PyDict_CheckExact(dict_)) { @@ -3343,6 +3387,7 @@ void py_dict_set_item(PyObjectRef dict, RObject key, RObject val) { // [[Rcpp::export]] int py_dict_length(PyObjectRef dict) { + GILScope _gil; if (!PyDict_CheckExact(dict)) return PyObject_Size(dict); @@ -3372,12 +3417,14 @@ PyObject* py_dict_get_keys_impl(PyObject* dict) { // [[Rcpp::export]] PyObjectRef py_dict_get_keys(PyObjectRef dict) { + GILScope _gil; PyObject* keys = py_dict_get_keys_impl(dict); return py_ref(keys, dict.convert()); } // [[Rcpp::export]] CharacterVector py_dict_get_keys_as_str(PyObjectRef dict) { + GILScope _gil; // get the dictionary keys PyObjectPtr py_keys(py_dict_get_keys_impl(dict)); @@ -3421,7 +3468,7 @@ CharacterVector py_dict_get_keys_as_str(PyObjectRef dict) { // [[Rcpp::export]] PyObjectRef py_tuple(const List& items, bool convert) { - ensure_python_initialized(); + GILScope _gil; R_xlen_t n = items.length(); PyObject* tuple = PyTuple_New(n); @@ -3439,7 +3486,7 @@ PyObjectRef py_tuple(const List& items, bool convert) { // [[Rcpp::export]] int py_tuple_length(PyObjectRef tuple) { - + GILScope _gil; if (!PyTuple_CheckExact(tuple)) return PyObject_Size(tuple); @@ -3450,7 +3497,7 @@ int py_tuple_length(PyObjectRef tuple) { // [[Rcpp::export]] PyObjectRef py_module_import(const std::string& module, bool convert) { - + GILScope _gil; PyObject* pModule = py_import(module); if (pModule == NULL) throw PythonException(py_fetch_error()); @@ -3463,6 +3510,7 @@ PyObjectRef py_module_import(const std::string& module, bool convert) { void py_module_proxy_import(PyObjectRef proxy) { Rcpp::Environment refenv = proxy.get_refenv(); if (refenv.exists("module")) { + GILScope _gil; Rcpp::RObject r_module = refenv.get("module"); std::string module = as(r_module); PyObject* pModule = py_import(module); @@ -3481,6 +3529,7 @@ void py_module_proxy_import(PyObjectRef proxy) { // [[Rcpp::export]] CharacterVector py_list_submodules(const std::string& module) { + GILScope _gil; std::vector modules; PyObject* modulesDict = PyImport_GetModuleDict(); @@ -3507,7 +3556,7 @@ SEXP py_run_string_impl(const std::string& code, bool local = false, bool convert = true) { - ensure_python_initialized(); + GILScope _gil; PyFlushOutputOnScopeExit flush_; // retrieve reference to main module dictionary // note: both PyImport_AddModule() and PyModule_GetDict() @@ -3547,7 +3596,7 @@ SEXP py_run_string_impl(const std::string& code, PyObjectRef py_run_file_impl(const std::string& file, bool local = false, bool convert = true) { - ensure_python_initialized(); + GILScope _gil; FILE* fp = fopen(file.c_str(), "rb"); if (fp == NULL) stop("Unable to open file '%s'", file); @@ -3590,7 +3639,7 @@ PyObjectRef py_run_file_impl(const std::string& file, // [[Rcpp::export]] SEXP py_eval_impl(const std::string& code, bool convert = true) { - ensure_python_initialized(); + GILScope _gil; // compile the code PyObjectPtr compiledCode; if (Py_CompileStringExFlags != NULL) @@ -3675,6 +3724,7 @@ SEXPTYPE nullable_typename_to_sexptype (const std::string& name) { // [[Rcpp::export]] SEXP py_convert_pandas_series(PyObjectRef series) { + GILScope _gil; // extract dtype PyObjectPtr dtype(PyObject_GetAttrString(series, "dtype")); @@ -3813,6 +3863,7 @@ SEXP py_convert_pandas_series(PyObjectRef series) { // [[Rcpp::export]] SEXP py_convert_pandas_df(PyObjectRef df) { + GILScope _gil; // pd.DataFrame.items() returns an iterator over (column name, Series) pairs PyObjectPtr items(PyObject_CallMethod(df, "items", NULL)); @@ -3975,7 +4026,7 @@ PyObject* r_to_py_pandas_nullable_series (const RObject& column, const bool conv // [[Rcpp::export]] PyObjectRef r_convert_dataframe(RObject dataframe, bool convert) { - + GILScope _gil; Function r_convert_dataframe_column = Environment::namespace_env("reticulate")["r_convert_dataframe_column"]; @@ -4061,6 +4112,7 @@ PyObject* r_convert_date_impl(PyObject* datetime, // [[Rcpp::export]] PyObjectRef r_convert_date(DateVector dates, bool convert) { + GILScope _gil; PyObjectPtr datetime(PyImport_ImportModule("datetime")); // short path for n == 1 @@ -4085,6 +4137,7 @@ PyObjectRef r_convert_date(DateVector dates, bool convert) { // [[Rcpp::export]] SEXP py_list_length(PyObjectRef x) { + GILScope _gil; Py_ssize_t value; if (PyList_CheckExact(x)) @@ -4100,7 +4153,7 @@ SEXP py_list_length(PyObjectRef x) { // [[Rcpp::export]] SEXP py_len_impl(PyObjectRef x, SEXP defaultValue = R_NilValue) { - + GILScope _gil; PyObject *er_type, *er_value, *er_traceback; if (defaultValue != R_NilValue) PyErr_Fetch(&er_type, &er_value, &er_traceback); @@ -4125,6 +4178,7 @@ SEXP py_len_impl(PyObjectRef x, SEXP defaultValue = R_NilValue) { // [[Rcpp::export]] SEXP py_bool_impl(PyObjectRef x, bool silent = false) { + GILScope _gil; int result; if(silent) { PyErrorScopeGuard _g; @@ -4150,6 +4204,7 @@ SEXP py_bool_impl(PyObjectRef x, bool silent = false) { // [[Rcpp::export]] SEXP py_has_method(PyObjectRef object, const std::string& name) { + GILScope _gil; PyObject* object_ = object.get(); // ensure python initialized, module proxy resolved PyObjectPtr attr(PyObject_GetAttrString(object_, name.c_str())); @@ -4179,6 +4234,7 @@ SEXP py_has_method(PyObjectRef object, const std::string& name) { SEXP py_id(PyObjectRef object) { if (py_is_null_xptr(object)) return R_NilValue; + GILScope _gil; std::stringstream id; id << (uintptr_t) object.get(); @@ -4189,7 +4245,7 @@ SEXP py_id(PyObjectRef object) { // [[Rcpp::export]] PyObjectRef py_capsule(SEXP x) { - ensure_python_initialized(); + GILScope _gil; return py_ref(py_capsule_new(x), false); } @@ -4197,7 +4253,7 @@ PyObjectRef py_capsule(SEXP x) { // [[Rcpp::export]] PyObjectRef py_slice(SEXP start = R_NilValue, SEXP stop = R_NilValue, SEXP step = R_NilValue) { - ensure_python_initialized(); + GILScope _gil; PyObjectPtr start_, stop_, step_; @@ -4219,7 +4275,7 @@ PyObjectRef py_slice(SEXP start = R_NilValue, SEXP stop = R_NilValue, SEXP step //' @export // [[Rcpp::export]] SEXP as_iterator(SEXP x) { - ensure_python_initialized(); + GILScope _gil; // If already inherits from iterator, return as is if (inherits2(x, "python.builtin.iterator")) @@ -4252,6 +4308,7 @@ SEXP as_iterator(SEXP x) { // [[Rcpp::export]] SEXP py_iter_next(PyObjectRef iterator, RObject completed) { + GILScope _gil; if(!PyIter_Check(iterator)) stop("object is not an iterator"); @@ -4280,7 +4337,7 @@ SEXP py_iter_next(PyObjectRef iterator, RObject completed) { // [[Rcpp::export]] SEXP py_iterate(PyObjectRef x, Function f, bool simplify = true) { - ensure_python_initialized(); + GILScope _gil; SEXP out; { // open scope so we can invoke c++ destructors before @@ -4440,3 +4497,15 @@ SEXP py_exception_as_condition(PyObject* object, SEXP refenv) { UNPROTECT(1); return out; } + + +// [[Rcpp::export]] +bool py_allow_threads_impl(bool allow = true) { + PyGILState_STATE gstate = PyGILState_Ensure(); + if (allow) { + PyGILState_Release(PyGILState_UNLOCKED); + } else { + PyGILState_Release(PyGILState_LOCKED); + } + return gstate == PyGILState_UNLOCKED; +} diff --git a/src/reticulate_types.h b/src/reticulate_types.h index 32cd9269a..3ae1c7dfe 100644 --- a/src/reticulate_types.h +++ b/src/reticulate_types.h @@ -158,25 +158,14 @@ extern bool s_is_python_initialized; class GILScope { private: PyGILState_STATE gstate; - bool acquired = false; public: GILScope() { - if (s_is_python_initialized) { gstate = PyGILState_Ensure(); - acquired = true; } - } - - GILScope(bool force) { - if (force) { - gstate = PyGILState_Ensure(); - acquired = true; - } - } ~GILScope() { - if (acquired) PyGILState_Release(gstate); + PyGILState_Release(gstate); } }; @@ -196,22 +185,6 @@ struct PythonException { }; -// This custom BEGIN_RCPP is effectively identical to upstream -// except for the last line, which we use to ensure that the -// GIL is acquired when calling into Python (and released otherwise). -// Limitations of the macro preprocessor make it difficult to -// do this in a more elegant way. - -#undef BEGIN_RCPP -#define BEGIN_RCPP \ - int rcpp_output_type = 0; \ - int nprot = 0; \ - (void)rcpp_output_type; \ - SEXP rcpp_output_condition = R_NilValue; \ - (void)rcpp_output_condition; \ - static SEXP stop_sym = Rf_install("stop"); \ - try { \ - GILScope gilscope; // This custom END_RCPP is effectively identical to upstream // except for the addition of one additional catch block, which diff --git a/tests/testthat/test-python-numpy.R b/tests/testthat/test-python-numpy.R index 1cd5cdb45..977a7325c 100644 --- a/tests/testthat/test-python-numpy.R +++ b/tests/testthat/test-python-numpy.R @@ -164,6 +164,7 @@ test_that("numpy non-simple arrays work", { expect_s3_class(rec_array, "numpy.ndarray") expect_s3_class(rec_array, "python.builtin.object") + skip_if_no_pandas() # Test that a registered S3 method for the non-simple numpy array will be # called. (Note, some packages, like {zellkonverter}, will register this # directly for numpy.ndarray) diff --git a/tests/testthat/test-python-threads.R b/tests/testthat/test-python-threads.R new file mode 100644 index 000000000..c16d051df --- /dev/null +++ b/tests/testthat/test-python-threads.R @@ -0,0 +1,40 @@ + + +test_that("py_allow_threads() can enable/disable background threads", { + + file <- tempfile() + on.exit(unlink(file), add = TRUE) + + write_to_file_from_thread <- py_run_string(" +def write_to_file_from_thread(path, lines): + from time import sleep, localtime, strftime + + def write_to_file(path, lines): + sleep(.1) # don't try to run until we've had a chance to return to the R main thread + with open(path, 'w') as f: + for line in list(lines): + f.write(line + '\\n') + + from _thread import start_new_thread + start_new_thread(write_to_file, (path, lines)) +", local = TRUE)$write_to_file_from_thread + + reticulate:::py_allow_threads_impl(FALSE) + write_to_file_from_thread(file, letters) + Sys.sleep(.5) + # confirm background thread did not run while R was sleeping + expect_false(file.exists(file)) + # explicitly enter python and release the gil + import("time")$sleep(.3) + # confirm the background thread ran on py_sleep() + expect_identical(readLines(file), letters) + + unlink(file) + + reticulate:::py_allow_threads_impl(TRUE) + write_to_file_from_thread(file, letters) + Sys.sleep(.3) + # confirm that the background thread ran while R was sleeping. + expect_identical(readLines(file), letters) + +})