Skip to content

Commit

Permalink
Organiza o fetch_votacoes_camara
Browse files Browse the repository at this point in the history
  • Loading branch information
jairNeto committed Feb 21, 2019
1 parent e454b79 commit 6d5c3ed
Show file tree
Hide file tree
Showing 9 changed files with 41 additions and 41 deletions.
2 changes: 1 addition & 1 deletion R/colunas_constants.R
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@
"nome_poder_origem"="character", "sigla_casa_origem"="character", "nome_casa_origem"="character", "proposicoes_relacionadas"="character",
"proposicoes_apensadas"="character", "codigo_natureza"="integer", "nome_natureza"="character", "descricao_natureza"="character", "autor_nome"="character")

.COLNAMES_VOTACOES <- c("id"="integer","uri"="character","titulo"="character","uriEvento"="character","uriProposicaoPrincipal"="character",
.COLNAMES_VOTACOES_CAMARA <- c("id"="integer","uri"="character","titulo"="character","uriEvento"="character","uriProposicaoPrincipal"="character",
"tipoVotacao"="character","aprovada"="logical","placarSim"="integer","placarNao"="integer","placarAbstencao"="integer",
"proposicao.id"="integer","proposicao.uri"="character","proposicao.siglaTipo"="character","proposicao.codTipo"="integer",
"proposicao.numero"="integer","proposicao.ano"="integer","proposicao.ementa"="character")
Expand Down
23 changes: 0 additions & 23 deletions R/proposicoes.R
Original file line number Diff line number Diff line change
Expand Up @@ -142,29 +142,6 @@ fetch_proposicao_senado <- function(id) {
.coerce_types(.COLNAMES_PROPOSICAO_SENADO)
}

#' @title Fetches all the votings which a proposition went through
#' @description Returns all the votings related to a proposition by its id.
#' @param id_prop Proposition's ID
#' @return Dataframe containing all the votings.
#' @examples
#' votacoes_pec241 <- fetch_votacoes(2088351)
#' @seealso
#' \code{\link[rcongresso]{fetch_id_proposicao_camara}}, \code{\link[rcongresso]{fetch_proposicao_from_votacao}}
#' @rdname fetch_votacoes
#' @export
fetch_votacoes <- function(id_prop){
id <- NULL
tibble::tibble(id = id_prop) %>%
dplyr::mutate(path = paste0(.CAMARA_PROPOSICOES_PATH, "/", id, "/votacoes")) %>%
dplyr::rowwise() %>%
dplyr::do(
.camara_api(.$path)
) %>%
dplyr::ungroup() %>%
.assert_dataframe_completo(.COLNAMES_VOTACOES) %>%
.coerce_types(.COLNAMES_VOTACOES)
}

#' @title Fetches all propositions related to a proposition
#' @description Returns all propositions related to a proposition by its id.
#' @param id_prop Proposition's ID
Expand Down
25 changes: 24 additions & 1 deletion R/votacoes.R
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,29 @@ fetch_votacao <- function(id_votacao = NULL){
.coerce_types(.COLNAMES_VOTACAO)
}

#' @title Fetches all the votings which a proposition went through
#' @description Returns all the votings related to a proposition by its id.
#' @param id_prop Proposition's ID
#' @return Dataframe containing all the votings.
#' @examples
#' votacoes_pec241 <- fetch_votacoes_camara(2088351)
#' @seealso
#' \code{\link[rcongresso]{fetch_id_proposicao_camara}}, \code{\link[rcongresso]{fetch_proposicao_from_votacao}}
#' @rdname fetch_votacoes_camara
#' @export
fetch_votacoes_camara <- function(id_prop){
id <- NULL
tibble::tibble(id = id_prop) %>%
dplyr::mutate(path = paste0(.CAMARA_PROPOSICOES_PATH, "/", id, "/votacoes")) %>%
dplyr::rowwise() %>%
dplyr::do(
.camara_api(.$path)
) %>%
dplyr::ungroup() %>%
.assert_dataframe_completo(.COLNAMES_VOTACOES_CAMARA) %>%
.coerce_types(.COLNAMES_VOTACOES_CAMARA)
}

#' @title Fetches details about a voting on Senate
#' @description Fetches details about a voting on Senate.
#' Ao fim, a função retira todos as colunas que tenham tipo lista para uniformizar o dataframe.
Expand Down Expand Up @@ -120,7 +143,7 @@ fetch_votos <- function(id_votacao = NULL){
#' @param votacoes Dataframe containing all the votings related to a proposition
#' @return Dataframe containing only the last voting related to a proposition
#' @examples
#' votacoes_pec241 <- fetch_votacoes(2088351)
#' votacoes_pec241 <- fetch_votacoes_camara(2088351)
#' ultima_votacao <- ultima_votacao(votacoes_pec241)
#' @rdname ultima_votacao
#' @export
Expand Down
10 changes: 5 additions & 5 deletions man/fetch_votacoes.Rd → man/fetch_votacoes_camara.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion man/ultima_votacao.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

7 changes: 0 additions & 7 deletions tests/testthat/test_proposicoes.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,6 @@ pec_241_id <<- fetch_id_proposicao_camara("PEC", 241, 2016)
pec_241_por_id <<- fetch_proposicao_camara(pec_241_id)
pls_91341 <<- fetch_proposicao_senado(91341)
pls_1489 <<- fetch_proposicao_senado(1489)
votacoes_pec_241 <<- fetch_votacoes(pec_241_id)
relacionadas_pec_241 <<- fetch_relacionadas(pec_241_id)
deferimento <- fetch_deferimento(c("102343", "109173", "115853"))

Expand All @@ -29,14 +28,12 @@ test_that("GET proposição com ID inexistente", {expect_error(fetch_proposicao_
test_that("Is dataframe", {
expect_true(is.data.frame(pec_241))
expect_true(is.data.frame(pec_241_por_id))
expect_true(is.data.frame(votacoes_pec_241))
expect_true(is.data.frame(deferimento))
})

test_that("Not Empty", {
expect_true(nrow(pec_241) != 0)
expect_true(nrow(pec_241_por_id) != 0)
expect_true(nrow(votacoes_pec_241) != 0)
expect_true(nrow(deferimento) != 0)
})

Expand Down Expand Up @@ -65,10 +62,6 @@ test_that("fetch_proposicao_senado() is dataframe", {
expect_true(is.data.frame(pls_1489))
})

test_that("fetch_votacoes()", {
expect_true(all(sapply(votacoes_pec_241, class) %in% .COLNAMES_VOTACOES))
})

test_that("fetch_relacionadas()", {
expect_true(all(sapply(relacionadas_pec_241, class) %in% .COLNAMES_RELACIONADAS))
})
Expand Down
9 changes: 8 additions & 1 deletion tests/testthat/test_votacoes.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,10 +4,11 @@ context("Votações")
votos_pec241 <<- fetch_votos(7252)
votacao_pec241 <<- fetch_votacao(7252)
orientacoes_pec241 <<- fetch_orientacoes(7252)
ultima_votacao_pec241 <<- fetch_votacoes(2088351) %>% ultima_votacao()
ultima_votacao_pec241 <<- fetch_votacoes_camara(2088351) %>% ultima_votacao()
votos_partidos_pec241 <<- get_votos_partidos(7252)
proposicao_votacao7252 <<- fetch_proposicao_from_votacao(7252)
proposicao_votacao_senado <<- fetch_votacoes_senado(91341)
votacoes_pec_241_prop_id <<- fetch_votacoes_camara(pec_241_id)


# Testa erros
Expand All @@ -24,6 +25,7 @@ test_that("Is dataframe", {
expect_true(is.data.frame(votos_partidos_pec241))
expect_true(is.data.frame(proposicao_votacao7252))
expect_true(is.data.frame(proposicao_votacao_senado))
expect_true(is.data.frame(votacoes_pec_241_prop_id))
})

test_that("Not Empty", {
Expand All @@ -34,6 +36,11 @@ test_that("Not Empty", {
expect_true(nrow(votos_partidos_pec241) != 0)
expect_true(nrow(proposicao_votacao7252) != 0)
expect_true(nrow(proposicao_votacao_senado) != 0)
expect_true(nrow(votacoes_pec_241_prop_id) != 0)
})

test_that("fetch_votacoes_camara()", {
expect_true(all(sapply(votacoes_pec_241_prop_id, class) %in% .COLNAMES_VOTACOES_CAMARA))
})

test_that("fetch_votos()", {
Expand Down
2 changes: 1 addition & 1 deletion vignettes/introducao-rcongresso.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@ glimpse(pl4302)
Com o ID da proposição você pode recuperar **todas as votações pelas quais aquela proposição já passou**:

```{r}
votacoes_pl4302 <- fetch_votacoes(id_prop=pl4302_id)
votacoes_pl4302 <- fetch_votacoes_camara(id_prop=pl4302_id)
votacoes_pl4302 %>%
select(id, titulo, placarSim, placarNao, placarAbstencao) %>%
Expand Down
2 changes: 1 addition & 1 deletion vignettes/purrr-e-rcongresso.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ Uma proposição pode ter várias votações no plenário da câmara. Aqui vamos

```{r}
fetch_id_ultima_votacao = function(id_proposicao){
fetch_votacoes(id_proposicao) %>%
fetch_votacoes_camara(id_proposicao) %>%
ultima_votacao() %>%
pull(id)
}
Expand Down

0 comments on commit 6d5c3ed

Please sign in to comment.