You are viewing a plain text version of this content. The canonical link for it is here.
Posted to github@arrow.apache.org by "paleolimbot (via GitHub)" <gi...@apache.org> on 2023/05/18 14:27:20 UTC

[GitHub] [arrow-adbc] paleolimbot opened a new pull request, #693: feat(r): Add scoping + lifecycle helpers

paleolimbot opened a new pull request, #693:
URL: https://github.com/apache/arrow-adbc/pull/693

   TODO: tests, and something about the pointer moving isn't working.
   
   See https://github.com/r-dbi/adbc/discussions/4


-- 
This is an automated message from the Apache Git Service.
To respond to the message, please log on to GitHub and use the
URL above to go to the specific comment.

To unsubscribe, e-mail: github-unsubscribe@arrow.apache.org

For queries about this service, please contact Infrastructure at:
users@infra.apache.org


[GitHub] [arrow-adbc] paleolimbot commented on pull request #693: feat(r): Add scoping + lifecycle helpers

Posted by "paleolimbot (via GitHub)" <gi...@apache.org>.
paleolimbot commented on PR #693:
URL: https://github.com/apache/arrow-adbc/pull/693#issuecomment-1561123563

   This is blocking some other work so I'm going to merge...feel free to leave your comments whenever you're ready and I will follow up with another PR!


-- 
This is an automated message from the Apache Git Service.
To respond to the message, please log on to GitHub and use the
URL above to go to the specific comment.

To unsubscribe, e-mail: github-unsubscribe@arrow.apache.org

For queries about this service, please contact Infrastructure at:
users@infra.apache.org


[GitHub] [arrow-adbc] krlmlr commented on a diff in pull request #693: feat(r): Add scoping + lifecycle helpers

Posted by "krlmlr (via GitHub)" <gi...@apache.org>.
krlmlr commented on code in PR #693:
URL: https://github.com/apache/arrow-adbc/pull/693#discussion_r1205474561


##########
r/adbcdrivermanager/R/adbc.R:
##########
@@ -118,13 +122,18 @@ adbc_connection_init.default <- function(database, ...) {
 adbc_connection_init_default <- function(database, options = NULL, subclass = character()) {
   connection <- .Call(RAdbcConnectionNew)
   connection$database <- database
-  error <- adbc_allocate_error()
-  status <- .Call(RAdbcConnectionInit, connection, database, error)
-  stop_for_error(status, error)
 
-  adbc_connection_set_options(connection, options)
-  class(connection) <- c(subclass, class(connection))
-  connection
+  with_adbc(connection, {

Review Comment:
   Since we also have `local_adbc()`, any reason to prefer the `with_()` variant?



##########
r/adbcdrivermanager/R/helpers.R:
##########
@@ -0,0 +1,170 @@
+# Licensed to the Apache Software Foundation (ASF) under one
+# or more contributor license agreements.  See the NOTICE file
+# distributed with this work for additional information
+# regarding copyright ownership.  The ASF licenses this file
+# to you under the Apache License, Version 2.0 (the
+# "License"); you may not use this file except in compliance
+# with the License.  You may obtain a copy of the License at
+#
+#   http://www.apache.org/licenses/LICENSE-2.0
+#
+# Unless required by applicable law or agreed to in writing,
+# software distributed under the License is distributed on an
+# "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
+# KIND, either express or implied.  See the License for the
+# specific language governing permissions and limitations
+# under the License.
+
+#' Cleanup helpers
+#'
+#' Managing the lifecycle of databases, connections, and statements can
+#' be complex and error-prone. The R objects that wrap the underlying ADBC
+#' pointers will perform cleanup in the correct order if you rely on garbage
+#' collection (i.e., do nothing and let the objects go out of scope); however
+#' it is good practice to explicitly clean up these objects. These helpers
+#' are designed to make explicit and predictable cleanup easy to accomplish.
+#'
+#' Note that you can use [adbc_connection_join()],
+#' [adbc_statement_join()], and [adbc_stream_join()]
+#' to tie the lifecycle of the parent object to that of the child object.
+#' These functions mark any previous references to the parent object as
+#' released so you can still use local and with helpers to manage the parent
+#' object before it is joined.
+#'
+#' @param x An ADBC database, ADBC connection, ADBC statement, or
+#'   nanoarrow_array_stream returned from calls to an ADBC function.
+#' @param code Code to execute before cleaning up the input.
+#' @param .local_envir The execution environment whose scope should be tied
+#'   to the input.
+#'
+#' @return
+#'   - `with_adbc()` returns the result of `code`
+#'   - `local_adbc()` returns the input, invisibly.
+#' @export
+#'
+#' @examples
+#' # Using with_adbc():
+#' with_adbc(db <- adbc_database_init(adbc_driver_void()), {
+#'   with_adbc(con <- adbc_connection_init(db), {
+#'     with_adbc(stmt <- adbc_statement_init(con), {
+#'       # adbc_statement_set_sql_query(stmt, "SELECT * FROM foofy")
+#'       # adbc_statement_execute_query(stmt)
+#'       "some result"
+#'     })
+#'   })
+#' })
+#'
+#' # Using local_adbc_*() (works best within a function, test, or local())
+#' local({
+#'   db <- local_adbc(adbc_database_init(adbc_driver_void()))
+#'   con <- local_adbc(adbc_connection_init(db))
+#'   stmt <- local_adbc(adbc_statement_init(con))
+#'   # adbc_statement_set_sql_query(stmt, "SELECT * FROM foofy")
+#'   # adbc_statement_execute_query(stmt)
+#'   "some result"
+#' })
+#'
+with_adbc <- function(x, code) {
+  assert_adbc(x)
+
+  on.exit(adbc_release_non_null(x))
+  force(code)
+}
+
+#' @rdname with_adbc
+#' @export
+local_adbc <- function(x, .local_envir = parent.frame()) {
+  assert_adbc(x)
+
+  withr::defer(adbc_release_non_null(x), envir = .local_envir)
+  invisible(x)
+}
+
+#' Join the lifecycle of a unique parent to its child
+#'
+#' It is occasionally useful to return a connection, statement, or stream
+#' from a function that was created from a unique parent. These helpers
+#' tie the lifecycle of a unique parent object to its child such that the
+#' parent object is released predictably and immediately after the child.
+#' These functions will invalidate all references to the previous R object.
+#'
+#' @param database A database created with [adbc_database_init()]
+#' @param connection A connection created with [adbc_connection_init()]
+#' @param statement A statement created with [adbc_statement_init()]
+#' @param stream A [nanoarrow_array_stream][nanoarrow::as_nanoarrow_array_stream]
+#' @inheritParams with_adbc
+#'
+#' @return The input, invisibly.
+#' @export
+#'
+#' @examples
+#' # Use local_adbc to ensure prompt cleanup on error;
+#' # use join functions to return a single object that manages
+#' # the lifecycle of all three.
+#' stmt <- local({
+#'   db <- local_adbc(adbc_database_init(adbc_driver_log()))
+#'
+#'   con <- local_adbc(adbc_connection_init(db))
+#'   adbc_connection_join(con, db)
+#'
+#'   stmt <- local_adbc(adbc_statement_init(con))
+#'   adbc_statement_join(stmt, con)
+#'
+#'   adbc_xptr_move(stmt)
+#' })
+#'
+#' # Everything is released immediately when the last object is released
+#' adbc_statement_release(stmt)
+#'
+adbc_connection_join <- function(connection, database) {
+  assert_adbc(connection, "adbc_connection")
+  assert_adbc(database, "adbc_database")
+
+  connection$.release_database <- TRUE
+  connection$database <- adbc_xptr_move(database)

Review Comment:
   Can `$database` already exist here?



##########
r/adbcdrivermanager/R/utils.R:
##########
@@ -94,3 +94,102 @@ str.adbc_xptr <- function(object, ...) {
   str(env_proxy, ...)
   invisible(object)
 }
+
+
+#' Low-level pointer details
+#'
+#' - `adbc_xptr_move()` allocates a fresh R object and moves all values pointed
+#'   to by `x` into it. The original R object is invalidated by zeroing its
+#'   content. This is useful when returning from a function where
+#'   [lifecycle helpers][with_adbc] were used to manage the original
+#'   object.
+#' - `adbc_xptr_is_valid()` provides a means by which to test for an invalidated
+#'   pointer.
+#'
+#' @param x An 'adbc_database', 'adbc_connection', 'adbc_statement', or
+#'   'nanoarrow_array_stream'
+#'
+#' @return
+#' - `adbc_xptr_move()`: A freshly-allocated R object identical to `x`
+#' - `adbc_xptr_is_valid()`: Returns FALSE if the ADBC object pointed to by `x`
+#'   has been invalidated.
+#' @export
+#'
+#' @examples
+#' db <- adbc_database_init(adbc_driver_void())
+#' adbc_xptr_is_valid(db)
+#' db_new <- adbc_xptr_move(db)
+#' adbc_xptr_is_valid(db)
+#' adbc_xptr_is_valid(db_new)
+#'
+adbc_xptr_move <- function(x) {
+  if (inherits(x, "adbc_database")) {
+    .Call(RAdbcMoveDatabase, x)
+  } else if (inherits(x, "adbc_connection")) {
+    .Call(RAdbcMoveConnection, x)
+  } else if (inherits(x, "adbc_statement")) {
+    .Call(RAdbcMoveStatement, x)
+  } else if (inherits(x, "nanoarrow_array_stream")) {

Review Comment:
   Is this class also the responsibility of this function? Do we even need the genericity of `adbc_xptr_move()`, perhaps exposing specialized `adbc_xptr_move_database()` and friends? Same for `_is_valid()` .



##########
r/adbcdrivermanager/R/utils.R:
##########
@@ -94,3 +94,102 @@ str.adbc_xptr <- function(object, ...) {
   str(env_proxy, ...)
   invisible(object)
 }
+
+
+#' Low-level pointer details
+#'
+#' - `adbc_xptr_move()` allocates a fresh R object and moves all values pointed
+#'   to by `x` into it. The original R object is invalidated by zeroing its
+#'   content. This is useful when returning from a function where
+#'   [lifecycle helpers][with_adbc] were used to manage the original
+#'   object.
+#' - `adbc_xptr_is_valid()` provides a means by which to test for an invalidated
+#'   pointer.
+#'
+#' @param x An 'adbc_database', 'adbc_connection', 'adbc_statement', or
+#'   'nanoarrow_array_stream'
+#'
+#' @return
+#' - `adbc_xptr_move()`: A freshly-allocated R object identical to `x`
+#' - `adbc_xptr_is_valid()`: Returns FALSE if the ADBC object pointed to by `x`
+#'   has been invalidated.
+#' @export
+#'
+#' @examples
+#' db <- adbc_database_init(adbc_driver_void())
+#' adbc_xptr_is_valid(db)
+#' db_new <- adbc_xptr_move(db)
+#' adbc_xptr_is_valid(db)
+#' adbc_xptr_is_valid(db_new)
+#'
+adbc_xptr_move <- function(x) {
+  if (inherits(x, "adbc_database")) {
+    .Call(RAdbcMoveDatabase, x)
+  } else if (inherits(x, "adbc_connection")) {
+    .Call(RAdbcMoveConnection, x)
+  } else if (inherits(x, "adbc_statement")) {
+    .Call(RAdbcMoveStatement, x)
+  } else if (inherits(x, "nanoarrow_array_stream")) {
+    stream <- nanoarrow::nanoarrow_allocate_array_stream()
+    nanoarrow::nanoarrow_pointer_move(x, stream)
+    stream
+  } else {
+    assert_adbc(x)
+  }
+}
+
+#' @rdname adbc_xptr_move
+#' @export
+adbc_xptr_is_valid <- function(x) {
+  if (inherits(x, "adbc_database")) {
+    .Call(RAdbcDatabaseValid, x)
+  } else if (inherits(x, "adbc_connection")) {
+    .Call(RAdbcConnectionValid, x)
+  } else if (inherits(x, "adbc_statement")) {
+    .Call(RAdbcStatementValid, x)
+  } else if (inherits(x, "nanoarrow_array_stream")) {
+    nanoarrow::nanoarrow_pointer_is_valid(x)
+  } else {
+    assert_adbc(x)
+  }
+}
+
+# Usually we want errors for an attempt at double release; however,
+# the helpers we want to be compatible with adbc_xptr_move() which sets the
+# managed pointer to NULL.
+adbc_release_non_null <- function(x) {

Review Comment:
   Can "release" be implemented via "move" + throw away result?



##########
r/adbcdrivermanager/R/adbc.R:
##########
@@ -151,6 +160,11 @@ adbc_connection_set_options <- function(connection, options) {
 #' @rdname adbc_connection_init
 #' @export
 adbc_connection_release <- function(connection) {
+  if (isTRUE(connection$.release_database)) {
+    database <- connection$database
+    on.exit(adbc_database_release(database))

Review Comment:
   Do you mean to release the database even in case of an error? What error can happen when releasing?



-- 
This is an automated message from the Apache Git Service.
To respond to the message, please log on to GitHub and use the
URL above to go to the specific comment.

To unsubscribe, e-mail: github-unsubscribe@arrow.apache.org

For queries about this service, please contact Infrastructure at:
users@infra.apache.org


[GitHub] [arrow-adbc] paleolimbot merged pull request #693: feat(r): Add scoping + lifecycle helpers

Posted by "paleolimbot (via GitHub)" <gi...@apache.org>.
paleolimbot merged PR #693:
URL: https://github.com/apache/arrow-adbc/pull/693


-- 
This is an automated message from the Apache Git Service.
To respond to the message, please log on to GitHub and use the
URL above to go to the specific comment.

To unsubscribe, e-mail: github-unsubscribe@arrow.apache.org

For queries about this service, please contact Infrastructure at:
users@infra.apache.org


[GitHub] [arrow-adbc] paleolimbot commented on a diff in pull request #693: feat(r): Add scoping + lifecycle helpers

Posted by "paleolimbot (via GitHub)" <gi...@apache.org>.
paleolimbot commented on code in PR #693:
URL: https://github.com/apache/arrow-adbc/pull/693#discussion_r1205550599


##########
r/adbcdrivermanager/R/adbc.R:
##########
@@ -151,6 +160,11 @@ adbc_connection_set_options <- function(connection, options) {
 #' @rdname adbc_connection_init
 #' @export
 adbc_connection_release <- function(connection) {
+  if (isTRUE(connection$.release_database)) {
+    database <- connection$database
+    on.exit(adbc_database_release(database))

Review Comment:
   That's a good point...it probably shouldn't. The main error that happens when releasing is (1) something like "connection busy" (SQLite will give you this if you have a sqlite_stmt still open) or (2) double release (something like "invalid state"). In the case of "connection busy", attempting to release the underlying database is probably a bad idea.
   
   Of course, when all this happens automatically (e.g., in an exit handler), maybe it's best to try to release as much as possible?



##########
r/adbcdrivermanager/R/adbc.R:
##########
@@ -118,13 +122,18 @@ adbc_connection_init.default <- function(database, ...) {
 adbc_connection_init_default <- function(database, options = NULL, subclass = character()) {
   connection <- .Call(RAdbcConnectionNew)
   connection$database <- database
-  error <- adbc_allocate_error()
-  status <- .Call(RAdbcConnectionInit, connection, database, error)
-  stop_for_error(status, error)
 
-  adbc_connection_set_options(connection, options)
-  class(connection) <- c(subclass, class(connection))
-  connection
+  with_adbc(connection, {

Review Comment:
   I did that because `local_adbc()` requires withr and `with_adbc()` doesn't. I normally wouldn't care about a withr dependency but the driver manager currently only depends on nanoarrow, which as zero dependencies (and we could even remove the nanoarrow dependency in a pinch).



##########
r/adbcdrivermanager/R/helpers.R:
##########
@@ -0,0 +1,170 @@
+# Licensed to the Apache Software Foundation (ASF) under one
+# or more contributor license agreements.  See the NOTICE file
+# distributed with this work for additional information
+# regarding copyright ownership.  The ASF licenses this file
+# to you under the Apache License, Version 2.0 (the
+# "License"); you may not use this file except in compliance
+# with the License.  You may obtain a copy of the License at
+#
+#   http://www.apache.org/licenses/LICENSE-2.0
+#
+# Unless required by applicable law or agreed to in writing,
+# software distributed under the License is distributed on an
+# "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
+# KIND, either express or implied.  See the License for the
+# specific language governing permissions and limitations
+# under the License.
+
+#' Cleanup helpers
+#'
+#' Managing the lifecycle of databases, connections, and statements can
+#' be complex and error-prone. The R objects that wrap the underlying ADBC
+#' pointers will perform cleanup in the correct order if you rely on garbage
+#' collection (i.e., do nothing and let the objects go out of scope); however
+#' it is good practice to explicitly clean up these objects. These helpers
+#' are designed to make explicit and predictable cleanup easy to accomplish.
+#'
+#' Note that you can use [adbc_connection_join()],
+#' [adbc_statement_join()], and [adbc_stream_join()]
+#' to tie the lifecycle of the parent object to that of the child object.
+#' These functions mark any previous references to the parent object as
+#' released so you can still use local and with helpers to manage the parent
+#' object before it is joined.
+#'
+#' @param x An ADBC database, ADBC connection, ADBC statement, or
+#'   nanoarrow_array_stream returned from calls to an ADBC function.
+#' @param code Code to execute before cleaning up the input.
+#' @param .local_envir The execution environment whose scope should be tied
+#'   to the input.
+#'
+#' @return
+#'   - `with_adbc()` returns the result of `code`
+#'   - `local_adbc()` returns the input, invisibly.
+#' @export
+#'
+#' @examples
+#' # Using with_adbc():
+#' with_adbc(db <- adbc_database_init(adbc_driver_void()), {
+#'   with_adbc(con <- adbc_connection_init(db), {
+#'     with_adbc(stmt <- adbc_statement_init(con), {
+#'       # adbc_statement_set_sql_query(stmt, "SELECT * FROM foofy")
+#'       # adbc_statement_execute_query(stmt)
+#'       "some result"
+#'     })
+#'   })
+#' })
+#'
+#' # Using local_adbc_*() (works best within a function, test, or local())
+#' local({
+#'   db <- local_adbc(adbc_database_init(adbc_driver_void()))
+#'   con <- local_adbc(adbc_connection_init(db))
+#'   stmt <- local_adbc(adbc_statement_init(con))
+#'   # adbc_statement_set_sql_query(stmt, "SELECT * FROM foofy")
+#'   # adbc_statement_execute_query(stmt)
+#'   "some result"
+#' })
+#'
+with_adbc <- function(x, code) {
+  assert_adbc(x)
+
+  on.exit(adbc_release_non_null(x))
+  force(code)
+}
+
+#' @rdname with_adbc
+#' @export
+local_adbc <- function(x, .local_envir = parent.frame()) {
+  assert_adbc(x)
+
+  withr::defer(adbc_release_non_null(x), envir = .local_envir)
+  invisible(x)
+}
+
+#' Join the lifecycle of a unique parent to its child
+#'
+#' It is occasionally useful to return a connection, statement, or stream
+#' from a function that was created from a unique parent. These helpers
+#' tie the lifecycle of a unique parent object to its child such that the
+#' parent object is released predictably and immediately after the child.
+#' These functions will invalidate all references to the previous R object.
+#'
+#' @param database A database created with [adbc_database_init()]
+#' @param connection A connection created with [adbc_connection_init()]
+#' @param statement A statement created with [adbc_statement_init()]
+#' @param stream A [nanoarrow_array_stream][nanoarrow::as_nanoarrow_array_stream]
+#' @inheritParams with_adbc
+#'
+#' @return The input, invisibly.
+#' @export
+#'
+#' @examples
+#' # Use local_adbc to ensure prompt cleanup on error;
+#' # use join functions to return a single object that manages
+#' # the lifecycle of all three.
+#' stmt <- local({
+#'   db <- local_adbc(adbc_database_init(adbc_driver_log()))
+#'
+#'   con <- local_adbc(adbc_connection_init(db))
+#'   adbc_connection_join(con, db)
+#'
+#'   stmt <- local_adbc(adbc_statement_init(con))
+#'   adbc_statement_join(stmt, con)
+#'
+#'   adbc_xptr_move(stmt)
+#' })
+#'
+#' # Everything is released immediately when the last object is released
+#' adbc_statement_release(stmt)
+#'
+adbc_connection_join <- function(connection, database) {
+  assert_adbc(connection, "adbc_connection")
+  assert_adbc(database, "adbc_database")
+
+  connection$.release_database <- TRUE
+  connection$database <- adbc_xptr_move(database)

Review Comment:
   It does already exist here; however, after `adbc_xptr_move()` it will be invalid (the `AdbcDatabase` struct will have been zeroed). I suppose it would be good to check that `database` and `connection$database` point to the same struct before doing this (or maybe the `database` argument is superfluous since we already know what it is, or, conversely, maybe storing the `database` backreference in a connection is not useful).



##########
r/adbcdrivermanager/R/utils.R:
##########
@@ -94,3 +94,102 @@ str.adbc_xptr <- function(object, ...) {
   str(env_proxy, ...)
   invisible(object)
 }
+
+
+#' Low-level pointer details
+#'
+#' - `adbc_xptr_move()` allocates a fresh R object and moves all values pointed
+#'   to by `x` into it. The original R object is invalidated by zeroing its
+#'   content. This is useful when returning from a function where
+#'   [lifecycle helpers][with_adbc] were used to manage the original
+#'   object.
+#' - `adbc_xptr_is_valid()` provides a means by which to test for an invalidated
+#'   pointer.
+#'
+#' @param x An 'adbc_database', 'adbc_connection', 'adbc_statement', or
+#'   'nanoarrow_array_stream'
+#'
+#' @return
+#' - `adbc_xptr_move()`: A freshly-allocated R object identical to `x`
+#' - `adbc_xptr_is_valid()`: Returns FALSE if the ADBC object pointed to by `x`
+#'   has been invalidated.
+#' @export
+#'
+#' @examples
+#' db <- adbc_database_init(adbc_driver_void())
+#' adbc_xptr_is_valid(db)
+#' db_new <- adbc_xptr_move(db)
+#' adbc_xptr_is_valid(db)
+#' adbc_xptr_is_valid(db_new)
+#'
+adbc_xptr_move <- function(x) {
+  if (inherits(x, "adbc_database")) {
+    .Call(RAdbcMoveDatabase, x)
+  } else if (inherits(x, "adbc_connection")) {
+    .Call(RAdbcMoveConnection, x)
+  } else if (inherits(x, "adbc_statement")) {
+    .Call(RAdbcMoveStatement, x)
+  } else if (inherits(x, "nanoarrow_array_stream")) {

Review Comment:
   It seemed easier this way but I'm not particularly fussed as long as it errors for something that cannot be moved in that way.



##########
r/adbcdrivermanager/R/utils.R:
##########
@@ -94,3 +94,102 @@ str.adbc_xptr <- function(object, ...) {
   str(env_proxy, ...)
   invisible(object)
 }
+
+
+#' Low-level pointer details
+#'
+#' - `adbc_xptr_move()` allocates a fresh R object and moves all values pointed
+#'   to by `x` into it. The original R object is invalidated by zeroing its
+#'   content. This is useful when returning from a function where
+#'   [lifecycle helpers][with_adbc] were used to manage the original
+#'   object.
+#' - `adbc_xptr_is_valid()` provides a means by which to test for an invalidated
+#'   pointer.
+#'
+#' @param x An 'adbc_database', 'adbc_connection', 'adbc_statement', or
+#'   'nanoarrow_array_stream'
+#'
+#' @return
+#' - `adbc_xptr_move()`: A freshly-allocated R object identical to `x`
+#' - `adbc_xptr_is_valid()`: Returns FALSE if the ADBC object pointed to by `x`
+#'   has been invalidated.
+#' @export
+#'
+#' @examples
+#' db <- adbc_database_init(adbc_driver_void())
+#' adbc_xptr_is_valid(db)
+#' db_new <- adbc_xptr_move(db)
+#' adbc_xptr_is_valid(db)
+#' adbc_xptr_is_valid(db_new)
+#'
+adbc_xptr_move <- function(x) {
+  if (inherits(x, "adbc_database")) {
+    .Call(RAdbcMoveDatabase, x)
+  } else if (inherits(x, "adbc_connection")) {
+    .Call(RAdbcMoveConnection, x)
+  } else if (inherits(x, "adbc_statement")) {
+    .Call(RAdbcMoveStatement, x)
+  } else if (inherits(x, "nanoarrow_array_stream")) {
+    stream <- nanoarrow::nanoarrow_allocate_array_stream()
+    nanoarrow::nanoarrow_pointer_move(x, stream)
+    stream
+  } else {
+    assert_adbc(x)
+  }
+}
+
+#' @rdname adbc_xptr_move
+#' @export
+adbc_xptr_is_valid <- function(x) {
+  if (inherits(x, "adbc_database")) {
+    .Call(RAdbcDatabaseValid, x)
+  } else if (inherits(x, "adbc_connection")) {
+    .Call(RAdbcConnectionValid, x)
+  } else if (inherits(x, "adbc_statement")) {
+    .Call(RAdbcStatementValid, x)
+  } else if (inherits(x, "nanoarrow_array_stream")) {
+    nanoarrow::nanoarrow_pointer_is_valid(x)
+  } else {
+    assert_adbc(x)
+  }
+}
+
+# Usually we want errors for an attempt at double release; however,
+# the helpers we want to be compatible with adbc_xptr_move() which sets the
+# managed pointer to NULL.
+adbc_release_non_null <- function(x) {

Review Comment:
   I think that would involve an unreferenceable object whose release is contingent on the garbage collector? Release can fail, so explicitly doing so is sometimes helpful.



-- 
This is an automated message from the Apache Git Service.
To respond to the message, please log on to GitHub and use the
URL above to go to the specific comment.

To unsubscribe, e-mail: github-unsubscribe@arrow.apache.org

For queries about this service, please contact Infrastructure at:
users@infra.apache.org