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/11 10:23:41 UTC

[GitHub] [arrow] AlenkaF opened a new pull request, #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

AlenkaF opened a new pull request, #12855:
URL: https://github.com/apache/arrow/pull/12855

   This PR adds bindings for lubridate's `dseconds`, `dmilliseconds`, `dmicroseconds` and `dnanoseconds`.
   
   As `picoseconds` are not supported by [duration in Arrow](https://arrow.apache.org/docs/cpp/api/datatype.html#_CPPv4N5arrow4Type4type8DURATIONE) and duration is of integer type, the call to `picoseconds()` raises a warning.


-- 
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] dragosmg commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
dragosmg commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r849420961


##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -323,6 +323,37 @@ register_bindings_duration <- function() {
 
     build_expr("cast", x, options = cast_options(to_type = duration(unit = "s")))
   })
+  register_binding("dseconds", function(x = 1) {
+    if (!inherits(x, "Expression")) {
+      x <- Expression$scalar(x)
+    }
+    dseconds_int64 <- Expression$create("cast", x, options = cast_options(to_type = int64()))
+    build_expr("cast", dseconds_int64, options = list(to_type = duration(unit = "s")))
+  })
+  register_binding("dmilliseconds", function(x = 1) {
+    if (!inherits(x, "Expression")) {
+      x <- Expression$scalar(x)
+    }
+    dmilliseconds_int64 <- Expression$create("cast", x, options = cast_options(to_type = int64()))
+    build_expr("cast", dmilliseconds_int64, options = list(to_type = duration(unit = "ms")))

Review Comment:
   ```suggestion
       if (!inherits(x, "Expression")) {
         x <- Expression$scalar(x)
       }
       dmilliseconds_int64 <- Expression$create("cast", x, options = cast_options(to_type = int64()))
       build_expr("cast", dmilliseconds_int64, options = list(to_type = duration(unit = "ms")))
   ```
   ```suggestion
       x <- build_expr("cast", x, options = cast_options(to_type = int64()))
       x$cast(duration("ms")
   ```



##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -323,6 +323,37 @@ register_bindings_duration <- function() {
 
     build_expr("cast", x, options = cast_options(to_type = duration(unit = "s")))
   })
+  register_binding("dseconds", function(x = 1) {
+    if (!inherits(x, "Expression")) {
+      x <- Expression$scalar(x)
+    }
+    dseconds_int64 <- Expression$create("cast", x, options = cast_options(to_type = int64()))
+    build_expr("cast", dseconds_int64, options = list(to_type = duration(unit = "s")))
+  })
+  register_binding("dmilliseconds", function(x = 1) {
+    if (!inherits(x, "Expression")) {
+      x <- Expression$scalar(x)
+    }
+    dmilliseconds_int64 <- Expression$create("cast", x, options = cast_options(to_type = int64()))
+    build_expr("cast", dmilliseconds_int64, options = list(to_type = duration(unit = "ms")))

Review Comment:
   ```suggestion
       if (!inherits(x, "Expression")) {
         x <- Expression$scalar(x)
       }
       dmilliseconds_int64 <- Expression$create("cast", x, options = cast_options(to_type = int64()))
       build_expr("cast", dmilliseconds_int64, options = list(to_type = duration(unit = "ms")))
   ```
   ```suggestion
       x <- build_expr("cast", x, options = cast_options(to_type = int64()))
       x$cast(duration("ms")
   ```



-- 
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] AlenkaF commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r849515621


##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -323,6 +323,37 @@ register_bindings_duration <- function() {
 
     build_expr("cast", x, options = cast_options(to_type = duration(unit = "s")))
   })
+  register_binding("dseconds", function(x = 1) {
+    if (!inherits(x, "Expression")) {
+      x <- Expression$scalar(x)
+    }
+    dseconds_int64 <- Expression$create("cast", x, options = cast_options(to_type = int64()))

Review Comment:
   That is very good to know! Thanks



-- 
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] github-actions[bot] commented on pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
github-actions[bot] commented on PR #12855:
URL: https://github.com/apache/arrow/pull/12855#issuecomment-1094877037

   https://issues.apache.org/jira/browse/ARROW-14942


-- 
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] thisisnic commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
thisisnic commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r854012780


##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -376,6 +376,21 @@ register_bindings_duration_helpers <- function() {
   register_binding("dyears", function(x = 1) {
     make_duration(x * 31557600, "s")
   })
+  register_binding("dseconds", function(x = 1) {
+    make_duration(x, "s")
+  })
+  register_binding("dmilliseconds", function(x = 1) {
+    make_duration(x, "ms")
+  })
+  register_binding("dmicroseconds", function(x = 1) {
+    make_duration(x, "us")
+  })
+  register_binding("dnanoseconds", function(x = 1) {
+    make_duration(x, "ns")
+  })
+  register_binding("dpicoseconds", function(x = 1) {
+    abort("Duration in picoseconds not supported in Arrow.")
+  })

Review Comment:
   When you say "where to look for what's wrong", how do you know something is wrong?



-- 
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] AlenkaF commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r854052860


##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -376,6 +376,21 @@ register_bindings_duration_helpers <- function() {
   register_binding("dyears", function(x = 1) {
     make_duration(x * 31557600, "s")
   })
+  register_binding("dseconds", function(x = 1) {
+    make_duration(x, "s")
+  })
+  register_binding("dmilliseconds", function(x = 1) {
+    make_duration(x, "ms")
+  })
+  register_binding("dmicroseconds", function(x = 1) {
+    make_duration(x, "us")
+  })
+  register_binding("dnanoseconds", function(x = 1) {
+    make_duration(x, "ns")
+  })
+  register_binding("dpicoseconds", function(x = 1) {
+    abort("Duration in picoseconds not supported in Arrow.")
+  })

Review Comment:
   Yeah, it would be good to post an output 🤦‍♀️ 
   
   ```R
   > devtools::test(filter="datetime")
   ℹ Loading arrow
   Some features are not enabled in this build of Arrow. Run `arrow_info()` for more information.
   ℹ Testing arrow
   Some features are not enabled in this build of Arrow. Run `arrow_info()` for more information.
   ✔ | F W S  OK | Context
   ✖ | 7     381 | dplyr-funcs-datetime [2.0s]                                                                                                                  
   ─────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────
   Failure (test-dplyr-funcs-datetime.R:1263:3): dminutes, dhours, ddays, dweeks, dmonths, dyears
   `via_batch <- rlang::eval_tidy(expr, rlang::new_data_mask(rlang::env(.input = record_batch(tbl))))` threw an unexpected warning.
   Message: Expression dyears(x) not supported in Arrow; pulling data into R
   Class:   simpleWarning/warning/condition
   Backtrace:
     1. arrow:::compare_dplyr_binding(...)
          at test-dplyr-funcs-datetime.R:1263:2
    12. arrow::mutate.ArrowTabular(...)
    13. arrow::abandon_ship(call, .data, msg)
          at r/R/dplyr-mutate.R:62:6
   
   Failure (test-dplyr-funcs-datetime.R:1263:3): dminutes, dhours, ddays, dweeks, dmonths, dyears
   `via_table <- rlang::eval_tidy(expr, rlang::new_data_mask(rlang::env(.input = arrow_table(tbl))))` threw an unexpected warning.
   Message: Expression dyears(x) not supported in Arrow; pulling data into R
   Class:   simpleWarning/warning/condition
   Backtrace:
     1. arrow:::compare_dplyr_binding(...)
          at test-dplyr-funcs-datetime.R:1263:2
    12. arrow::mutate.ArrowTabular(...)
    13. arrow::abandon_ship(call, .data, msg)
          at r/R/dplyr-mutate.R:62:6
   
   Failure (test-dplyr-funcs-datetime.R:1278:3): dminutes, dhours, ddays, dweeks, dmonths, dyears
   `via_batch <- rlang::eval_tidy(expr, rlang::new_data_mask(rlang::env(.input = record_batch(tbl))))` threw an unexpected warning.
   Message: Expression date_to_add + ddays - dhours(3) not supported in Arrow; pulling data into R
   Class:   simpleWarning/warning/condition
   Backtrace:
     1. arrow:::compare_dplyr_binding(...)
          at test-dplyr-funcs-datetime.R:1278:2
    12. arrow::mutate.ArrowTabular(...)
    13. arrow::abandon_ship(call, .data, msg)
          at r/R/dplyr-mutate.R:62:6
   
   Failure (test-dplyr-funcs-datetime.R:1278:3): dminutes, dhours, ddays, dweeks, dmonths, dyears
   `via_table <- rlang::eval_tidy(expr, rlang::new_data_mask(rlang::env(.input = arrow_table(tbl))))` threw an unexpected warning.
   Message: Expression date_to_add + ddays - dhours(3) not supported in Arrow; pulling data into R
   Class:   simpleWarning/warning/condition
   Backtrace:
     1. arrow:::compare_dplyr_binding(...)
          at test-dplyr-funcs-datetime.R:1278:2
    12. arrow::mutate.ArrowTabular(...)
    13. arrow::abandon_ship(call, .data, msg)
          at r/R/dplyr-mutate.R:62:6
   
   Failure (test-dplyr-funcs-datetime.R:1292:3): dminutes, dhours, ddays, dweeks, dmonths, dyears
   `via_batch <- rlang::eval_tidy(expr, rlang::new_data_mask(rlang::env(.input = record_batch(tbl))))` threw an unexpected warning.
   Message: Expression dminutes(1) not supported in Arrow; pulling data into R
   Class:   simpleWarning/warning/condition
   Backtrace:
     1. arrow:::compare_dplyr_binding(...)
          at test-dplyr-funcs-datetime.R:1292:2
    12. arrow::mutate.ArrowTabular(...)
    13. arrow::abandon_ship(call, .data, msg)
          at r/R/dplyr-mutate.R:62:6
   
   Failure (test-dplyr-funcs-datetime.R:1292:3): dminutes, dhours, ddays, dweeks, dmonths, dyears
   `via_table <- rlang::eval_tidy(expr, rlang::new_data_mask(rlang::env(.input = arrow_table(tbl))))` threw an unexpected warning.
   Message: Expression dminutes(1) not supported in Arrow; pulling data into R
   Class:   simpleWarning/warning/condition
   Backtrace:
     1. arrow:::compare_dplyr_binding(...)
          at test-dplyr-funcs-datetime.R:1292:2
    12. arrow::mutate.ArrowTabular(...)
    13. arrow::abandon_ship(call, .data, msg)
          at r/R/dplyr-mutate.R:62:6
   
   Error (test-dplyr-funcs-datetime.R:1312:3): dseconds, dmilliseconds, dmicroseconds, dnanoseconds, dpicoseconds
   Error in `collect(.)`: NotImplemented: Function 'multiply_checked' has no kernel matching input types (array[int32], scalar[string])
   /Users/alenkafrim/repos/arrow/cpp/src/arrow/compute/exec/expression.cc:340  call.function->DispatchBest(&descrs)
   /Users/alenkafrim/repos/arrow/cpp/src/arrow/compute/exec/expression.cc:411  BindImpl(std::move(argument), in, shape, exec_context)
   /Users/alenkafrim/repos/arrow/cpp/src/arrow/compute/exec/expression.cc:411  BindImpl(std::move(argument), in, shape, exec_context)
   /Users/alenkafrim/repos/arrow/cpp/src/arrow/compute/exec/project_node.cc:67  expr.Bind(*inputs[0]->output_schema())
   Backtrace:
     1. arrow:::compare_dplyr_binding(...)
          at test-dplyr-funcs-datetime.R:1312:2
    11. arrow::collect.arrow_dplyr_query(.)
   ─────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────
   
   ══ Results ══════════════════════════════════════════════════════════════════════════════════════════════════════════════════════════════════════════════════
   Duration: 2.2 s
   
   [ FAIL 7 | WARN 0 | SKIP 0 | PASS 381 ]
   ```



-- 
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] AlenkaF commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r854082872


##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -376,6 +376,21 @@ register_bindings_duration_helpers <- function() {
   register_binding("dyears", function(x = 1) {
     make_duration(x * 31557600, "s")
   })
+  register_binding("dseconds", function(x = 1) {
+    make_duration(x, "s")
+  })
+  register_binding("dmilliseconds", function(x = 1) {
+    make_duration(x, "ms")
+  })
+  register_binding("dmicroseconds", function(x = 1) {
+    make_duration(x, "us")
+  })
+  register_binding("dnanoseconds", function(x = 1) {
+    make_duration(x, "ns")
+  })
+  register_binding("dpicoseconds", function(x = 1) {
+    abort("Duration in picoseconds not supported in Arrow.")
+  })

Review Comment:
   Thanks @thisisnic for all the help! Will do a better job at asking questions next time (reprex and such).
   
   The code needs a bit of tweaking and will be ready to commit.



-- 
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] jonkeane commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
jonkeane commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r855484022


##########
r/tests/testthat/test-dplyr-funcs-datetime.R:
##########
@@ -1303,6 +1303,74 @@ test_that("dminutes, dhours, ddays, dweeks, dmonths, dyears", {
     tibble(),
     ignore_attr = TRUE
   )
+
+  # double -> duration not supported in Arrow.
+  # Error is generated in the C++ code
+  expect_error(
+    test_df %>%
+      arrow_table() %>%
+      mutate(r_obj_dminutes = dminutes(1.12345)) %>%
+      collect()
+  )

Review Comment:
   Thanks for this comment about why we are `expect_error()` but not actually asserting it (since this is all C++). 💯 



##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -353,6 +353,44 @@ register_bindings_duration <- function() {
   })
 }
 
+.helpers_function_map <- list(
+  "dminutes" = list(60, "s"),
+  "dhours" = list(3600, "s"),
+  "ddays" = list(86400, "s"),
+  "dweeks" = list(604800, "s"),
+  "dmonths" = list(2629800, "s"),
+  "dyears" = list(31557600, "s"),
+  "dseconds" = list(1, "s"),
+  "dmilliseconds" = list(1, "ms"),
+  "dmicroseconds" = list(1, "us"),
+  "dnanoseconds" = list(1, "ns")
+)
+make_duration <- function(x, unit) {
+  x <- build_expr("cast", x, options = cast_options(to_type = int64()))
+  x$cast(duration(unit))
+}
+register_bindings_duration_helpers <- function() {
+  duration_helpers_map_factory <- function(value, unit) {
+    force(value)
+    force(unit)
+    function(x = 1) make_duration(x * value, unit)
+  }
+
+  for (name in names(.helpers_function_map)) {
+    register_binding(
+      name,
+      duration_helpers_map_factory(
+        .helpers_function_map[[name]][[1]],
+        .helpers_function_map[[name]][[2]]
+      )
+    )
+  }

Review Comment:
   Nice! This is actually even shorter than I though it would be!



##########
r/tests/testthat/test-dplyr-funcs-datetime.R:
##########
@@ -1303,6 +1303,74 @@ test_that("dminutes, dhours, ddays, dweeks, dmonths, dyears", {
     tibble(),
     ignore_attr = TRUE
   )
+
+  # double -> duration not supported in Arrow.
+  # Error is generated in the C++ code
+  expect_error(
+    test_df %>%
+      arrow_table() %>%
+      mutate(r_obj_dminutes = dminutes(1.12345)) %>%
+      collect()
+  )
+})
+
+test_that("dseconds, dmilliseconds, dmicroseconds, dnanoseconds, dpicoseconds", {
+  example_d <- tibble(x = c(1:10, NA))
+  date_to_add <- ymd("2009-08-03", tz = "Pacific/Marquesas")
+
+  compare_dplyr_binding(
+    .input %>%
+      mutate(
+        dseconds = dseconds(x),
+        dmilliseconds = dmilliseconds(x),
+        dmicroseconds = dmicroseconds(x),
+        dnanoseconds = dnanoseconds(x),
+      ) %>%
+      collect(),
+    example_d,
+    ignore_attr = TRUE
+  )
+
+  compare_dplyr_binding(
+    .input %>%
+      mutate(
+        dseconds = dseconds(x),
+        dmicroseconds = dmicroseconds(x),
+        new_date_1 = date_to_add + dseconds,
+        new_date_2 = date_to_add + dseconds - dmicroseconds,
+        new_duration = dseconds - dmicroseconds
+      ) %>%
+      collect(),
+    example_d,
+    ignore_attr = TRUE

Review Comment:
   I didn't see this in the PR (though might have missed something), what `attr` are we ignoring? Maybe we should add a comment about what we're using that for



-- 
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] dragosmg commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
dragosmg commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r849422530


##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -323,6 +323,37 @@ register_bindings_duration <- function() {
 
     build_expr("cast", x, options = cast_options(to_type = duration(unit = "s")))
   })
+  register_binding("dseconds", function(x = 1) {
+    if (!inherits(x, "Expression")) {
+      x <- Expression$scalar(x)
+    }
+    dseconds_int64 <- Expression$create("cast", x, options = cast_options(to_type = int64()))
+    build_expr("cast", dseconds_int64, options = list(to_type = duration(unit = "s")))
+  })
+  register_binding("dmilliseconds", function(x = 1) {
+    if (!inherits(x, "Expression")) {
+      x <- Expression$scalar(x)
+    }
+    dmilliseconds_int64 <- Expression$create("cast", x, options = cast_options(to_type = int64()))
+    build_expr("cast", dmilliseconds_int64, options = list(to_type = duration(unit = "ms")))

Review Comment:
   ```suggestion
       x <- build_expr("cast", x, options = cast_options(to_type = int64()))
       x$cast(duration("ms))
   ```



##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -323,6 +323,37 @@ register_bindings_duration <- function() {
 
     build_expr("cast", x, options = cast_options(to_type = duration(unit = "s")))
   })
+  register_binding("dseconds", function(x = 1) {
+    if (!inherits(x, "Expression")) {
+      x <- Expression$scalar(x)
+    }
+    dseconds_int64 <- Expression$create("cast", x, options = cast_options(to_type = int64()))
+    build_expr("cast", dseconds_int64, options = list(to_type = duration(unit = "s")))
+  })
+  register_binding("dmilliseconds", function(x = 1) {
+    if (!inherits(x, "Expression")) {
+      x <- Expression$scalar(x)
+    }
+    dmilliseconds_int64 <- Expression$create("cast", x, options = cast_options(to_type = int64()))
+    build_expr("cast", dmilliseconds_int64, options = list(to_type = duration(unit = "ms")))

Review Comment:
   ```suggestion
       x <- build_expr("cast", x, options = cast_options(to_type = int64()))
       x$cast(duration("ms))
   ```



-- 
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] dragosmg commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
dragosmg commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r849420964


##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -323,6 +323,37 @@ register_bindings_duration <- function() {
 
     build_expr("cast", x, options = cast_options(to_type = duration(unit = "s")))
   })
+  register_binding("dseconds", function(x = 1) {
+    if (!inherits(x, "Expression")) {
+      x <- Expression$scalar(x)
+    }
+    dseconds_int64 <- Expression$create("cast", x, options = cast_options(to_type = int64()))
+    build_expr("cast", dseconds_int64, options = list(to_type = duration(unit = "s")))
+  })
+  register_binding("dmilliseconds", function(x = 1) {
+    if (!inherits(x, "Expression")) {
+      x <- Expression$scalar(x)
+    }
+    dmilliseconds_int64 <- Expression$create("cast", x, options = cast_options(to_type = int64()))
+    build_expr("cast", dmilliseconds_int64, options = list(to_type = duration(unit = "ms")))

Review Comment:
   ```suggestion
       if (!inherits(x, "Expression")) {
         x <- Expression$scalar(x)
       }
       dmilliseconds_int64 <- Expression$create("cast", x, options = cast_options(to_type = int64()))
       build_expr("cast", dmilliseconds_int64, options = list(to_type = duration(unit = "ms")))
   ```
   ```suggestion
       x <- build_expr("cast", x, options = cast_options(to_type = int64()))
       x$cast(duration("ms")
   ```



-- 
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] AlenkaF commented on pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on PR #12855:
URL: https://github.com/apache/arrow/pull/12855#issuecomment-1105378896

   @jonkeane I tried to address all the comments and I think the PR is ready for another review.


-- 
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] AlenkaF commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r850247992


##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -354,21 +354,21 @@ register_bindings_duration <- function() {
 }
 
 register_bindings_duration_helpers <- function() {
-  register_binding("dseconds", function(x = 1) {
+  make_duration <- function(x, unit) {

Review Comment:
   Done!



-- 
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] ursabot commented on pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
ursabot commented on PR #12855:
URL: https://github.com/apache/arrow/pull/12855#issuecomment-1110309383

   ['Python', 'R'] benchmarks have high level of regressions.
   [ursa-i9-9960x](https://conbench.ursa.dev/compare/runs/37596a0f832f4e1987ef4beefc929e30...109a24b473db4316865063af54b0319e/)
   


-- 
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] jonkeane closed pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
jonkeane closed pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds
URL: https://github.com/apache/arrow/pull/12855


-- 
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] AlenkaF commented on pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on PR #12855:
URL: https://github.com/apache/arrow/pull/12855#issuecomment-1106045587

   Errors do not seem to be related to this 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] AlenkaF commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r854049688


##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -376,6 +376,21 @@ register_bindings_duration_helpers <- function() {
   register_binding("dyears", function(x = 1) {
     make_duration(x * 31557600, "s")
   })
+  register_binding("dseconds", function(x = 1) {
+    make_duration(x, "s")
+  })
+  register_binding("dmilliseconds", function(x = 1) {
+    make_duration(x, "ms")
+  })
+  register_binding("dmicroseconds", function(x = 1) {
+    make_duration(x, "us")
+  })
+  register_binding("dnanoseconds", function(x = 1) {
+    make_duration(x, "ns")
+  })
+  register_binding("dpicoseconds", function(x = 1) {
+    abort("Duration in picoseconds not supported in Arrow.")
+  })

Review Comment:
   The tests are failing and they have passed before :(



-- 
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] dragosmg commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
dragosmg commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r850231996


##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -354,21 +354,21 @@ register_bindings_duration <- function() {
 }
 
 register_bindings_duration_helpers <- function() {
-  register_binding("dseconds", function(x = 1) {
+  make_duration <- function(x, unit) {

Review Comment:
   Thanks for this and sorry to be a pain. I think `make_duration()` can be a standalone function, it doesn't need to be a binding since there is no `lubridate` equivalent to it.



-- 
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] AlenkaF commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r850239512


##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -354,21 +354,21 @@ register_bindings_duration <- function() {
 }
 
 register_bindings_duration_helpers <- function() {
-  register_binding("dseconds", function(x = 1) {
+  make_duration <- function(x, unit) {

Review Comment:
   Oh, my mistake of positioning. Thanks for catching it!



-- 
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] dragosmg commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
dragosmg commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r849416453


##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -323,6 +323,37 @@ register_bindings_duration <- function() {
 
     build_expr("cast", x, options = cast_options(to_type = duration(unit = "s")))
   })
+  register_binding("dseconds", function(x = 1) {
+    if (!inherits(x, "Expression")) {
+      x <- Expression$scalar(x)
+    }
+    dseconds_int64 <- Expression$create("cast", x, options = cast_options(to_type = int64()))

Review Comment:
   You could replace `Expression$create()` with `build_expr()` which then allows you to get rid of the `if (!inherits(x, "Expression"))` logic.
   `build_expr()` is in fact `Expression$create()` plus an automatic conversion of R objects to Scalar. 



##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -323,6 +323,37 @@ register_bindings_duration <- function() {
 
     build_expr("cast", x, options = cast_options(to_type = duration(unit = "s")))
   })
+  register_binding("dseconds", function(x = 1) {
+    if (!inherits(x, "Expression")) {
+      x <- Expression$scalar(x)
+    }
+    dseconds_int64 <- Expression$create("cast", x, options = cast_options(to_type = int64()))

Review Comment:
   You could replace `Expression$create()` with `build_expr()` which then allows you to get rid of the `if (!inherits(x, "Expression"))` logic.
   `build_expr()` is in fact `Expression$create()` plus an automatic conversion of R objects to Scalar. 



-- 
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] AlenkaF commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r851358792


##########
r/tests/testthat/test-dplyr-funcs-datetime.R:
##########
@@ -1304,3 +1304,53 @@ test_that("dminutes, dhours, ddays, dweeks, dmonths, dyears", {
     ignore_attr = TRUE
   )
 })
+
+test_that("dseconds, dmilliseconds, dmicroseconds, dnanoseconds, dpicoseconds", {
+  example_d <- tibble(x = c(1:10, NA))

Review Comment:
   Of course, thanks for this! Will test and see =)



-- 
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] ursabot commented on pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
ursabot commented on PR #12855:
URL: https://github.com/apache/arrow/pull/12855#issuecomment-1108857145

   Benchmark runs are scheduled for baseline = 0ce8ce8b192c75e63a7f796711326b6001449aa2 and contender = c4b646e715d155c1f77d34804796864465caa97b. c4b646e715d155c1f77d34804796864465caa97b is a master commit associated with this PR. Results will be available as each benchmark for each run completes.
   Conbench compare runs links:
   [Finished :arrow_down:0.0% :arrow_up:0.0%] [ec2-t3-xlarge-us-east-2](https://conbench.ursa.dev/compare/runs/dede1913c60e4422807ae05f13833933...e0518ef37dff459a8a32fbec80c5a30b/)
   [Failed] [test-mac-arm](https://conbench.ursa.dev/compare/runs/93b69223cc1f4e238ce145ad0815ac80...e3ff024d35994bac9558f28bbccaa3d1/)
   [Failed :arrow_down:1.13% :arrow_up:0.0%] [ursa-i9-9960x](https://conbench.ursa.dev/compare/runs/37596a0f832f4e1987ef4beefc929e30...109a24b473db4316865063af54b0319e/)
   [Finished :arrow_down:0.25% :arrow_up:0.08%] [ursa-thinkcentre-m75q](https://conbench.ursa.dev/compare/runs/90ca37587d9d4a9a9545c740b7cf1996...d936f306033546299ec35e647ca74b22/)
   Buildkite builds:
   [Finished] <https://buildkite.com/apache-arrow/arrow-bci-benchmark-on-ec2-t3-xlarge-us-east-2/builds/586| `c4b646e7` ec2-t3-xlarge-us-east-2>
   [Failed] <https://buildkite.com/apache-arrow/arrow-bci-benchmark-on-test-mac-arm/builds/574| `c4b646e7` test-mac-arm>
   [Failed] <https://buildkite.com/apache-arrow/arrow-bci-benchmark-on-ursa-i9-9960x/builds/572| `c4b646e7` ursa-i9-9960x>
   [Finished] <https://buildkite.com/apache-arrow/arrow-bci-benchmark-on-ursa-thinkcentre-m75q/builds/584| `c4b646e7` ursa-thinkcentre-m75q>
   [Finished] <https://buildkite.com/apache-arrow/arrow-bci-benchmark-on-ec2-t3-xlarge-us-east-2/builds/585| `0ce8ce8b` ec2-t3-xlarge-us-east-2>
   [Failed] <https://buildkite.com/apache-arrow/arrow-bci-benchmark-on-test-mac-arm/builds/573| `0ce8ce8b` test-mac-arm>
   [Failed] <https://buildkite.com/apache-arrow/arrow-bci-benchmark-on-ursa-i9-9960x/builds/571| `0ce8ce8b` ursa-i9-9960x>
   [Finished] <https://buildkite.com/apache-arrow/arrow-bci-benchmark-on-ursa-thinkcentre-m75q/builds/583| `0ce8ce8b` ursa-thinkcentre-m75q>
   Supported benchmarks:
   ec2-t3-xlarge-us-east-2: Supported benchmark langs: Python, R. Runs only benchmarks with cloud = True
   test-mac-arm: Supported benchmark langs: C++, Python, R
   ursa-i9-9960x: Supported benchmark langs: Python, R, JavaScript
   ursa-thinkcentre-m75q: Supported benchmark langs: C++, Java
   


-- 
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] AlenkaF commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r855756291


##########
r/tests/testthat/test-dplyr-funcs-datetime.R:
##########
@@ -1303,6 +1303,74 @@ test_that("dminutes, dhours, ddays, dweeks, dmonths, dyears", {
     tibble(),
     ignore_attr = TRUE
   )
+
+  # double -> duration not supported in Arrow.
+  # Error is generated in the C++ code
+  expect_error(
+    test_df %>%
+      arrow_table() %>%
+      mutate(r_obj_dminutes = dminutes(1.12345)) %>%
+      collect()
+  )
+})
+
+test_that("dseconds, dmilliseconds, dmicroseconds, dnanoseconds, dpicoseconds", {
+  example_d <- tibble(x = c(1:10, NA))
+  date_to_add <- ymd("2009-08-03", tz = "Pacific/Marquesas")
+
+  compare_dplyr_binding(
+    .input %>%
+      mutate(
+        dseconds = dseconds(x),
+        dmilliseconds = dmilliseconds(x),
+        dmicroseconds = dmicroseconds(x),
+        dnanoseconds = dnanoseconds(x),
+      ) %>%
+      collect(),
+    example_d,
+    ignore_attr = TRUE
+  )
+
+  compare_dplyr_binding(
+    .input %>%
+      mutate(
+        dseconds = dseconds(x),
+        dmicroseconds = dmicroseconds(x),
+        new_date_1 = date_to_add + dseconds,
+        new_date_2 = date_to_add + dseconds - dmicroseconds,
+        new_duration = dseconds - dmicroseconds
+      ) %>%
+      collect(),
+    example_d,
+    ignore_attr = TRUE

Review Comment:
   We are using `ignore_attr = TRUE` due to the diff in attributes `package`, `units` and `class: (difftime vs Duration)`. I added a comment about it in the beginning of both tests.



-- 
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] AlenkaF commented on pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on PR #12855:
URL: https://github.com/apache/arrow/pull/12855#issuecomment-1098855587

   Sure, makes sense 👍  Will do.


-- 
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] amol- commented on pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
amol- commented on PR #12855:
URL: https://github.com/apache/arrow/pull/12855#issuecomment-1097868927

   @dragosmg ming reviewing this one?


-- 
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] AlenkaF commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r853998157


##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -376,6 +376,21 @@ register_bindings_duration_helpers <- function() {
   register_binding("dyears", function(x = 1) {
     make_duration(x * 31557600, "s")
   })
+  register_binding("dseconds", function(x = 1) {
+    make_duration(x, "s")
+  })
+  register_binding("dmilliseconds", function(x = 1) {
+    make_duration(x, "ms")
+  })
+  register_binding("dmicroseconds", function(x = 1) {
+    make_duration(x, "us")
+  })
+  register_binding("dnanoseconds", function(x = 1) {
+    make_duration(x, "ns")
+  })
+  register_binding("dpicoseconds", function(x = 1) {
+    abort("Duration in picoseconds not supported in Arrow.")
+  })

Review Comment:
   I am a bit stuck, any pointers where to look for what's wrong in this try of the mapping?
   
   ```R
   .helpers_function_map <- list(
     "dminutes" = c(60, "s"),
     "dhours" = c(3600, "s"),
     "ddays" = c(86400, "s"),
     "dweeks" = c(604800, "s"),
     "dmonths" = c(2629800, "s"),
     "ydyears" = c(31557600, "s"),
     "dseconds" = c(1, "s"),
     "dmilliseconds" = c(1, "ms"),
     "dmicroseconds" = c(1, "us"),
     "dnanoseconds" = c(1, "ns")
   )
   make_duration <- function(x, unit) {
     x <- build_expr("cast", x, options = cast_options(to_type = int64()))
     x$cast(duration(unit))
   }
   register_bindings_duration_helpers <- function() {
     duration_helpers_map_factory <- function(value, unit) {
       force(value)
       force(unit)
       function(x = 1) make_duration(x * value, unit)
     }
   
     for (name in names(.helpers_function_map)){
       register_binding(
         name,
         duration_helpers_map_factory(
           .helpers_function_map[[name]][1],
           .helpers_function_map[[name]][2]
         )
       )
     }
   
     register_binding("dpicoseconds", function(x = 1) {
       abort("Duration in picoseconds not supported in Arrow.")
     })
   }
   ```



-- 
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] AlenkaF commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r853899691


##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -376,6 +376,21 @@ register_bindings_duration_helpers <- function() {
   register_binding("dyears", function(x = 1) {
     make_duration(x * 31557600, "s")
   })
+  register_binding("dseconds", function(x = 1) {
+    make_duration(x, "s")
+  })
+  register_binding("dmilliseconds", function(x = 1) {
+    make_duration(x, "ms")
+  })
+  register_binding("dmicroseconds", function(x = 1) {
+    make_duration(x, "us")
+  })
+  register_binding("dnanoseconds", function(x = 1) {
+    make_duration(x, "ns")
+  })
+  register_binding("dpicoseconds", function(x = 1) {
+    abort("Duration in picoseconds not supported in Arrow.")
+  })

Review Comment:
   I would like to try with programmatically mapping function names and `register_binding()`, to see how it goes =)



-- 
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] AlenkaF commented on pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on PR #12855:
URL: https://github.com/apache/arrow/pull/12855#issuecomment-1105381109

   The errors do not look related ...


-- 
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] AlenkaF commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r855492715


##########
r/tests/testthat/test-dplyr-funcs-datetime.R:
##########
@@ -1303,6 +1303,74 @@ test_that("dminutes, dhours, ddays, dweeks, dmonths, dyears", {
     tibble(),
     ignore_attr = TRUE
   )
+
+  # double -> duration not supported in Arrow.
+  # Error is generated in the C++ code
+  expect_error(
+    test_df %>%
+      arrow_table() %>%
+      mutate(r_obj_dminutes = dminutes(1.12345)) %>%
+      collect()
+  )
+})
+
+test_that("dseconds, dmilliseconds, dmicroseconds, dnanoseconds, dpicoseconds", {
+  example_d <- tibble(x = c(1:10, NA))
+  date_to_add <- ymd("2009-08-03", tz = "Pacific/Marquesas")
+
+  compare_dplyr_binding(
+    .input %>%
+      mutate(
+        dseconds = dseconds(x),
+        dmilliseconds = dmilliseconds(x),
+        dmicroseconds = dmicroseconds(x),
+        dnanoseconds = dnanoseconds(x),
+      ) %>%
+      collect(),
+    example_d,
+    ignore_attr = TRUE
+  )
+
+  compare_dplyr_binding(
+    .input %>%
+      mutate(
+        dseconds = dseconds(x),
+        dmicroseconds = dmicroseconds(x),
+        new_date_1 = date_to_add + dseconds,
+        new_date_2 = date_to_add + dseconds - dmicroseconds,
+        new_duration = dseconds - dmicroseconds
+      ) %>%
+      collect(),
+    example_d,
+    ignore_attr = TRUE

Review Comment:
   I will add a comment, you can wait with merging. But I have to remember, if I am honest =) Will do it tomorrow morning and add the comment then.
   
   Thank you for the review!



-- 
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] AlenkaF commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r855310949


##########
r/tests/testthat/test-dplyr-funcs-datetime.R:
##########
@@ -1304,3 +1304,53 @@ test_that("dminutes, dhours, ddays, dweeks, dmonths, dyears", {
     ignore_attr = TRUE
   )
 })
+
+test_that("dseconds, dmilliseconds, dmicroseconds, dnanoseconds, dpicoseconds", {
+  example_d <- tibble(x = c(1:10, NA))

Review Comment:
   I added a test for the error when the argument multiplied with the value of the multiplication factor of the duration helper function is float (went with easier solution - didn't go forward with forcing evaluation to check for type of an argument or try catching C++ error).



-- 
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] dragosmg commented on pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
dragosmg commented on PR #12855:
URL: https://github.com/apache/arrow/pull/12855#issuecomment-1098850022

   I've been thinking a bit about this. Do you think it's worth having a helper function (to avoid all the repetition), something like `make_duration(x, unit)`?
   Where:
   ```r
   make_duration <- function(x, unit) {
     x <- build_expr("cast", x, options = cast_options(to_type = int64()))
     x$cast(duration(unit))
   }
   ```


-- 
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] AlenkaF commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r851358792


##########
r/tests/testthat/test-dplyr-funcs-datetime.R:
##########
@@ -1304,3 +1304,53 @@ test_that("dminutes, dhours, ddays, dweeks, dmonths, dyears", {
     ignore_attr = TRUE
   )
 })
+
+test_that("dseconds, dmilliseconds, dmicroseconds, dnanoseconds, dpicoseconds", {
+  example_d <- tibble(x = c(1:10, NA))

Review Comment:
   Of course, thanks for this!
   Will search for discussions Dragos already had about casting float -> duration, then test and see =)



-- 
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] jonkeane commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
jonkeane commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r851296829


##########
r/tests/testthat/test-dplyr-funcs-datetime.R:
##########
@@ -1304,3 +1304,53 @@ test_that("dminutes, dhours, ddays, dweeks, dmonths, dyears", {
     ignore_attr = TRUE
   )
 })
+
+test_that("dseconds, dmilliseconds, dmicroseconds, dnanoseconds, dpicoseconds", {
+  example_d <- tibble(x = c(1:10, NA))
+  date_to_add <- ymd("2009-08-03", tz = "America/Chicago")

Review Comment:
   ```suggestion
     date_to_add <- ymd("2009-08-03", tz = "Pacific/Marquesas")
   ```
   
   If we don't need a specific feature of Chicago's timezone here, we should use our default "unusual" timezone of "Pacific/Marquesas" so that we have a low probability of this being a developer's timezone



##########
r/tests/testthat/test-dplyr-funcs-datetime.R:
##########
@@ -1304,3 +1304,53 @@ test_that("dminutes, dhours, ddays, dweeks, dmonths, dyears", {
     ignore_attr = TRUE
   )
 })
+
+test_that("dseconds, dmilliseconds, dmicroseconds, dnanoseconds, dpicoseconds", {
+  example_d <- tibble(x = c(1:10, NA))

Review Comment:
   Should we also test what happens when we pass floats here too? 
   
   ```
   > lubridate::dseconds(1.5)
   [1] "1.5s"
   ```
   
   Seems to work, so we should ensure we can do that (or error helpfully if we can't for some reason)



##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -376,6 +376,21 @@ register_bindings_duration_helpers <- function() {
   register_binding("dyears", function(x = 1) {
     make_duration(x * 31557600, "s")
   })
+  register_binding("dseconds", function(x = 1) {
+    make_duration(x, "s")
+  })
+  register_binding("dmilliseconds", function(x = 1) {
+    make_duration(x, "ms")
+  })
+  register_binding("dmicroseconds", function(x = 1) {
+    make_duration(x, "us")
+  })
+  register_binding("dnanoseconds", function(x = 1) {
+    make_duration(x, "ns")
+  })
+  register_binding("dpicoseconds", function(x = 1) {
+    abort("Duration in picoseconds not supported in Arrow.")
+  })

Review Comment:
   I think we should keep this as is written out like this, but this is right on the border where we might consider doing the mapping between function names and durations programmatically call `register_binding()`. 



-- 
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] AlenkaF commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r853898124


##########
r/tests/testthat/test-dplyr-funcs-datetime.R:
##########
@@ -1304,3 +1304,53 @@ test_that("dminutes, dhours, ddays, dweeks, dmonths, dyears", {
     ignore_attr = TRUE
   )
 })
+
+test_that("dseconds, dmilliseconds, dmicroseconds, dnanoseconds, dpicoseconds", {
+  example_d <- tibble(x = c(1:10, NA))

Review Comment:
   As `duration` type in Arrow is `int64` and we can't pass floats here I will go with erroring helpfully. Will add it in the next commit.



-- 
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] dragosmg commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
dragosmg commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r853929212


##########
r/tests/testthat/test-dplyr-funcs-datetime.R:
##########
@@ -1304,3 +1304,53 @@ test_that("dminutes, dhours, ddays, dweeks, dmonths, dyears", {
     ignore_attr = TRUE
   )
 })
+
+test_that("dseconds, dmilliseconds, dmicroseconds, dnanoseconds, dpicoseconds", {
+  example_d <- tibble(x = c(1:10, NA))

Review Comment:
   [ARROW-16253](https://issues.apache.org/jira/browse/ARROW-16253) might be relevant here too. 



-- 
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] AlenkaF commented on a diff in pull request #12855: ARROW-14942: [R] Bindings for lubridate's dpicoseconds, dnanoseconds, desconds, dmilliseconds, dmicroseconds

Posted by GitBox <gi...@apache.org>.
AlenkaF commented on code in PR #12855:
URL: https://github.com/apache/arrow/pull/12855#discussion_r854052860


##########
r/R/dplyr-funcs-datetime.R:
##########
@@ -376,6 +376,21 @@ register_bindings_duration_helpers <- function() {
   register_binding("dyears", function(x = 1) {
     make_duration(x * 31557600, "s")
   })
+  register_binding("dseconds", function(x = 1) {
+    make_duration(x, "s")
+  })
+  register_binding("dmilliseconds", function(x = 1) {
+    make_duration(x, "ms")
+  })
+  register_binding("dmicroseconds", function(x = 1) {
+    make_duration(x, "us")
+  })
+  register_binding("dnanoseconds", function(x = 1) {
+    make_duration(x, "ns")
+  })
+  register_binding("dpicoseconds", function(x = 1) {
+    abort("Duration in picoseconds not supported in Arrow.")
+  })

Review Comment:
   Yeah, it would be good to post an output 🤦‍♀️ 
   
   <details>
   <summary>See the output:</summary>
   <pre>
   
   ```R
   > devtools::test(filter="datetime")
   ℹ Loading arrow
   Some features are not enabled in this build of Arrow. Run `arrow_info()` for more information.
   ℹ Testing arrow
   Some features are not enabled in this build of Arrow. Run `arrow_info()` for more information.
   ✔ | F W S  OK | Context
   ✖ | 7     381 | dplyr-funcs-datetime [2.0s]                                                                                                                  
   ─────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────
   Failure (test-dplyr-funcs-datetime.R:1263:3): dminutes, dhours, ddays, dweeks, dmonths, dyears
   `via_batch <- rlang::eval_tidy(expr, rlang::new_data_mask(rlang::env(.input = record_batch(tbl))))` threw an unexpected warning.
   Message: Expression dyears(x) not supported in Arrow; pulling data into R
   Class:   simpleWarning/warning/condition
   Backtrace:
     1. arrow:::compare_dplyr_binding(...)
          at test-dplyr-funcs-datetime.R:1263:2
    12. arrow::mutate.ArrowTabular(...)
    13. arrow::abandon_ship(call, .data, msg)
          at r/R/dplyr-mutate.R:62:6
   
   Failure (test-dplyr-funcs-datetime.R:1263:3): dminutes, dhours, ddays, dweeks, dmonths, dyears
   `via_table <- rlang::eval_tidy(expr, rlang::new_data_mask(rlang::env(.input = arrow_table(tbl))))` threw an unexpected warning.
   Message: Expression dyears(x) not supported in Arrow; pulling data into R
   Class:   simpleWarning/warning/condition
   Backtrace:
     1. arrow:::compare_dplyr_binding(...)
          at test-dplyr-funcs-datetime.R:1263:2
    12. arrow::mutate.ArrowTabular(...)
    13. arrow::abandon_ship(call, .data, msg)
          at r/R/dplyr-mutate.R:62:6
   
   Failure (test-dplyr-funcs-datetime.R:1278:3): dminutes, dhours, ddays, dweeks, dmonths, dyears
   `via_batch <- rlang::eval_tidy(expr, rlang::new_data_mask(rlang::env(.input = record_batch(tbl))))` threw an unexpected warning.
   Message: Expression date_to_add + ddays - dhours(3) not supported in Arrow; pulling data into R
   Class:   simpleWarning/warning/condition
   Backtrace:
     1. arrow:::compare_dplyr_binding(...)
          at test-dplyr-funcs-datetime.R:1278:2
    12. arrow::mutate.ArrowTabular(...)
    13. arrow::abandon_ship(call, .data, msg)
          at r/R/dplyr-mutate.R:62:6
   
   Failure (test-dplyr-funcs-datetime.R:1278:3): dminutes, dhours, ddays, dweeks, dmonths, dyears
   `via_table <- rlang::eval_tidy(expr, rlang::new_data_mask(rlang::env(.input = arrow_table(tbl))))` threw an unexpected warning.
   Message: Expression date_to_add + ddays - dhours(3) not supported in Arrow; pulling data into R
   Class:   simpleWarning/warning/condition
   Backtrace:
     1. arrow:::compare_dplyr_binding(...)
          at test-dplyr-funcs-datetime.R:1278:2
    12. arrow::mutate.ArrowTabular(...)
    13. arrow::abandon_ship(call, .data, msg)
          at r/R/dplyr-mutate.R:62:6
   
   Failure (test-dplyr-funcs-datetime.R:1292:3): dminutes, dhours, ddays, dweeks, dmonths, dyears
   `via_batch <- rlang::eval_tidy(expr, rlang::new_data_mask(rlang::env(.input = record_batch(tbl))))` threw an unexpected warning.
   Message: Expression dminutes(1) not supported in Arrow; pulling data into R
   Class:   simpleWarning/warning/condition
   Backtrace:
     1. arrow:::compare_dplyr_binding(...)
          at test-dplyr-funcs-datetime.R:1292:2
    12. arrow::mutate.ArrowTabular(...)
    13. arrow::abandon_ship(call, .data, msg)
          at r/R/dplyr-mutate.R:62:6
   
   Failure (test-dplyr-funcs-datetime.R:1292:3): dminutes, dhours, ddays, dweeks, dmonths, dyears
   `via_table <- rlang::eval_tidy(expr, rlang::new_data_mask(rlang::env(.input = arrow_table(tbl))))` threw an unexpected warning.
   Message: Expression dminutes(1) not supported in Arrow; pulling data into R
   Class:   simpleWarning/warning/condition
   Backtrace:
     1. arrow:::compare_dplyr_binding(...)
          at test-dplyr-funcs-datetime.R:1292:2
    12. arrow::mutate.ArrowTabular(...)
    13. arrow::abandon_ship(call, .data, msg)
          at r/R/dplyr-mutate.R:62:6
   
   Error (test-dplyr-funcs-datetime.R:1312:3): dseconds, dmilliseconds, dmicroseconds, dnanoseconds, dpicoseconds
   Error in `collect(.)`: NotImplemented: Function 'multiply_checked' has no kernel matching input types (array[int32], scalar[string])
   /Users/alenkafrim/repos/arrow/cpp/src/arrow/compute/exec/expression.cc:340  call.function->DispatchBest(&descrs)
   /Users/alenkafrim/repos/arrow/cpp/src/arrow/compute/exec/expression.cc:411  BindImpl(std::move(argument), in, shape, exec_context)
   /Users/alenkafrim/repos/arrow/cpp/src/arrow/compute/exec/expression.cc:411  BindImpl(std::move(argument), in, shape, exec_context)
   /Users/alenkafrim/repos/arrow/cpp/src/arrow/compute/exec/project_node.cc:67  expr.Bind(*inputs[0]->output_schema())
   Backtrace:
     1. arrow:::compare_dplyr_binding(...)
          at test-dplyr-funcs-datetime.R:1312:2
    11. arrow::collect.arrow_dplyr_query(.)
   ─────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────────
   
   ══ Results ══════════════════════════════════════════════════════════════════════════════════════════════════════════════════════════════════════════════════
   Duration: 2.2 s
   
   [ FAIL 7 | WARN 0 | SKIP 0 | PASS 381 ]
   ```
   </pre>
   </details>



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