diff --git a/cpp11test/src/test-as.cpp b/cpp11test/src/test-as.cpp index 76b4ee39..6a3282c3 100644 --- a/cpp11test/src/test-as.cpp +++ b/cpp11test/src/test-as.cpp @@ -8,6 +8,24 @@ #include "Rcpp.h" +struct Vec3 { + double x, y, z; +}; + +namespace cpp11 { +template <> +struct as_cpp_impl { + static Vec3 convert(SEXP from) { + if (Rf_isReal(from)) { + if (Rf_xlength(from) == 3) { + return {REAL_ELT(from, 0), REAL_ELT(from, 1), REAL_ELT(from, 2)}; + } + } + stop("Expected three double values"); + } +}; +} // namespace cpp11 + context("as_cpp-C++") { test_that("as_cpp(INTSEXP)") { SEXP r = PROTECT(Rf_allocVector(INTSXP, 1)); @@ -57,6 +75,18 @@ context("as_cpp-C++") { UNPROTECT(1); } + test_that("as_cpp(REALSXP)") { + SEXP r = PROTECT(Rf_allocVector(REALSXP, 3)); + REAL(r)[0] = 1; + REAL(r)[1] = 2; + REAL(r)[2] = 4; + + Vec3 v = cpp11::as_cpp(r); + expect_true(v.x == 1); + expect_true(v.y == 2); + expect_true(v.z == 4); + } + test_that("as_cpp(NA)") { SEXP r = PROTECT(Rf_allocVector(REALSXP, 1)); SEXP i = PROTECT(Rf_allocVector(INTSXP, 1)); @@ -209,6 +239,25 @@ context("as_cpp-C++") { UNPROTECT(1); } +#if defined(__APPLE__) && defined(R_VERSION) && R_VERSION >= R_Version(3, 5, 0) + test_that("as_cpp(ALTREP_INTSXP)") { + SEXP r = PROTECT(R_compact_intrange(1, 5)); + + expect_true(ALTREP(r)); + auto x1 = cpp11::as_cpp>(r); + expect_true(ALTREP(r)); + + expect_true(x1.size() == 5); + int expected = 1; + for (int actual : x1) { + expect_true(actual == expected); + ++expected; + } + + UNPROTECT(1); + } +#endif + test_that("as_cpp>()") { SEXP r = PROTECT(Rf_allocVector(STRSXP, 3)); SET_STRING_ELT(r, 0, Rf_mkChar("foo")); diff --git a/inst/include/cpp11/as.hpp b/inst/include/cpp11/as.hpp index a02c7588..6e2b5e24 100644 --- a/inst/include/cpp11/as.hpp +++ b/inst/include/cpp11/as.hpp @@ -11,12 +11,12 @@ namespace cpp11 { -template -using enable_if_t = typename std::enable_if::type; - template using decay_t = typename std::decay::type; +template +using enable_if_t = typename std::enable_if::type; + template struct is_smart_ptr : std::false_type {}; @@ -29,27 +29,63 @@ struct is_smart_ptr> : std::true_type {}; template struct is_smart_ptr> : std::true_type {}; -template -using enable_if_constructible_from_sexp = - enable_if_t::value && // workaround for gcc 4.8 - std::is_class::value && std::is_constructible::value, - R>; +template +using is_constructible_from_sexp = std::integral_constant< + bool, std::is_same::value || + (!is_smart_ptr::value && // workaround for gcc 4.8 + std::is_class::value && std::is_constructible::value)>; -template -using enable_if_is_sexp = enable_if_t::value, R>; +template +using is_convertible_to_sexp = std::is_convertible; -template -using enable_if_convertible_to_sexp = enable_if_t::value, R>; +template +struct as_cpp_impl; -template -using disable_if_convertible_to_sexp = - enable_if_t::value, R>; +/// If T defines explicit construction from SEXP, that will override as_cpp_impl +template +enable_if_t::value, T> as_cpp(SEXP from) { + static_assert(std::is_same, T>::value, ""); + return T(from); +} + +template ::value>> +auto as_cpp(SEXP from) -> decltype(as_cpp_impl::convert(from)) { + static_assert(std::is_same, T>::value, ""); + return as_cpp_impl::convert(from); +} + +/// Temporary workaround for compatibility with cpp11 0.1.0 +template +enable_if_t, T>::value, decay_t> as_cpp(SEXP from) { + return as_cpp>(from); +} + +template +struct as_sexp_impl; + +/// If T defines explicit construction from SEXP, that will override as_sexp_impl +template +enable_if_t::value, SEXP> as_sexp(const T& from) { + return static_cast(from); +} + +/// Override as_sexp so that as_sexp(r_string(...)) results in a single element vector +/// instead of a CHRSXP +class r_string; +inline SEXP as_sexp(r_string from); + +template ::value>> +auto as_sexp(const T& from) -> decltype(as_sexp_impl>::convert(from)) { + return as_sexp_impl>::convert(from); +} + +template +using is_integral = std::integral_constant::value && + !std::is_same::value && + !std::is_same::value>; template -using enable_if_integral = - enable_if_t::value && !std::is_same::value && - !std::is_same::value, - R>; +using enable_if_integral = enable_if_t::value, R>; template using enable_if_floating_point = @@ -59,277 +95,356 @@ template using enable_if_enum = enable_if_t::value, R>; template -using enable_if_bool = enable_if_t::value, R>; +using enable_if_is_sexp = enable_if_t::value, R>; template -using enable_if_char = enable_if_t::value, R>; +using enable_if_convertible_to_sexp = enable_if_t::value, R>; template -using enable_if_std_string = enable_if_t::value, R>; +using disable_if_convertible_to_sexp = + enable_if_t::value, R>; -template -using enable_if_c_string = enable_if_t::value, R>; +namespace detail { // https://stackoverflow.com/a/1521682/2055486 -// -inline bool is_convertable_without_loss_to_integer(double value) { +static bool is_convertible_without_loss_to_integer(double value) { double int_part; return std::modf(value, &int_part) == 0.0; } -template -enable_if_constructible_from_sexp as_cpp(SEXP from) { - return T(from); -} +template ::type> +using enum_to_int_type = + typename std::conditional::value, + int, // `char` triggers undesired string conversions + Underlying>::type; -template -enable_if_is_sexp as_cpp(SEXP from) { - return from; -} +} // namespace detail template -enable_if_integral as_cpp(SEXP from) { - if (Rf_isInteger(from)) { - if (Rf_xlength(from) == 1) { - return INTEGER_ELT(from, 0); - } - } else if (Rf_isReal(from)) { - if (Rf_xlength(from) == 1) { - if (ISNA(REAL_ELT(from, 0))) { - return NA_INTEGER; +struct as_cpp_impl> { + static T convert(SEXP from) { + if (Rf_isInteger(from)) { + if (Rf_xlength(from) == 1) { + return INTEGER_ELT(from, 0); } - double value = REAL_ELT(from, 0); - if (is_convertable_without_loss_to_integer(value)) { - return value; + } else if (Rf_isReal(from)) { + if (Rf_xlength(from) == 1) { + if (ISNA(REAL_ELT(from, 0))) { + return NA_INTEGER; + } + double value = REAL_ELT(from, 0); + if (detail::is_convertible_without_loss_to_integer(value)) { + return value; + } } - } - } else if (Rf_isLogical(from)) { - if (Rf_xlength(from) == 1) { - if (LOGICAL_ELT(from, 0) == NA_LOGICAL) { - return NA_INTEGER; + } else if (Rf_isLogical(from)) { + if (Rf_xlength(from) == 1) { + if (LOGICAL_ELT(from, 0) == NA_LOGICAL) { + return NA_INTEGER; + } } } + + stop("Expected single integer value"); } +}; - stop("Expected single integer value"); -} +template +struct as_sexp_impl> { + static SEXP convert(T from) { return safe[Rf_ScalarInteger](from); } +}; template -enable_if_enum as_cpp(SEXP from) { - if (Rf_isInteger(from)) { - using underlying_type = typename std::underlying_type::type; - using int_type = typename std::conditional::value, - int, // as_cpp would trigger - // undesired string conversions - underlying_type>::type; - return static_cast(as_cpp(from)); - } +struct as_cpp_impl> { + static E convert(SEXP from) { + if (Rf_isInteger(from)) { + return static_cast(as_cpp>(from)); + } - stop("Expected single integer value"); -} + stop("Expected single integer value"); + } +}; -template -enable_if_bool as_cpp(SEXP from) { - if (Rf_isLogical(from)) { - if (Rf_xlength(from) == 1) { - return LOGICAL_ELT(from, 0) == 1; +template +struct as_sexp_impl> { + static SEXP convert(E from) { + return as_sexp(static_cast>(from)); + } +}; + +template <> +struct as_cpp_impl { + static bool convert(SEXP from) { + if (Rf_isLogical(from)) { + if (Rf_xlength(from) == 1) { + return LOGICAL_ELT(from, 0) == 1; + } } + + stop("Expected single logical value"); } +}; - stop("Expected single logical value"); -} +template <> +struct as_sexp_impl { + static SEXP convert(bool from) { return safe[Rf_ScalarLogical](from); } +}; template -enable_if_floating_point as_cpp(SEXP from) { - if (Rf_isReal(from)) { - if (Rf_xlength(from) == 1) { - return REAL_ELT(from, 0); +struct as_cpp_impl> { + static T convert(SEXP from) { + if (Rf_isReal(from)) { + if (Rf_xlength(from) == 1) { + return REAL_ELT(from, 0); + } } - } - // All 32 bit integers can be coerced to doubles, so we just convert them. - if (Rf_isInteger(from)) { - if (Rf_xlength(from) == 1) { - if (INTEGER_ELT(from, 0) == NA_INTEGER) { - return NA_REAL; + // All 32 bit integers can be coerced to doubles, so we just convert them. + if (Rf_isInteger(from)) { + if (Rf_xlength(from) == 1) { + if (INTEGER_ELT(from, 0) == NA_INTEGER) { + return NA_REAL; + } + return INTEGER_ELT(from, 0); } - return INTEGER_ELT(from, 0); } - } - // Also allow NA values - if (Rf_isLogical(from)) { - if (Rf_xlength(from) == 1) { - if (LOGICAL_ELT(from, 0) == NA_LOGICAL) { - return NA_REAL; + // Also allow NA values + if (Rf_isLogical(from)) { + if (Rf_xlength(from) == 1) { + if (LOGICAL_ELT(from, 0) == NA_LOGICAL) { + return NA_REAL; + } } } - } - stop("Expected single double value"); -} + stop("Expected single double value"); + } +}; template -enable_if_char as_cpp(SEXP from) { - if (Rf_isString(from)) { - if (Rf_xlength(from) == 1) { - return unwind_protect([&] { return Rf_translateCharUTF8(STRING_ELT(from, 0))[0]; }); +struct as_sexp_impl> { + static SEXP convert(T from) { return safe[Rf_ScalarReal](from); } +}; + +template <> +struct as_cpp_impl { + static const char* convert(SEXP from) { + if (Rf_isString(from)) { + if (Rf_xlength(from) == 1) { + // NB: vmaxget/vmaxset here would cause translated strings to be freed before + // return. Without this explicit management, the return value of as_cpp(str) will freed at the end of the call to .C, .Call, or .External + return unwind_protect([&] { return Rf_translateCharUTF8(STRING_ELT(from, 0)); }); + } } - } - stop("Expected string vector of length 1"); -} + stop("Expected string vector of length 1"); + } +}; -template -enable_if_c_string as_cpp(SEXP from) { - if (Rf_isString(from)) { - if (Rf_xlength(from) == 1) { - // TODO: use vmaxget / vmaxset here? - return {unwind_protect([&] { return Rf_translateCharUTF8(STRING_ELT(from, 0)); })}; - } +template <> +struct as_sexp_impl { + static SEXP convert(const char* from) { + return unwind_protect([&] { return Rf_ScalarString(Rf_mkCharCE(from, CE_UTF8)); }); } +}; - stop("Expected string vector of length 1"); -} +template <> +struct as_sexp_impl { + static SEXP convert(const char* from) { return as_sexp(from); } +}; -template -enable_if_std_string as_cpp(SEXP from) { - return {as_cpp(from)}; -} +template <> +struct as_cpp_impl { + static std::string convert(SEXP from) { return as_cpp(from); } +}; -/// Temporary workaround for compatibility with cpp11 0.1.0 -template -enable_if_t, T>::value, decay_t> as_cpp(SEXP from) { - return as_cpp>(from); -} +template <> +struct as_sexp_impl { + static SEXP convert(const std::string& from) { return as_sexp(from.c_str()); } +}; -template -enable_if_integral as_sexp(T from) { - return safe[Rf_ScalarInteger](from); -} +template <> +struct as_cpp_impl { + static char convert(SEXP from) { return as_cpp(from)[0]; } +}; -template -enable_if_floating_point as_sexp(T from) { - return safe[Rf_ScalarReal](from); -} +template <> +struct as_sexp_impl { + static SEXP convert(char from) { return as_sexp(std::string({from})); } +}; -template -enable_if_bool as_sexp(T from) { - return safe[Rf_ScalarLogical](from); -} +namespace detail { -template -enable_if_c_string as_sexp(T from) { - return unwind_protect([&] { return Rf_ScalarString(Rf_mkCharCE(from, CE_UTF8)); }); -} +template +using sexptype_constant = std::integral_constant; -template -enable_if_std_string as_sexp(const T& from) { - return as_sexp(from.c_str()); -} +inline int* get_raws(SEXP vec, sexptype_constant) { return LOGICAL(vec); } +inline int* get_raws(SEXP vec, sexptype_constant) { return INTEGER(vec); } +inline double* get_raws(SEXP vec, sexptype_constant) { return REAL(vec); } -template > -enable_if_integral as_sexp(const Container& from) { +template +SEXP as_sexp_raws(const Container& from, sexptype_constant sexptype) { R_xlen_t size = from.size(); - SEXP data = safe[Rf_allocVector](INTSXP, size); + SEXP data = PROTECT(safe[Rf_allocVector](sexptype, size)); - auto it = from.begin(); - int* data_p = INTEGER(data); - for (R_xlen_t i = 0; i < size; ++i, ++it) { - data_p[i] = *it; + auto raw_data = get_raws(data, sexptype); + for (auto el : from) { + *raw_data++ = el; } + + UNPROTECT(1); return data; } -inline SEXP as_sexp(std::initializer_list from) { - return as_sexp>(from); +template +Container as_cpp_raws(SEXP from, sexptype_constant sexptype) { + // FIXME altrep is broken + auto raw_data = get_raws(from, sexptype); + return Container{raw_data, raw_data + Rf_xlength(from)}; } -template > -enable_if_floating_point as_sexp(const Container& from) { +template +SEXP as_sexp_strings(const Container& from, const ToCstring& to_c_str) { R_xlen_t size = from.size(); - SEXP data = safe[Rf_allocVector](REALSXP, size); + SEXP data = PROTECT(safe[Rf_allocVector](STRSXP, size)); - auto it = from.begin(); - double* data_p = REAL(data); - for (R_xlen_t i = 0; i < size; ++i, ++it) { - data_p[i] = *it; + try { + R_xlen_t i = 0; + for (const auto& s : from) { + SET_STRING_ELT(data, i++, safe[Rf_mkCharCE](to_c_str(s), CE_UTF8)); + } + } catch (const unwind_exception& e) { + UNPROTECT(1); + throw e; } + + UNPROTECT(1); return data; } -inline SEXP as_sexp(std::initializer_list from) { - return as_sexp>(from); -} +template +Container as_cpp_strings(SEXP from) { + struct iterator { + using difference_type = int; + using value_type = const char*; + using reference = value_type&; + using pointer = value_type*; + using iterator_category = std::forward_iterator_tag; + + const char* operator*() const { + return Rf_translateCharUTF8(STRING_ELT(data_, index_)); + } -template > -enable_if_bool as_sexp(const Container& from) { - R_xlen_t size = from.size(); - SEXP data = safe[Rf_allocVector](LGLSXP, size); + iterator& operator++() { + ++index_; + return *this; + } - auto it = from.begin(); - int* data_p = LOGICAL(data); - for (R_xlen_t i = 0; i < size; ++i, ++it) { - data_p[i] = *it; - } - return data; -} + bool operator!=(const iterator& other) const { return index_ != other.index_; } -inline SEXP as_sexp(std::initializer_list from) { - return as_sexp>(from); + SEXP data_; + R_xlen_t index_; + }; + + iterator begin{from, 0}; + iterator end{from, Rf_xlength(from)}; + return Container(begin, end); } -namespace detail { -template -SEXP as_sexp_strings(const Container& from, AsCstring&& c_str) { - R_xlen_t size = from.size(); +} // namespace detail - SEXP data; - try { - data = PROTECT(safe[Rf_allocVector](STRSXP, size)); +template +struct as_cpp_impl::value>> { + static Container convert(SEXP from) { + return detail::as_cpp_raws(from, detail::sexptype_constant{}); + } +}; + +template +struct as_cpp_impl< + Container, + enable_if_t::value>> { + static Container convert(SEXP from) { + return detail::as_cpp_raws(from, detail::sexptype_constant{}); + } +}; - auto it = from.begin(); - for (R_xlen_t i = 0; i < size; ++i, ++it) { - SET_STRING_ELT(data, i, safe[Rf_mkCharCE](c_str(*it), CE_UTF8)); - } - } catch (const unwind_exception& e) { - UNPROTECT(1); - throw e; +template +struct as_cpp_impl< + Container, enable_if_t::value>> { + static Container convert(SEXP from) { + return detail::as_cpp_raws(from, detail::sexptype_constant{}); + } +}; + +template +struct as_cpp_impl::value>> { + static Container convert(SEXP from) { return detail::as_cpp_strings(from); } +}; + +template +struct as_sexp_impl::value>> { + static SEXP convert(const Container& from) { + return detail::as_sexp_raws(from, detail::sexptype_constant{}); + } +}; + +template +struct as_sexp_impl< + Container, + enable_if_t::value>> { + static SEXP convert(const Container& from) { + return detail::as_sexp_raws(from, detail::sexptype_constant{}); } +}; - UNPROTECT(1); - return data; -} -} // namespace detail +template +struct as_sexp_impl< + Container, enable_if_t::value>> { + static SEXP convert(const Container& from) { + return detail::as_sexp_raws(from, detail::sexptype_constant{}); + } +}; + +template +struct as_sexp_impl< + Container, + enable_if_t::value>> { + static SEXP convert(const Container& from) { + return detail::as_sexp_strings( + from, [](const std::string& s) { return s.c_str(); }); + } +}; + +template +struct as_sexp_impl::value>> { + static SEXP convert(const Container& from) { + return detail::as_sexp_strings( + from, [](const typename Container::value_type& s) { + return static_cast(s); + }); + } +}; -class r_string; +inline SEXP as_sexp(std::initializer_list from) { + return as_sexp>(from); +} -template -using disable_if_r_string = enable_if_t::value, R>; - -template > -enable_if_t::value && - !std::is_convertible::value, - SEXP> -as_sexp(const Container& from) { - return detail::as_sexp_strings(from, [](const std::string& s) { return s.c_str(); }); +inline SEXP as_sexp(std::initializer_list from) { + return as_sexp>(from); } -template -enable_if_c_string as_sexp(const Container& from) { - return detail::as_sexp_strings(from, [](const char* s) { return s; }); +inline SEXP as_sexp(std::initializer_list from) { + return as_sexp>(from); } inline SEXP as_sexp(std::initializer_list from) { return as_sexp>(from); } -template > -enable_if_convertible_to_sexp as_sexp(const T& from) { - return from; -} - } // namespace cpp11 diff --git a/inst/include/cpp11/r_string.hpp b/inst/include/cpp11/r_string.hpp index 3c7cc4a4..40e627a7 100644 --- a/inst/include/cpp11/r_string.hpp +++ b/inst/include/cpp11/r_string.hpp @@ -68,12 +68,9 @@ inline SEXP as_sexp(std::initializer_list il) { inline bool is_na(const r_string& x) { return x == NA_STRING; } -template -using enable_if_r_string = enable_if_t::value, R>; - -template -enable_if_r_string as_sexp(T from) { +inline SEXP as_sexp(r_string from) { r_string str(from); + sexp res; unwind_protect([&] { res = Rf_allocVector(STRSXP, 1); diff --git a/inst/include/cpp11/r_vector.hpp b/inst/include/cpp11/r_vector.hpp index 628fe2b9..578f80fd 100644 --- a/inst/include/cpp11/r_vector.hpp +++ b/inst/include/cpp11/r_vector.hpp @@ -922,42 +922,6 @@ inline void r_vector::proxy::operator++() { } // namespace writable -// TODO: is there a better condition we could use, e.g. assert something true -// rather than three things false? -template -using is_container_but_not_sexp_or_string = typename std::enable_if< - !std::is_constructible::value && - !std::is_same::type, std::string>::value && - !std::is_same::type, std::string>::value, - typename std::decay::type>::type; - -template ::type::value_type> -// typename T = typename C::value_type> -is_container_but_not_sexp_or_string as_cpp(SEXP from) { - auto obj = cpp11::r_vector(from); - return {obj.begin(), obj.end()}; -} - -// TODO: could we make this generalize outside of std::string? -template -using is_vector_of_strings = typename std::enable_if< - std::is_same::type, std::string>::value, - typename std::decay::type>::type; - -template ::type::value_type> -// typename T = typename C::value_type> -is_vector_of_strings as_cpp(SEXP from) { - auto obj = cpp11::r_vector(from); - typename std::decay::type res; - auto it = obj.begin(); - while (it != obj.end()) { - r_string s = *it; - res.emplace_back(static_cast(s)); - ++it; - } - return res; -} - template bool operator==(const r_vector& lhs, const r_vector& rhs) { if (lhs.size() != rhs.size()) { diff --git a/vignettes/internals.Rmd b/vignettes/internals.Rmd index c7b1649c..8c489da8 100644 --- a/vignettes/internals.Rmd +++ b/vignettes/internals.Rmd @@ -100,7 +100,28 @@ This is definitely the most complex part of the cpp11 code, with extensive use o In particular the [substitution failure is not an error (SFINAE)](https://en.wikipedia.org/wiki/Substitution_failure_is_not_an_error) technique is used to control overloading of the functions. If we could use C++20 a lot of this code would be made simpler with [Concepts](https://en.cppreference.com/w/cpp/language/constraints), but alas. -The most common C++ types are included in the test suite and should work without issues, as more exotic types are used in real projects additional issues may arise. +A range of common C++ types are included in the test suite and should work without issues. +To add custom coercion behavior, define `operator SEXP()` and a constructor which takes an SEXP. +These will be used by `as_sexp()` and `as_cpp<>()` respectively, if available. +If constructors or conversion operators cannot be defined, coercion behavior can be customized by specializing the trait structs `as_sexp_impl` and `as_cpp_impl` respectively. +(cpp11's own coercion logic for STL containers is defined by specializing these traits since we can't add members to `std::vector`.) +For example, to define coercion from SEXP to `struct Vec3 { double x,y,z; };`: + +```c++ +namespace cpp11 { +template <> +struct as_cpp_impl { + static Vec3 convert(SEXP from) { + if (Rf_isReal(from) && Rf_xlength(from) == 3) { + return Vec3{REAL_ELT(from, 0), REAL_ELT(from, 1), REAL_ELT(from, 2)}; + } + stop("Expected three double values"); + } +}; +} +``` + +Note that specializing `as_sexp_impl` will never override an explicit conversion operator to SEXP, nor will specializing `as_cpp_impl` override a constructor from SEXP. Some useful links on SFINAE