You are viewing a plain text version of this content. The canonical link for it is here.
Posted to github@arrow.apache.org by GitBox <gi...@apache.org> on 2022/04/18 15:54:50 UTC

[GitHub] [arrow] paleolimbot commented on a diff in pull request #12817: ARROW-15168: [R] Add S3 generics to create main Arrow objects

paleolimbot commented on code in PR #12817:
URL: https://github.com/apache/arrow/pull/12817#discussion_r852216643


##########
r/R/array.R:
##########
@@ -217,6 +217,93 @@ Array$create <- function(x, type = NULL) {
 Array$import_from_c <- ImportArray
 
 
+#' Convert an object to an Arrow Array
+#'
+#' Whereas `Array$create()` constructs an [Array] from the built-in data types
+#' for which the Arrow package implements fast converters, `as_arrow_array()`
+#' provides a means by which other packages can define conversions to Arrow
+#' objects.
+#'
+#' @param x An object to convert to an Arrow Array
+#' @param ... Passed to S3 methods
+#' @param type A [type][data-type] for the final Array. A value of `NULL`
+#'   will default to the type guessed by [type()].
+#'
+#' @return An [Array].
+#' @export
+#'
+#' @examplesIf arrow_available()
+#' as_arrow_array(1:5)
+#'
+as_arrow_array <- function(x, ..., type = NULL) {
+  UseMethod("as_arrow_array")
+}
+
+#' @rdname as_arrow_array
+#' @export
+as_arrow_array.Array <- function(x, ..., type = NULL) {
+  if (is.null(type)) {
+    x
+  } else {
+    x$cast(type)
+  }
+}
+
+#' @rdname as_arrow_array
+#' @export
+as_arrow_array.ChunkedArray <- function(x, ..., type = NULL) {
+  concat_arrays(!!! x$chunks, type = type)
+}
+
+#' @rdname as_arrow_array
+#' @export
+as_arrow_array.vctrs_vctr <- function(x, ..., type = NULL) {
+  if (is.null(type)) {
+    vctrs_extension_array(x)
+  } else if (inherits(type, "VctrsExtensionType")) {
+    vctrs_extension_array(
+      x,
+      ptype = type$ptype(),
+      storage_type = type$storage_type()
+    )
+  } else {
+    NextMethod()
+  }
+}
+
+#' @export
+as_arrow_array.POSIXlt <- function(x, ..., type = NULL) {
+  as_arrow_array.vctrs_vctr(x, ..., type = type)

Review Comment:
   I hadn't considered that! It doesn't look like that example causes problems and I haven't historically had problems with `NextMethod()`. Is there a related case I should be checking?
   
   ``` r
   # remotes::install_github("apache/arrow/r#12817")
   library(arrow, warn.conflicts = FALSE)
   
   x <- as.POSIXlt(Sys.Date())
   class(x) <- c("vctrs_vctr", "POSIXlt")
   array <- as_arrow_array(x)
   x2 <- as.vector(array)
   class(x2)
   #> [1] "vctrs_vctr" "POSIXlt"
   ```



-- 
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