Skip to content

Commit

Permalink
Merge pull request #116 from chainsawriot/fixpoll
Browse files Browse the repository at this point in the history
fix #115
  • Loading branch information
schochastics authored Nov 28, 2022
2 parents 1746946 + 9b55833 commit d8ef57d
Show file tree
Hide file tree
Showing 3 changed files with 25 additions and 1 deletion.
6 changes: 5 additions & 1 deletion R/datastructure.R
Original file line number Diff line number Diff line change
Expand Up @@ -112,7 +112,11 @@ parse_poll <- function(poll, parse_date = TRUE) {
if (parse_date) {
output$expires_at <- format_date(output$expires_at)
}
for (field in c("own_votes", "options", "emojis")) {
output[["own_votes"]] <- I(list(list()))
if (has_name_(poll, "own_votes") & length(poll[["own_votes"]] != 0)) {
output[["own_votes"]] <- list(poll[["own_votes"]])
}
for (field in c("options", "emojis")) {
if (has_name_(poll, field) & length(poll[[field]]) != 0) {
output[[field]] <- list(dplyr::bind_rows(poll[[field]]))
} else {
Expand Down
Binary file not shown.
20 changes: 20 additions & 0 deletions tests/testthat/test-parse_status.R
Original file line number Diff line number Diff line change
Expand Up @@ -96,3 +96,23 @@ test_that("date parsing", {
expect_true("POSIXlt" %in% class(res1$created_at))
expect_false("POSIXlt" %in% class(res2$created_at))
})

test_that("poll parsing with own_votes, issue #115", {
poll <- list(id = "615", expires_at = "2022-11-27T11:06:56.000Z", expired = TRUE,
multiple = TRUE, votes_count = 86L, voters_count = 84L, voted = TRUE,
own_votes = list(0L), options = list(list(title = "mu4e",
votes_count = 50L),
list(title = "notmuch", votes_count = 20L),
list(title = "gnus", votes_count = 13L),
list(title = "other (please comment)",
votes_count = 3L)),
emojis = list())
expect_error(parse_poll(poll), NA)
poll$own_votes <- list()
expect_error(parse_poll(poll), NA)
## integration test
timeline <- readRDS("../testdata/timeline/timeline_with_poll115.RDS")
expect_error(s <- parse_status(timeline[[20]]), NA)
expect_equal(s$poll[[1]]$own_votes[[1]][[1]], 0)
expect_error(v(parse_status)(timeline), NA)
})

0 comments on commit d8ef57d

Please sign in to comment.