Skip to content

Commit

Permalink
Merge pull request #44 from rOpenGov/feat/add-week-number-parsing
Browse files Browse the repository at this point in the history
Add week number parsing
  • Loading branch information
aleksanderbl29 authored Dec 10, 2024
2 parents df41ee5 + 51b2567 commit 991d202
Show file tree
Hide file tree
Showing 2 changed files with 38 additions and 1 deletion.
31 changes: 30 additions & 1 deletion R/dst_date_parse.R
Original file line number Diff line number Diff line change
@@ -1,7 +1,13 @@
#' Helper function to parse the dates from the statbank.
#'
#' @description
#' The weeks are returned to be the first day of the week. It does happen that
#' the first day of week 1 is a day in december of the year before. This is
#' intended and a weird artefact of the system we have.
#'
#'
#' @param dst_date A vector of length one or more with date formats like
#' 1982M12D09, 1982M12, 1982Q4 or 1982
#' 1982M12D09, 2004U27, 1982M12, 1982Q4 or 1982
#' @returns Returns the input date formatted to be Europe/Copenhagen
#' @noRd
dst_date_parse <- function(dst_date) {
Expand All @@ -22,6 +28,29 @@ dst_date_parse <- function(dst_date) {
),
tz = tz
)
} else if (
# nolint start
all(stringr::str_detect(dst_date, "^[0-9]{4}U(0[1-9]|[1-4][0-9]|5[0-2])$")) &&
all(stringr::str_length(string = dst_date) == 7)
) {
# Weekly format
# Find year and and week
year <- lubridate::ymd(paste0(
stringr::str_sub(dst_date, start = 1L, end = 4L),
"-01-01"))
# nolint end

week <- stringr::str_sub(dst_date, start = -2L)

# Get the first day of the week that is 7 (days) times weeks minus one to
# account for weird date-numbers. Also ensure the week starts on a monday
dst_date <- lubridate::floor_date(
year + lubridate::days(7 * (as.numeric(week) - 1)),
unit = "week",
week_start = 1
)

dst_date <- lubridate::ymd(dst_date, tz = tz)
} else if (
# nolint start
all(stringr::str_detect(
Expand Down
8 changes: 8 additions & 0 deletions tests/testthat/test-dst_date_parse.R
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,10 @@ test_that("dst_date_parse gives the correct class.", {
expect_equal(class(dst_date_parse(dst_date = "2000M01D01")), exp_dates)
expect_equal(class(dst_date_parse(dst_date = c("2000M01D20", "2000M02D21", "2000M03D23", "2000M04D24"))), exp_dates)

# Weekly
expect_equal(class(dst_date_parse(dst_date = "2000U01")), exp_dates)
expect_equal(class(dst_date_parse(dst_date = c("2000U01", "2000U03", "2023U47", "2005U11"))), exp_dates)

# Monthly
expect_equal(class(dst_date_parse(dst_date = "2000M01")), exp_dates)
expect_equal(class(dst_date_parse(dst_date = c("2000M01", "2000M02", "2000M03", "2000M04", "2000M10", "2000M11"))), exp_dates)
Expand Down Expand Up @@ -33,6 +37,10 @@ test_that("Test that dst_date_parse stops when the input is bad.", {
expect_error(dst_date_parse(dst_date = "2000M01D35"))
expect_error(dst_date_parse(dst_date = "2000M10D40"))

# Daily
expect_error(dst_date_parse(dst_date = "2000U57"))
expect_error(dst_date_parse(dst_date = "20000U40"))

# Monthly
expect_error(dst_date_parse(dst_date = "20000M01"))
expect_error(dst_date_parse(dst_date = "2000M101"))
Expand Down

0 comments on commit 991d202

Please sign in to comment.