Skip to content

Commit

Permalink
fix: sub-day precision Date should be floored when treated as integer
Browse files Browse the repository at this point in the history
  • Loading branch information
eitsupi committed Feb 6, 2025
1 parent eaa2634 commit 8b314a3
Show file tree
Hide file tree
Showing 2 changed files with 19 additions and 5 deletions.
9 changes: 4 additions & 5 deletions R/write-parquet.R
Original file line number Diff line number Diff line change
Expand Up @@ -162,10 +162,9 @@ prepare_write_df <- function(x) {
}

# Date must be integer
dates <- which(vapply(x, "inherits", "Date", FUN.VALUE = logical(1)))
for (idx in dates) {
# this keeps the class
mode(x[[idx]]) <- "integer"
double_dates <- which(vapply(x, function(x) inherits(x, "Date") && is.double(x), FUN.VALUE = logical(1)))
for (idx in double_dates) {
x[[idx]] <- .Date(as.integer(floor(as.numeric(x[[idx]]))))
}

# Convert hms to double
Expand Down Expand Up @@ -405,4 +404,4 @@ append_parquet <- function(
} else {
res
}
}
}
15 changes: 15 additions & 0 deletions tests/testthat/test-write-parquet-2.R
Original file line number Diff line number Diff line change
Expand Up @@ -186,3 +186,18 @@ test_that("zstd compression", {
expect_equal(read_parquet_page(tmp, 4L)$codec, "ZSTD")
expect_equal(read_parquet(tmp), d);
})

test_that("Conversion of sub-dates prior Posix origin is correct", {
data <- data.frame(
days = as.Date(c(-1.1, -0.1, 0, 0.1, 1.1), origin = "1970-01-01")
)

tmp <- tempfile(fileext = ".parquet")
on.exit(unlink(tmp), add = TRUE)

write_parquet(data, tmp)
expect_equal(
as.character(as.data.frame(read_parquet(tmp))$date),
as.character(data$date)
)
})

0 comments on commit 8b314a3

Please sign in to comment.