Skip to content

Commit

Permalink
feat: more integer conversions for ids
Browse files Browse the repository at this point in the history
  • Loading branch information
m-muecke committed Dec 10, 2024
1 parent e6efb57 commit f773dc9
Show file tree
Hide file tree
Showing 3 changed files with 28 additions and 26 deletions.
9 changes: 5 additions & 4 deletions R/assertions.R
Original file line number Diff line number Diff line change
Expand Up @@ -31,10 +31,7 @@ is_count_or_null <- function(x) {
is.null(x) || is_count(x)
}

is_valid_date <- function(x) {
if (is.null(x)) {
return(TRUE)
}
is_dateish <- function(x) {
if (length(x) != 1L) {
return(FALSE)
}
Expand All @@ -45,3 +42,7 @@ is_valid_date <- function(x) {
FALSE
}
}

is_dateish_or_null <- function(x) {
is.null(x) || is_dateish(x)
}
9 changes: 5 additions & 4 deletions R/indicators.R
Original file line number Diff line number Diff line change
Expand Up @@ -305,7 +305,7 @@ wb_indicator <- function(indicator = NULL, lang = "en") {
id = map_chr(data, "id"),
name = map_chr(data, "name"),
unit = map_chr(data, "unit"),
source_id = map_chr(data, \(x) x$source$id),
source_id = map_chr(data, \(x) x$source$id) |> as.integer(),
source_value = map_chr(data, \(x) x$source$value),
source_note = map_chr(data, "sourceNote"),
source_organization = map_chr(data, "sourceOrganization"),
Expand All @@ -315,7 +315,8 @@ wb_indicator <- function(indicator = NULL, lang = "en") {
} else {
NA_character_
}
}),
}) |>
as.integer(),
topic_value = map_chr(data, function(x) {
if (length(x$topics) > 0L && length(x$topics[[1L]]) > 0L) {
x$topics[[1L]]$value
Expand Down Expand Up @@ -373,8 +374,8 @@ wb_country_indicator <- function(indicator = "NY.GDP.MKTP.CD",
stopifnot(
is_string(indicator),
is_character_or_null(country), nchar(country) %in% 2:3,
is_valid_date(start_date),
is_valid_date(end_date)
is_dateish_or_null(start_date),
is_dateish_or_null(end_date)
)
has_start_date <- !is.null(start_date)
has_end_date <- !is.null(end_date)
Expand Down
36 changes: 18 additions & 18 deletions tests/testthat/test-utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -35,28 +35,28 @@ test_that("format_date works", {
expect_identical(format_date("", "2025"), ":2025")
})

test_that("is_valid_date works", {
test_that("is_dateish_or_null works", {
# NULL input
expect_true(is_valid_date(NULL))
expect_true(is_dateish_or_null(NULL))
# valid year
expect_true(is_valid_date(2024))
expect_true(is_valid_date("2024"))
expect_true(is_dateish_or_null(2024))
expect_true(is_dateish_or_null("2024"))
# valid year with month
expect_true(is_valid_date("2024M01"))
expect_true(is_valid_date("2024M12"))
expect_true(is_dateish_or_null("2024M01"))
expect_true(is_dateish_or_null("2024M12"))
# valid year with quarter
expect_true(is_valid_date("2024Q1"))
expect_true(is_valid_date("2024Q4"))
expect_true(is_dateish_or_null("2024Q1"))
expect_true(is_dateish_or_null("2024Q4"))
# invalid lengths
expect_false(is_valid_date(c("2024", "2025")))
expect_false(is_valid_date(c("2024M01", "2024Q1")))
expect_false(is_dateish_or_null(c("2024", "2025")))
expect_false(is_dateish_or_null(c("2024M01", "2024Q1")))
# invalid formats
expect_false(is_valid_date("202"))
expect_false(is_valid_date("2024M13"))
expect_false(is_valid_date("2024Q5"))
expect_false(is_valid_date("2024M00"))
expect_false(is_valid_date("2024X01"))
expect_false(is_valid_date("24M01"))
expect_false(is_valid_date("2024-Q1"))
expect_false(is_valid_date("2024/M01"))
expect_false(is_dateish_or_null("202"))
expect_false(is_dateish_or_null("2024M13"))
expect_false(is_dateish_or_null("2024Q5"))
expect_false(is_dateish_or_null("2024M00"))
expect_false(is_dateish_or_null("2024X01"))
expect_false(is_dateish_or_null("24M01"))
expect_false(is_dateish_or_null("2024-Q1"))
expect_false(is_dateish_or_null("2024/M01"))
})

0 comments on commit f773dc9

Please sign in to comment.