From 8b314a3e684c838992c2110072ed04f28793f94e Mon Sep 17 00:00:00 2001 From: eitsupi Date: Thu, 6 Feb 2025 03:51:32 +0000 Subject: [PATCH] fix: sub-day precision Date should be floored when treated as integer --- R/write-parquet.R | 9 ++++----- tests/testthat/test-write-parquet-2.R | 15 +++++++++++++++ 2 files changed, 19 insertions(+), 5 deletions(-) diff --git a/R/write-parquet.R b/R/write-parquet.R index 9690d46..e456f89 100644 --- a/R/write-parquet.R +++ b/R/write-parquet.R @@ -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 @@ -405,4 +404,4 @@ append_parquet <- function( } else { res } -} \ No newline at end of file +} diff --git a/tests/testthat/test-write-parquet-2.R b/tests/testthat/test-write-parquet-2.R index 8b1ec85..d6f8ec9 100644 --- a/tests/testthat/test-write-parquet-2.R +++ b/tests/testthat/test-write-parquet-2.R @@ -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) + ) +})