Skip to content

Commit

Permalink
Add Expression(schema) method and improve adq print method
Browse files Browse the repository at this point in the history
  • Loading branch information
nealrichardson committed May 10, 2021
1 parent 795e1f9 commit 2e6374f
Show file tree
Hide file tree
Showing 8 changed files with 52 additions and 10 deletions.
4 changes: 4 additions & 0 deletions r/R/arrowExports.R

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

15 changes: 9 additions & 6 deletions r/R/dplyr.R
Original file line number Diff line number Diff line change
Expand Up @@ -70,17 +70,20 @@ make_field_refs <- function(field_names) {
#' @export
print.arrow_dplyr_query <- function(x, ...) {
schm <- x$.data$schema
fields <- map_chr(x$selected_columns, function(expr) {
types <- map_chr(x$selected_columns, function(expr) {
name <- expr$field_name
if (nzchar(name)) {
schm$GetFieldByName(name)$ToString()
# Just a field_ref, so look up in the schema
schm$GetFieldByName(name)$type$ToString()
} else {
# It's "" because this is not a field_ref, it's a more complex expression
"expr"
# Expression, so get its type and append the expression
paste0(
expr$type(schm)$ToString(),
" (", expr$ToString(), ")"
)
}
})
# Strip off the field names as they are in the dataset and add the renamed ones
fields <- paste(names(fields), sub("^.*?: ", "", fields), sep = ": ", collapse = "\n")
fields <- paste(names(types), types, sep = ": ", collapse = "\n")
cat(class(x$.data)[1], " (query)\n", sep = "")
cat(fields, "\n", sep = "")
cat("\n")
Expand Down
1 change: 1 addition & 0 deletions r/R/expression.R
Original file line number Diff line number Diff line change
Expand Up @@ -250,6 +250,7 @@ print.array_expression <- function(x, ...) {
Expression <- R6Class("Expression", inherit = ArrowObject,
public = list(
ToString = function() compute___expr__ToString(self),
type = function(schema) compute___expr__type(self, schema),
cast = function(to_type, safe = TRUE, ...) {
opts <- list(
to_type = to_type,
Expand Down
17 changes: 17 additions & 0 deletions r/src/arrowExports.cpp

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

8 changes: 8 additions & 0 deletions r/src/expression.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -68,4 +68,12 @@ std::string compute___expr__ToString(const std::shared_ptr<compute::Expression>&
return x->ToString();
}

// [[arrow::export]]
std::shared_ptr<arrow::DataType> compute___expr__type(
const std::shared_ptr<compute::Expression>& x,
const std::shared_ptr<arrow::Schema>& schema) {
auto bound = ValueOrStop(x->Bind(*schema));
return bound.type();
}

#endif
4 changes: 2 additions & 2 deletions r/tests/testthat/test-dataset.R
Original file line number Diff line number Diff line change
Expand Up @@ -965,7 +965,7 @@ test_that("mutate()", {
chr: string
dbl: double
int: int32
twice: expr
twice: double (multiply_checked(int, 2))
* Filter: ((multiply_checked(dbl, 2) > 14) and (subtract_checked(dbl, 50) < 3))
See $.data for the source Arrow object",
Expand Down Expand Up @@ -1120,7 +1120,7 @@ test_that("arrange()", {
chr: string
dbl: double
int: int32
twice: expr
twice: double (multiply_checked(int, 2))
* Filter: ((multiply_checked(dbl, 2) > 14) and (subtract_checked(dbl, 50) < 3))
* Sorted by chr [asc], multiply_checked(int, 2) [desc], add_checked(dbl, int) [asc]
Expand Down
5 changes: 3 additions & 2 deletions r/tests/testthat/test-dplyr-mutate.R
Original file line number Diff line number Diff line change
Expand Up @@ -346,10 +346,11 @@ test_that("print a mutated table", {
print(),
'InMemoryDataset (query)
int: int32
twice: expr
twice: double (multiply_checked(int, 2))
See $.data for the source Arrow object',
fixed = TRUE)
fixed = TRUE
)

# Handling non-expressions/edge cases
skip("InMemoryDataset$Project() doesn't accept array (or could it?)")
Expand Down
8 changes: 8 additions & 0 deletions r/tests/testthat/test-expression.R
Original file line number Diff line number Diff line change
Expand Up @@ -76,6 +76,14 @@ test_that("C++ expressions", {
'Expression\n(f > 4)',
fixed = TRUE
)
expect_type_equal(
f$type(schema(f = float64())),
float64()
)
expect_type_equal(
(f > 4)$type(schema(f = float64())),
bool()
)
# Interprets that as a list type
expect_r6_class(f == c(1L, 2L), "Expression")
})
Expand Down

0 comments on commit 2e6374f

Please sign in to comment.