From 8e8199fafc84720edbe5bd3849dcee81246bd326 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Sat, 27 Jul 2024 17:42:04 -0400 Subject: [PATCH 01/10] Stop double protecting writable vectors And fix memory leak when assigning a `writable::r_vector&&` temporary value to an existing `writable::r_vector`. --- cpp11test/src/test-doubles.cpp | 6 ++- cpp11test/src/test-integers.cpp | 3 +- cpp11test/src/test-list.cpp | 3 +- inst/include/cpp11/doubles.hpp | 4 +- inst/include/cpp11/integers.hpp | 4 +- inst/include/cpp11/list.hpp | 5 +-- inst/include/cpp11/logicals.hpp | 5 +-- inst/include/cpp11/r_vector.hpp | 65 ++++++++++++++------------------- inst/include/cpp11/raws.hpp | 5 +-- inst/include/cpp11/strings.hpp | 12 ++---- 10 files changed, 42 insertions(+), 70 deletions(-) diff --git a/cpp11test/src/test-doubles.cpp b/cpp11test/src/test-doubles.cpp index a7423e1e..d49cb8fa 100644 --- a/cpp11test/src/test-doubles.cpp +++ b/cpp11test/src/test-doubles.cpp @@ -233,7 +233,11 @@ context("doubles-C++") { w = z; expect_true(w.size() == 5); expect_true(w.data() != z.data()); - expect_true(w.is_altrep() == z.is_altrep()); + // Shallow duplication of objects of a very small size (like 1:5) don't result in + // a new ALTREP object. Make sure we check ALTREP-ness of the newly duplicated object, + // instead of just blindly inheriting the ALTREP-ness of the thing we duplicate. + expect_true(w.is_altrep() != z.is_altrep()); + expect_true(w.is_altrep() == ALTREP(w.data())); } test_that("writable::doubles(SEXP) move assignment") { diff --git a/cpp11test/src/test-integers.cpp b/cpp11test/src/test-integers.cpp index a7aec08f..2b068d3c 100644 --- a/cpp11test/src/test-integers.cpp +++ b/cpp11test/src/test-integers.cpp @@ -223,7 +223,6 @@ context("integers-C++") { R_xlen_t after = cpp11::detail::store::count(); expect_true(before == 0); - // TODO: This should be 1 but writable vectors are being double protected - expect_true(after - before == 2); + expect_true(after - before == 1); } } diff --git a/cpp11test/src/test-list.cpp b/cpp11test/src/test-list.cpp index 9226039e..b5b61740 100644 --- a/cpp11test/src/test-list.cpp +++ b/cpp11test/src/test-list.cpp @@ -178,7 +178,6 @@ context("list-C++") { R_xlen_t after = cpp11::detail::store::count(); expect_true(before == 0); - // TODO: This should be 1 but writable vectors are being double protected - expect_true(after - before == 2); + expect_true(after - before == 1); } } diff --git a/inst/include/cpp11/doubles.hpp b/inst/include/cpp11/doubles.hpp index a0a92608..44d24bca 100644 --- a/inst/include/cpp11/doubles.hpp +++ b/inst/include/cpp11/doubles.hpp @@ -8,7 +8,7 @@ #include "cpp11/R.hpp" // for SEXP, SEXPREC, Rf_allocVector, REAL #include "cpp11/as.hpp" // for as_sexp #include "cpp11/named_arg.hpp" // for named_arg -#include "cpp11/protect.hpp" // for SEXP, SEXPREC, REAL_ELT, R_Preserve... +#include "cpp11/protect.hpp" // for safe #include "cpp11/r_vector.hpp" // for vector, vector<>::proxy, vector<>::... #include "cpp11/sexp.hpp" // for sexp @@ -84,7 +84,6 @@ template <> inline r_vector::r_vector(std::initializer_list il) : cpp11::r_vector(safe[Rf_allocVector](REALSXP, il.size())), capacity_(il.size()) { - protect_ = detail::store::insert(data_); int n_protected = 0; try { @@ -100,7 +99,6 @@ inline r_vector::r_vector(std::initializer_list il) UNPROTECT(n_protected); }); } catch (const unwind_exception& e) { - detail::store::release(protect_); UNPROTECT(n_protected); throw e; } diff --git a/inst/include/cpp11/integers.hpp b/inst/include/cpp11/integers.hpp index dd14d018..97f2c6a7 100644 --- a/inst/include/cpp11/integers.hpp +++ b/inst/include/cpp11/integers.hpp @@ -9,7 +9,7 @@ #include "cpp11/as.hpp" // for as_sexp #include "cpp11/attribute_proxy.hpp" // for attribute_proxy #include "cpp11/named_arg.hpp" // for named_arg -#include "cpp11/protect.hpp" // for store +#include "cpp11/protect.hpp" // for safe #include "cpp11/r_vector.hpp" // for r_vector, r_vector<>::proxy #include "cpp11/sexp.hpp" // for sexp @@ -100,7 +100,6 @@ template <> inline r_vector::r_vector(std::initializer_list il) : cpp11::r_vector(safe[Rf_allocVector](INTSXP, il.size())), capacity_(il.size()) { - protect_ = detail::store::insert(data_); int n_protected = 0; try { @@ -116,7 +115,6 @@ inline r_vector::r_vector(std::initializer_list il) UNPROTECT(n_protected); }); } catch (const unwind_exception& e) { - detail::store::release(protect_); UNPROTECT(n_protected); throw e; } diff --git a/inst/include/cpp11/list.hpp b/inst/include/cpp11/list.hpp index d8e1bb79..3f258a65 100644 --- a/inst/include/cpp11/list.hpp +++ b/inst/include/cpp11/list.hpp @@ -5,7 +5,7 @@ #include "cpp11/R.hpp" // for SEXP, SEXPREC, SET_VECTOR_ELT #include "cpp11/attribute_proxy.hpp" // for attribute_proxy #include "cpp11/named_arg.hpp" // for named_arg -#include "cpp11/protect.hpp" // for store +#include "cpp11/protect.hpp" // for safe #include "cpp11/r_string.hpp" // for r_string #include "cpp11/r_vector.hpp" // for r_vector, r_vector<>::proxy #include "cpp11/sexp.hpp" // for sexp @@ -78,7 +78,6 @@ template <> inline r_vector::r_vector(std::initializer_list il) : cpp11::r_vector(safe[Rf_allocVector](VECSXP, il.size())), capacity_(il.size()) { - protect_ = detail::store::insert(data_); auto it = il.begin(); for (R_xlen_t i = 0; i < capacity_; ++i, ++it) { SET_VECTOR_ELT(data_, i, *it); @@ -89,7 +88,6 @@ template <> inline r_vector::r_vector(std::initializer_list il) : cpp11::r_vector(safe[Rf_allocVector](VECSXP, il.size())), capacity_(il.size()) { - protect_ = detail::store::insert(data_); int n_protected = 0; try { @@ -105,7 +103,6 @@ inline r_vector::r_vector(std::initializer_list il) UNPROTECT(n_protected); }); } catch (const unwind_exception& e) { - detail::store::release(protect_); UNPROTECT(n_protected); throw e; } diff --git a/inst/include/cpp11/logicals.hpp b/inst/include/cpp11/logicals.hpp index 8b1d74b2..076135a5 100644 --- a/inst/include/cpp11/logicals.hpp +++ b/inst/include/cpp11/logicals.hpp @@ -7,7 +7,7 @@ #include "cpp11/R.hpp" // for SEXP, SEXPREC, Rf_all... #include "cpp11/attribute_proxy.hpp" // for attribute_proxy #include "cpp11/named_arg.hpp" // for named_arg -#include "cpp11/protect.hpp" // for store +#include "cpp11/protect.hpp" // for safe #include "cpp11/r_bool.hpp" // for r_bool #include "cpp11/r_vector.hpp" // for r_vector, r_vector<>::proxy #include "cpp11/sexp.hpp" // for sexp @@ -80,7 +80,6 @@ inline bool operator==(const r_vector::proxy& lhs, r_bool rhs) { template <> inline r_vector::r_vector(std::initializer_list il) : cpp11::r_vector(Rf_allocVector(LGLSXP, il.size())), capacity_(il.size()) { - protect_ = detail::store::insert(data_); auto it = il.begin(); for (R_xlen_t i = 0; i < capacity_; ++i, ++it) { SET_LOGICAL_ELT(data_, i, *it); @@ -91,7 +90,6 @@ template <> inline r_vector::r_vector(std::initializer_list il) : cpp11::r_vector(safe[Rf_allocVector](LGLSXP, il.size())), capacity_(il.size()) { - protect_ = detail::store::insert(data_); int n_protected = 0; try { @@ -107,7 +105,6 @@ inline r_vector::r_vector(std::initializer_list il) UNPROTECT(n_protected); }); } catch (const unwind_exception& e) { - detail::store::release(protect_); UNPROTECT(n_protected); throw e; } diff --git a/inst/include/cpp11/r_vector.hpp b/inst/include/cpp11/r_vector.hpp index 655f7229..b1246659 100644 --- a/inst/include/cpp11/r_vector.hpp +++ b/inst/include/cpp11/r_vector.hpp @@ -214,8 +214,6 @@ using has_begin_fun = std::decay()))>; template class r_vector : public cpp11::r_vector { private: - SEXP protect_ = R_NilValue; - // These are necessary because type names are not directly accessible in // template inheritance using typename cpp11::r_vector::underlying_type; @@ -224,6 +222,9 @@ class r_vector : public cpp11::r_vector { using cpp11::r_vector::data_p_; using cpp11::r_vector::is_altrep_; using cpp11::r_vector::length_; + using cpp11::r_vector::protect_; + + using cpp11::r_vector::get_p; R_xlen_t capacity_ = 0; @@ -302,8 +303,6 @@ class r_vector : public cpp11::r_vector { explicit r_vector(const R_xlen_t size); - ~r_vector(); - r_vector(const r_vector& rhs); r_vector(r_vector&& rhs); @@ -660,27 +659,20 @@ inline typename r_vector::iterator r_vector::end() const { template inline r_vector::r_vector(const SEXP& data) - : cpp11::r_vector(safe[Rf_shallow_duplicate](data)), - protect_(detail::store::insert(data_)), - capacity_(length_) {} + : cpp11::r_vector(safe[Rf_shallow_duplicate](data)), capacity_(length_) {} template inline r_vector::r_vector(const SEXP& data, bool is_altrep) : cpp11::r_vector(safe[Rf_shallow_duplicate](data), is_altrep), - protect_(detail::store::insert(data_)), capacity_(length_) {} template inline r_vector::r_vector(SEXP&& data) - : cpp11::r_vector(data), - protect_(detail::store::insert(data_)), - capacity_(length_) {} + : cpp11::r_vector(data), capacity_(length_) {} template inline r_vector::r_vector(SEXP&& data, bool is_altrep) - : cpp11::r_vector(data, is_altrep), - protect_(detail::store::insert(data_)), - capacity_(length_) {} + : cpp11::r_vector(data, is_altrep), capacity_(length_) {} template template @@ -709,11 +701,6 @@ inline r_vector::r_vector(const R_xlen_t size) : r_vector() { resize(size); } -template -inline r_vector::~r_vector() { - detail::store::release(protect_); -} - #ifdef LONG_VECTOR_SUPPORT template inline typename r_vector::proxy r_vector::operator[](const int pos) const { @@ -793,22 +780,15 @@ inline typename r_vector::iterator r_vector::find(const r_string& name) co template inline r_vector::r_vector(const r_vector& rhs) - : cpp11::r_vector(safe[Rf_shallow_duplicate](rhs)), - protect_(detail::store::insert(data_)), - capacity_(rhs.capacity_) {} + : cpp11::r_vector(safe[Rf_shallow_duplicate](rhs)), capacity_(rhs.capacity_) {} template inline r_vector::r_vector(r_vector&& rhs) - : cpp11::r_vector(rhs), protect_(rhs.protect_), capacity_(rhs.capacity_) { - rhs.data_ = R_NilValue; - rhs.protect_ = R_NilValue; -} + : cpp11::r_vector(rhs), capacity_(rhs.capacity_) {} template inline r_vector::r_vector(const cpp11::r_vector& rhs) - : cpp11::r_vector(safe[Rf_shallow_duplicate](rhs)), - protect_(detail::store::insert(data_)), - capacity_(rhs.length_) {} + : cpp11::r_vector(safe[Rf_shallow_duplicate](rhs)), capacity_(rhs.length_) {} // We don't release the old object until the end in case we throw an exception // during the duplicate. @@ -818,17 +798,21 @@ inline r_vector& r_vector::operator=(const r_vector& rhs) { return *this; } - cpp11::r_vector::operator=(rhs); - - auto old_protect = protect_; + SEXP old_protect = protect_; + // We are in writable mode, so we must duplicate the `rhs` (since it isn't a temporary + // we can just take ownership of) and recompute the properties from the duplicate. data_ = safe[Rf_shallow_duplicate](rhs.data_); protect_ = detail::store::insert(data_); + is_altrep_ = ALTREP(data_); + data_p_ = get_p(is_altrep_, data_); + length_ = rhs.length_; - detail::store::release(old_protect); - + // Specific to writable capacity_ = rhs.capacity_; + detail::store::release(old_protect); + return *this; } @@ -838,17 +822,22 @@ inline r_vector& r_vector::operator=(r_vector&& rhs) { return *this; } - cpp11::r_vector::operator=(rhs); - SEXP old_protect = protect_; + // `rhs` is a temporary. Take ownership of its properties and then set its `protect_` + // value to `R_NilValue` since we will handle that now. We don't want the `rhs` + // destructor to release the object we are taking ownership of. data_ = rhs.data_; protect_ = rhs.protect_; + is_altrep_ = rhs.is_altrep_; + data_p_ = rhs.data_p_; + length_ = rhs.length_; - detail::store::release(old_protect); - + // Specific to writable capacity_ = rhs.capacity_; + detail::store::release(old_protect); + rhs.data_ = R_NilValue; rhs.protect_ = R_NilValue; diff --git a/inst/include/cpp11/raws.hpp b/inst/include/cpp11/raws.hpp index e518f01e..419ce63f 100644 --- a/inst/include/cpp11/raws.hpp +++ b/inst/include/cpp11/raws.hpp @@ -8,7 +8,7 @@ #include "cpp11/R.hpp" // for RAW, SEXP, SEXPREC, Rf_allocVector #include "cpp11/attribute_proxy.hpp" // for attribute_proxy #include "cpp11/named_arg.hpp" // for named_arg -#include "cpp11/protect.hpp" // for store +#include "cpp11/protect.hpp" // for safe #include "cpp11/r_vector.hpp" // for r_vector, r_vector<>::proxy #include "cpp11/sexp.hpp" // for sexp @@ -88,7 +88,6 @@ template <> inline r_vector::r_vector(std::initializer_list il) : cpp11::r_vector(safe[Rf_allocVector](RAWSXP, il.size())), capacity_(il.size()) { - protect_ = detail::store::insert(data_); auto it = il.begin(); for (R_xlen_t i = 0; i < capacity_; ++i, ++it) { data_p_[i] = *it; @@ -99,7 +98,6 @@ template <> inline r_vector::r_vector(std::initializer_list il) : cpp11::r_vector(safe[Rf_allocVector](RAWSXP, il.size())), capacity_(il.size()) { - protect_ = detail::store::insert(data_); int n_protected = 0; try { @@ -116,7 +114,6 @@ inline r_vector::r_vector(std::initializer_list il) UNPROTECT(n_protected); }); } catch (const unwind_exception& e) { - detail::store::release(protect_); UNPROTECT(n_protected); throw e; } diff --git a/inst/include/cpp11/strings.hpp b/inst/include/cpp11/strings.hpp index a9c56223..2e1390e0 100644 --- a/inst/include/cpp11/strings.hpp +++ b/inst/include/cpp11/strings.hpp @@ -7,7 +7,7 @@ #include "cpp11/as.hpp" // for as_sexp #include "cpp11/attribute_proxy.hpp" // for attribute_proxy #include "cpp11/named_arg.hpp" // for named_arg -#include "cpp11/protect.hpp" // for store +#include "cpp11/protect.hpp" // for safe #include "cpp11/r_string.hpp" // for r_string #include "cpp11/r_vector.hpp" // for r_vector, r_vector<>::proxy #include "cpp11/sexp.hpp" // for sexp @@ -94,9 +94,7 @@ inline SEXP alloc_if_charsxp(const SEXP data) { template <> inline r_vector::r_vector(const SEXP& data) - : cpp11::r_vector(alloc_or_copy(data)), - protect_(detail::store::insert(data_)), - capacity_(length_) { + : cpp11::r_vector(alloc_or_copy(data)), capacity_(length_) { if (TYPEOF(data) == CHARSXP) { SET_STRING_ELT(data_, 0, data); } @@ -104,9 +102,7 @@ inline r_vector::r_vector(const SEXP& data) template <> inline r_vector::r_vector(SEXP&& data) - : cpp11::r_vector(alloc_if_charsxp(data)), - protect_(detail::store::insert(data_)), - capacity_(length_) { + : cpp11::r_vector(alloc_if_charsxp(data)), capacity_(length_) { if (TYPEOF(data) == CHARSXP) { SET_STRING_ELT(data_, 0, data); } @@ -120,7 +116,6 @@ template <> inline r_vector::r_vector(std::initializer_list il) : cpp11::r_vector(safe[Rf_allocVector](STRSXP, il.size())), capacity_(il.size()) { - protect_ = detail::store::insert(data_); int n_protected = 0; try { @@ -136,7 +131,6 @@ inline r_vector::r_vector(std::initializer_list il) UNPROTECT(n_protected); }); } catch (const unwind_exception& e) { - detail::store::release(protect_); UNPROTECT(n_protected); throw e; } From 2f825814499ad4a0f0ebb406d1255d809784233a Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Sun, 28 Jul 2024 13:45:51 -0400 Subject: [PATCH 02/10] NEWS bullet --- NEWS.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/NEWS.md b/NEWS.md index f0d78a5d..fba02877 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,7 @@ # cpp11 (development version) +* Fixed an issue where writable vectors were being protected twice (#365). + * Removed usage of the following non-API functions: * `SETLENGTH()` * `SET_TRUELENGTH()` From d69ef9ae23f3344bd68d75a37de4b3a921c69572 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Sun, 28 Jul 2024 14:25:35 -0400 Subject: [PATCH 03/10] Add read only move constructor and move assignment operator --- NEWS.md | 3 ++ inst/include/cpp11/r_vector.hpp | 92 +++++++++++++++++++++++---------- 2 files changed, 69 insertions(+), 26 deletions(-) diff --git a/NEWS.md b/NEWS.md index fba02877..2c486c35 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # cpp11 (development version) +* Read only `r_vector`s now have a move constructor and move assignment + operator (#365). + * Fixed an issue where writable vectors were being protected twice (#365). * Removed usage of the following non-API functions: diff --git a/inst/include/cpp11/r_vector.hpp b/inst/include/cpp11/r_vector.hpp index b1246659..fec9c826 100644 --- a/inst/include/cpp11/r_vector.hpp +++ b/inst/include/cpp11/r_vector.hpp @@ -78,8 +78,14 @@ class r_vector { bool contains(const r_string& name) const; + // Same reasoning as `r_vector(const r_vector& rhs)` constructor r_vector& operator=(const r_vector& rhs) { - SEXP old_protect = protect_; + if (data_ == rhs.data_) { + return *this; + } + + // Release existing object that we protect + detail::store::release(protect_); data_ = rhs.data_; protect_ = detail::store::insert(data_); @@ -87,21 +93,62 @@ class r_vector { data_p_ = rhs.data_p_; length_ = rhs.length_; - detail::store::release(old_protect); + return *this; + }; + + // Same reasoning as `r_vector(r_vector&& rhs)` constructor + r_vector& operator=(r_vector&& rhs) { + if (data_ == rhs.data_) { + return *this; + } + + // Release existing object that we protect + detail::store::release(protect_); + + data_ = rhs.data_; + protect_ = rhs.protect_; + is_altrep_ = rhs.is_altrep_; + data_p_ = rhs.data_p_; + length_ = rhs.length_; + + // Important for `rhs.protect_`, extra check for everything else + rhs.data_ = R_NilValue; + rhs.protect_ = R_NilValue; + rhs.is_altrep_ = false; + rhs.data_p_ = nullptr; + rhs.length_ = 0; return *this; }; + // We are in read-only space so we can just copy over all properties except for + // `protect_`, which we need to manage on our own. `rhs` persists after this call, so we + // don't clear anything. r_vector(const r_vector& rhs) { - SEXP old_protect = protect_; - data_ = rhs.data_; protect_ = detail::store::insert(data_); is_altrep_ = rhs.is_altrep_; data_p_ = rhs.data_p_; length_ = rhs.length_; + }; + + // `rhs` here is a temporary value, it is going to be destructed right after this. + // Take ownership over all `rhs` details, including `protect_`. + // Importantly, set `rhs.protect_` to `R_NilValue` to prevent the `rhs` destructor from + // releasing the object that we now own. + r_vector(r_vector&& rhs) { + data_ = rhs.data_; + protect_ = rhs.protect_; + is_altrep_ = rhs.is_altrep_; + data_p_ = rhs.data_p_; + length_ = rhs.length_; - detail::store::release(old_protect); + // Important for `rhs.protect_`, extra check for everything else + rhs.data_ = R_NilValue; + rhs.protect_ = R_NilValue; + rhs.is_altrep_ = false; + rhs.data_p_ = nullptr; + rhs.length_ = 0; }; r_vector(const writable::r_vector& rhs) : r_vector(static_cast(rhs)) {} @@ -784,22 +831,25 @@ inline r_vector::r_vector(const r_vector& rhs) template inline r_vector::r_vector(r_vector&& rhs) - : cpp11::r_vector(rhs), capacity_(rhs.capacity_) {} + : cpp11::r_vector(std::move(rhs)), capacity_(rhs.capacity_) { + rhs.capacity_ = 0; +} template inline r_vector::r_vector(const cpp11::r_vector& rhs) : cpp11::r_vector(safe[Rf_shallow_duplicate](rhs)), capacity_(rhs.length_) {} -// We don't release the old object until the end in case we throw an exception -// during the duplicate. template inline r_vector& r_vector::operator=(const r_vector& rhs) { if (data_ == rhs.data_) { return *this; } + // We don't release the old object until the end in case we throw an exception + // during the duplicate. SEXP old_protect = protect_; + // Unlike with move assignment operator, we can't just call the read only parent method. // We are in writable mode, so we must duplicate the `rhs` (since it isn't a temporary // we can just take ownership of) and recompute the properties from the duplicate. data_ = safe[Rf_shallow_duplicate](rhs.data_); @@ -808,11 +858,11 @@ inline r_vector& r_vector::operator=(const r_vector& rhs) { data_p_ = get_p(is_altrep_, data_); length_ = rhs.length_; - // Specific to writable - capacity_ = rhs.capacity_; - detail::store::release(old_protect); + // Handle fields specific to writable + capacity_ = rhs.capacity_; + return *this; } @@ -822,24 +872,14 @@ inline r_vector& r_vector::operator=(r_vector&& rhs) { return *this; } - SEXP old_protect = protect_; + // Call parent read only move assignment operator to move + // all other properties, including protection handling + cpp11::r_vector::operator=(std::move(rhs)); - // `rhs` is a temporary. Take ownership of its properties and then set its `protect_` - // value to `R_NilValue` since we will handle that now. We don't want the `rhs` - // destructor to release the object we are taking ownership of. - data_ = rhs.data_; - protect_ = rhs.protect_; - is_altrep_ = rhs.is_altrep_; - data_p_ = rhs.data_p_; - length_ = rhs.length_; - - // Specific to writable + // Handle fields specific to writable capacity_ = rhs.capacity_; - detail::store::release(old_protect); - - rhs.data_ = R_NilValue; - rhs.protect_ = R_NilValue; + rhs.capacity_ = 0; return *this; } From a4477f3af7bb52db47ce99346869645ddfa0eb53 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 7 Aug 2024 14:24:41 -0400 Subject: [PATCH 04/10] Add more assignment operator tests --- cpp11test/src/test-integers.cpp | 18 ---- cpp11test/src/test-list.cpp | 17 ---- cpp11test/src/test-r_vector.cpp | 163 ++++++++++++++++++++++++++++++++ 3 files changed, 163 insertions(+), 35 deletions(-) create mode 100644 cpp11test/src/test-r_vector.cpp diff --git a/cpp11test/src/test-integers.cpp b/cpp11test/src/test-integers.cpp index 2b068d3c..6f876c57 100644 --- a/cpp11test/src/test-integers.cpp +++ b/cpp11test/src/test-integers.cpp @@ -2,7 +2,6 @@ #include "cpp11/doubles.hpp" #include "cpp11/function.hpp" #include "cpp11/integers.hpp" -#include "cpp11/protect.hpp" #include "cpp11/strings.hpp" #include @@ -208,21 +207,4 @@ context("integers-C++") { int y = NA_INTEGER; expect_true(cpp11::is_na(y)); } - - test_that("writable integer vector temporary isn't leaked (#338)") { - R_xlen_t before = cpp11::detail::store::count(); - - // +1 from `x` allocation - cpp11::writable::integers x(1); - - // Calls move assignment operator `operator=(r_vector&& rhs)` - // +1 from `rhs` allocation and move into `x` - // -1 from old `x` release - x = cpp11::writable::integers(1); - - R_xlen_t after = cpp11::detail::store::count(); - - expect_true(before == 0); - expect_true(after - before == 1); - } } diff --git a/cpp11test/src/test-list.cpp b/cpp11test/src/test-list.cpp index b5b61740..55f27c13 100644 --- a/cpp11test/src/test-list.cpp +++ b/cpp11test/src/test-list.cpp @@ -163,21 +163,4 @@ context("list-C++") { expect_true(Rf_xlength(y) == 0); expect_true(y != R_NilValue); } - - test_that("writable list vector temporary isn't leaked (#338)") { - R_xlen_t before = cpp11::detail::store::count(); - - // +1 from `x` allocation - cpp11::writable::list x(1); - - // Calls move assignment operator `operator=(r_vector&& rhs)` - // +1 from `rhs` allocation and move into `x` - // -1 from old `x` release - x = cpp11::writable::list(1); - - R_xlen_t after = cpp11::detail::store::count(); - - expect_true(before == 0); - expect_true(after - before == 1); - } } diff --git a/cpp11test/src/test-r_vector.cpp b/cpp11test/src/test-r_vector.cpp new file mode 100644 index 00000000..92b44f47 --- /dev/null +++ b/cpp11test/src/test-r_vector.cpp @@ -0,0 +1,163 @@ +#include "cpp11/integers.hpp" +#include "cpp11/list.hpp" +#include "cpp11/protect.hpp" + +#include + +context("r_vector-C++") { + test_that("writable vector temporary isn't leaked (integer) (#338)") { + R_xlen_t before = cpp11::detail::store::count(); + + // +1 from `x` allocation + cpp11::writable::integers x(1); + + // Calls move assignment operator `operator=(r_vector&& rhs)` + // +1 from `rhs` allocation and move into `x` + // -1 from old `x` release + x = cpp11::writable::integers(1); + + R_xlen_t after = cpp11::detail::store::count(); + + expect_true(before == 0); + expect_true(after - before == 1); + } + + test_that("writable vector temporary isn't leaked (list) (#338)") { + R_xlen_t before = cpp11::detail::store::count(); + + // +1 from `x` allocation + cpp11::writable::list x(1); + + // Calls move assignment operator `operator=(r_vector&& rhs)` + // +1 from `rhs` allocation and move into `x` + // -1 from old `x` release + x = cpp11::writable::list(1); + + R_xlen_t after = cpp11::detail::store::count(); + + expect_true(before == 0); + expect_true(after - before == 1); + } + + test_that("read-only vector move assignment operator clears properties (#365)") { + R_xlen_t before = cpp11::detail::store::count(); + + SEXP x = PROTECT(Rf_allocVector(INTSXP, 1)); + INTEGER(x)[0] = 1; + + // +1 from `y` creation + cpp11::integers y(x); + + // +0 for default constructor + cpp11::integers z; + + // Calls read only move assignment operator `operator=(r_vector&& rhs)` + // +0 when moving + z = std::move(y); + + R_xlen_t after = cpp11::detail::store::count(); + + // `y` properties have been cleared in the move + expect_true(y.data() == R_NilValue); + expect_true(y.size() == 0); + + expect_true(before == 0); + expect_true(after - before == 1); + + UNPROTECT(1); + } + + test_that("read-only vector copy assignment operator doesn't clear properties (#365)") { + R_xlen_t before = cpp11::detail::store::count(); + + SEXP x = PROTECT(Rf_allocVector(INTSXP, 1)); + INTEGER(x)[0] = 1; + + // +1 from `y` creation + cpp11::integers y(x); + + // +0 for default constructor + cpp11::integers z; + + expect_true(z.data() == R_NilValue); + expect_true(z.size() == 0); + + // Calls read only copy assignment operator `operator=(const r_vector& rhs)` + // +1 from additional protection of `y` (but not duplicating `y`'s data) + z = y; + + R_xlen_t after = cpp11::detail::store::count(); + + // `y` properties have not been cleared + expect_true(y.data() != R_NilValue); + expect_true(y.size() == 1); + + // `z` properties have been updated + expect_true(z.data() != R_NilValue); + expect_true(z.size() == 1); + + // And these are the same! This is all read-only, so no need to duplicate + expect_true(z.data() == y.data()); + + expect_true(before == 0); + expect_true(after - before == 2); + + UNPROTECT(1); + } + + test_that("writable vector move assignment operator clears properties (#365)") { + R_xlen_t before = cpp11::detail::store::count(); + + // +1 from `y` allocation + cpp11::writable::integers y(1); + + // +0 for default constructor + cpp11::writable::integers z; + + // Calls writable move assignment operator `operator=(r_vector&& rhs)` + // +0 when moving (also clears `capacity` in this case) + z = std::move(y); + + R_xlen_t after = cpp11::detail::store::count(); + + // `y` properties have been cleared in the move + expect_true(y.data() == R_NilValue); + expect_true(y.size() == 0); + + expect_true(before == 0); + expect_true(after - before == 1); + } + + test_that("writable vector copy assignment operator doesn't clear properties (#365)") { + R_xlen_t before = cpp11::detail::store::count(); + + // +1 from `y` allocation + cpp11::writable::integers y(1); + + // +0 for default constructor + cpp11::writable::integers z; + + expect_true(z.data() == R_NilValue); + expect_true(z.size() == 0); + + // Calls writable copy assignment operator `operator=(const r_vector& rhs)` + // +1 from protecting duplicate of `y` + z = y; + + R_xlen_t after = cpp11::detail::store::count(); + + // `y` properties have not been cleared + expect_true(y.data() != R_NilValue); + expect_true(y.size() == 1); + + // `z` properties have been updated + expect_true(z.data() != R_NilValue); + expect_true(z.size() == 1); + + // And these are not the same, we made a duplicate + expect_true(z.data() != y.data()); + + expect_true(before == 0); + expect_true(after - before == 2); + } +} From 6f065e4827b3290183bb921e387fee737c59589c Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 7 Aug 2024 15:24:02 -0400 Subject: [PATCH 05/10] Add some extra comments on read only vector from writable vector ctor --- inst/include/cpp11/r_vector.hpp | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/inst/include/cpp11/r_vector.hpp b/inst/include/cpp11/r_vector.hpp index fec9c826..64300ed1 100644 --- a/inst/include/cpp11/r_vector.hpp +++ b/inst/include/cpp11/r_vector.hpp @@ -151,7 +151,14 @@ class r_vector { rhs.length_ = 0; }; + // `rhs` here is writable, meaning the underlying `SEXP` could have more `capacity` than + // a read only equivalent would expect. This means we have to go through `SEXP` first, + // to truncate the writable data, and then we can wrap it in a read only `r_vector`. + // + // It would be the same scenario if we came from a writable temporary, i.e. + // `writable::r_vector&& rhs`, so we let this method handle both scenarios. r_vector(const writable::r_vector& rhs) : r_vector(static_cast(rhs)) {} + r_vector(named_arg) = delete; bool is_altrep() const; From a36b905452ea8a1deccb6ff37a99dbf59d824c15 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 7 Aug 2024 15:24:59 -0400 Subject: [PATCH 06/10] Slightly more explicit writable from read only lvalue ctor --- inst/include/cpp11/r_vector.hpp | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/inst/include/cpp11/r_vector.hpp b/inst/include/cpp11/r_vector.hpp index 64300ed1..db628ddc 100644 --- a/inst/include/cpp11/r_vector.hpp +++ b/inst/include/cpp11/r_vector.hpp @@ -844,7 +844,7 @@ inline r_vector::r_vector(r_vector&& rhs) template inline r_vector::r_vector(const cpp11::r_vector& rhs) - : cpp11::r_vector(safe[Rf_shallow_duplicate](rhs)), capacity_(rhs.length_) {} + : cpp11::r_vector(safe[Rf_shallow_duplicate](rhs.data_)), capacity_(rhs.length_) {} template inline r_vector& r_vector::operator=(const r_vector& rhs) { From cab252d3cc3dfe4e48c5e1444aee5111fa163a41 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 7 Aug 2024 15:25:51 -0400 Subject: [PATCH 07/10] Fix issue related to writable move constructor And add more related tests --- cpp11test/src/test-r_vector.cpp | 135 +++++++++++++++++++++++++++++--- inst/include/cpp11/r_vector.hpp | 23 +++++- 2 files changed, 145 insertions(+), 13 deletions(-) diff --git a/cpp11test/src/test-r_vector.cpp b/cpp11test/src/test-r_vector.cpp index 92b44f47..c4280544 100644 --- a/cpp11test/src/test-r_vector.cpp +++ b/cpp11test/src/test-r_vector.cpp @@ -39,7 +39,7 @@ context("r_vector-C++") { expect_true(after - before == 1); } - test_that("read-only vector move assignment operator clears properties (#365)") { + test_that("read-only vector copy constructor doesn't clear properties (#365)") { R_xlen_t before = cpp11::detail::store::count(); SEXP x = PROTECT(Rf_allocVector(INTSXP, 1)); @@ -48,12 +48,42 @@ context("r_vector-C++") { // +1 from `y` creation cpp11::integers y(x); - // +0 for default constructor - cpp11::integers z; + // Calls read only copy constructor + // No duplication of `y`'s data is done + // +1 when adding `z`'s protection to the data + cpp11::integers z(y); - // Calls read only move assignment operator `operator=(r_vector&& rhs)` + R_xlen_t after = cpp11::detail::store::count(); + + // `y` properties have not been cleared + expect_true(y.data() != R_NilValue); + expect_true(y.size() == 1); + + // `z` owns them now + expect_true(z.data() != R_NilValue); + expect_true(z.size() == 1); + + // And these are the same! This is all read-only, so no need to duplicate + expect_true(z.data() == y.data()); + + expect_true(before == 0); + expect_true(after - before == 2); + + UNPROTECT(1); + } + + test_that("read-only vector move constructor clears properties (#365)") { + R_xlen_t before = cpp11::detail::store::count(); + + SEXP x = PROTECT(Rf_allocVector(INTSXP, 1)); + INTEGER(x)[0] = 1; + + // +1 from `y` creation + cpp11::integers y(x); + + // Calls read only move constructor // +0 when moving - z = std::move(y); + cpp11::integers z(std::move(y)); R_xlen_t after = cpp11::detail::store::count(); @@ -61,12 +91,67 @@ context("r_vector-C++") { expect_true(y.data() == R_NilValue); expect_true(y.size() == 0); + // `z` owns them now + expect_true(z.data() != R_NilValue); + expect_true(z.size() == 1); + expect_true(before == 0); expect_true(after - before == 1); UNPROTECT(1); } + test_that("writable vector copy constructor does not clear properties (#365)") { + R_xlen_t before = cpp11::detail::store::count(); + + // +1 from `y` allocation + cpp11::writable::integers y(1); + + // Calls writable copy constructor + // +1 from duplicating `y` and protecting result + cpp11::writable::integers z(y); + + R_xlen_t after = cpp11::detail::store::count(); + + // `y` properties have not been cleared + expect_true(y.data() != R_NilValue); + expect_true(y.size() == 1); + + // `z` is a duplicate of `y` + expect_true(z.data() != R_NilValue); + expect_true(z.size() == 1); + + // And these are not the same! This is writable, so a duplication occurred. + expect_true(z.data() != y.data()); + + expect_true(before == 0); + expect_true(after - before == 2); + } + + test_that("writable vector move constructor clears properties (#365)") { + R_xlen_t before = cpp11::detail::store::count(); + + // +1 from `y` allocation + cpp11::writable::integers y(1); + + // Calls writable move constructor + // +0 when moving + cpp11::writable::integers z(std::move(y)); + + R_xlen_t after = cpp11::detail::store::count(); + + // `y` properties have been cleared in the move + expect_true(y.data() == R_NilValue); + expect_true(y.size() == 0); + + // `z` owns them now + expect_true(z.data() != R_NilValue); + expect_true(z.size() == 1); + + expect_true(before == 0); + expect_true(after - before == 1); + } + test_that("read-only vector copy assignment operator doesn't clear properties (#365)") { R_xlen_t before = cpp11::detail::store::count(); @@ -105,17 +190,20 @@ context("r_vector-C++") { UNPROTECT(1); } - test_that("writable vector move assignment operator clears properties (#365)") { + test_that("read-only vector move assignment operator clears properties (#365)") { R_xlen_t before = cpp11::detail::store::count(); - // +1 from `y` allocation - cpp11::writable::integers y(1); + SEXP x = PROTECT(Rf_allocVector(INTSXP, 1)); + INTEGER(x)[0] = 1; + + // +1 from `y` creation + cpp11::integers y(x); // +0 for default constructor - cpp11::writable::integers z; + cpp11::integers z; - // Calls writable move assignment operator `operator=(r_vector&& rhs)` - // +0 when moving (also clears `capacity` in this case) + // Calls read only move assignment operator `operator=(r_vector&& rhs)` + // +0 when moving z = std::move(y); R_xlen_t after = cpp11::detail::store::count(); @@ -126,6 +214,8 @@ context("r_vector-C++") { expect_true(before == 0); expect_true(after - before == 1); + + UNPROTECT(1); } test_that("writable vector copy assignment operator doesn't clear properties (#365)") { @@ -160,4 +250,27 @@ context("r_vector-C++") { expect_true(before == 0); expect_true(after - before == 2); } + + test_that("writable vector move assignment operator clears properties (#365)") { + R_xlen_t before = cpp11::detail::store::count(); + + // +1 from `y` allocation + cpp11::writable::integers y(1); + + // +0 for default constructor + cpp11::writable::integers z; + + // Calls writable move assignment operator `operator=(r_vector&& rhs)` + // +0 when moving (also clears `capacity` in this case) + z = std::move(y); + + R_xlen_t after = cpp11::detail::store::count(); + + // `y` properties have been cleared in the move + expect_true(y.data() == R_NilValue); + expect_true(y.size() == 0); + + expect_true(before == 0); + expect_true(after - before == 1); + } } diff --git a/inst/include/cpp11/r_vector.hpp b/inst/include/cpp11/r_vector.hpp index db628ddc..af2f0f68 100644 --- a/inst/include/cpp11/r_vector.hpp +++ b/inst/include/cpp11/r_vector.hpp @@ -837,8 +837,27 @@ inline r_vector::r_vector(const r_vector& rhs) : cpp11::r_vector(safe[Rf_shallow_duplicate](rhs)), capacity_(rhs.capacity_) {} template -inline r_vector::r_vector(r_vector&& rhs) - : cpp11::r_vector(std::move(rhs)), capacity_(rhs.capacity_) { +inline r_vector::r_vector(r_vector&& rhs) { + // We don't want to pass through to the read-only constructor from a + // `writable::r_vector&& rhs` as that forces a truncation to be able to generate + // a well-formed read-only vector. Instead, we take advantage of the fact that we + // are going from writable input to writable output and just move everything over. + // + // This ends up looking very similar to the equivalent read-only constructor from a + // read-only `r_vector&& rhs`, with the addition of moving the capacity. + data_ = rhs.data_; + protect_ = rhs.protect_; + is_altrep_ = rhs.is_altrep_; + data_p_ = rhs.data_p_; + length_ = rhs.length_; + capacity_ = rhs.capacity_; + + // Important for `rhs.protect_`, extra check for everything else + rhs.data_ = R_NilValue; + rhs.protect_ = R_NilValue; + rhs.is_altrep_ = false; + rhs.data_p_ = nullptr; + rhs.length_ = 0; rhs.capacity_ = 0; } From d1667fcc2603c2dea099e3f3c97eb9b7c03b0e96 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 7 Aug 2024 16:20:18 -0400 Subject: [PATCH 08/10] Add extra test for capacity tracking --- cpp11test/src/test-r_vector.cpp | 22 ++++++++++++++++++++++ 1 file changed, 22 insertions(+) diff --git a/cpp11test/src/test-r_vector.cpp b/cpp11test/src/test-r_vector.cpp index c4280544..3358a64c 100644 --- a/cpp11test/src/test-r_vector.cpp +++ b/cpp11test/src/test-r_vector.cpp @@ -273,4 +273,26 @@ context("r_vector-C++") { expect_true(before == 0); expect_true(after - before == 1); } + + test_that("writable vector copy constructor correctly tracks the `capacity_`") { + cpp11::writable::integers x(2); + x[0] = 1; + x[1] = 2; + + // Doubles the capacity from 2 to 4 + x.push_back(3); + + // Calls writable copy constructor. + // Should duplicate without truncations and retain same capacity. + cpp11::writable::integers y(x); + + // In the past, we truncated (i.e. to size 3) but retained the same capacity of 4, + // so this could try to push without first resizing. + y.push_back(4); + + expect_true(y[0] == 1); + expect_true(y[1] == 2); + expect_true(y[2] == 3); + expect_true(y[3] == 4); + } } From 76e8b9a21b1eee642be0a9df1bb2043ecec485df Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 8 Aug 2024 12:00:46 -0400 Subject: [PATCH 09/10] Add a test for the read only copy constructor from writable vectors --- cpp11test/src/test-r_vector.cpp | 30 ++++++++++++++++++++++++++++++ 1 file changed, 30 insertions(+) diff --git a/cpp11test/src/test-r_vector.cpp b/cpp11test/src/test-r_vector.cpp index 3358a64c..b665c533 100644 --- a/cpp11test/src/test-r_vector.cpp +++ b/cpp11test/src/test-r_vector.cpp @@ -295,4 +295,34 @@ context("r_vector-C++") { expect_true(y[2] == 3); expect_true(y[3] == 4); } + + test_that( + "read only vector copy constructor from a writable vector correctly truncates") { + cpp11::writable::integers x(2); + x[0] = 1; + x[1] = 2; + + // Doubles the capacity from 2 to 4, meaning the underlying SEXP has length 4 now. + x.push_back(3); + expect_true(Rf_xlength(x.data()) == 4); + + // Calls read only copy constructor from a writable vector. + // Should truncate the SEXP before wrapping in a read only vector. + cpp11::integers y(x); + expect_true(Rf_xlength(y.data()) == 3); + + // `x` is still in a good state + expect_true(x.data() != R_NilValue); + expect_true(x.size() == 3); + + // Even if we get a temporary writable vector, that goes through the same copy + // constructor as above, because we still have to truncate before taking ownership. + cpp11::integers z(std::move(x)); + expect_true(Rf_xlength(z.data()) == 3); + + // So technically `x` is still in a working state after this, although that is + // implementation defined and up to us to decide on + expect_true(x.data() != R_NilValue); + expect_true(x.size() == 3); + } } From f6d8522e9cabbb1c2b86b46b8ef2f1d2f9bd4a45 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 8 Aug 2024 13:49:24 -0400 Subject: [PATCH 10/10] Tiny tweak --- inst/include/cpp11/r_vector.hpp | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/inst/include/cpp11/r_vector.hpp b/inst/include/cpp11/r_vector.hpp index af2f0f68..3b48e1d9 100644 --- a/inst/include/cpp11/r_vector.hpp +++ b/inst/include/cpp11/r_vector.hpp @@ -883,12 +883,10 @@ inline r_vector& r_vector::operator=(const r_vector& rhs) { is_altrep_ = ALTREP(data_); data_p_ = get_p(is_altrep_, data_); length_ = rhs.length_; + capacity_ = rhs.capacity_; detail::store::release(old_protect); - // Handle fields specific to writable - capacity_ = rhs.capacity_; - return *this; }