Skip to content

Commit

Permalink
Make printouts change depending on counties vs COGs
Browse files Browse the repository at this point in the history
  • Loading branch information
camille-s committed Dec 15, 2023
1 parent 1e259f9 commit 8714ca2
Show file tree
Hide file tree
Showing 5 changed files with 37 additions and 11 deletions.
3 changes: 2 additions & 1 deletion R/multi_geo_fetch.R
Original file line number Diff line number Diff line change
Expand Up @@ -411,7 +411,8 @@ multi_geo_prep <- function(src,
msa = msa,
us = us,
new_england = new_england,
nhood_type = nhood_valid_fips
nhood_type = nhood_valid_fips,
use_cogs = use_cogs
)
# print title
rlang::exec(table_printout, !!!tbl_title)
Expand Down
19 changes: 15 additions & 4 deletions R/printouts.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,11 +4,17 @@ bold_hdr <- function(place_name, place_type) {
}

######## CENSUS: ACS + DECENNIAL ----
geo_printout <- function(neighborhoods, tracts, blockgroups, towns, regions, pumas, counties, all_counties, drop_counties, state, msa, us, new_england, nhood_type) {
geo_printout <- function(neighborhoods, tracts, blockgroups, towns, regions, pumas, counties, all_counties, drop_counties, state, msa, us, new_england, nhood_type, use_cogs) {
geos <- tibble::lst(neighborhoods, tracts, blockgroups, towns, regions, pumas, counties, state)
if (drop_counties) {
geos$counties <- NULL
geos[["counties"]] <- NULL
}
# rename counties to cogs
if (!is.null(counties) & use_cogs) {
geos[["cogs"]] <- geos[["counties"]]
geos[["counties"]] <- NULL
}

# basically writing own imap_at
subgeos <- c("neighborhoods", "tracts", "blockgroups", "towns", "pumas")
geos[subgeos] <- purrr::map(subgeos, function(geo_hdr) {
Expand All @@ -17,13 +23,17 @@ geo_printout <- function(neighborhoods, tracts, blockgroups, towns, regions, pum
geo_txt <- NULL
} else if (identical(geo, "all")) {
if (all_counties) {
county_str <- "all counties"
if (use_cogs) {
county_str <- "all COGs"
} else {
county_str <- "all counties"
}
} else {
county_str <- "{counties}"
}
geo_txt <- sprintf("all %s in %s", geo_hdr, county_str)
} else {
if (geo_hdr == "towns") {
if (identical(geo_hdr, "towns")) {
geo_txt <- geo
} else {
geo_txt <- paste(length(unique(geo)), geo_hdr)
Expand All @@ -32,6 +42,7 @@ geo_printout <- function(neighborhoods, tracts, blockgroups, towns, regions, pum
geo_txt
})
geos <- rlang::set_names(geos, stringr::str_to_sentence)
geos <- rlang::set_names(geos, stringr::str_replace, "Cogs", "COGs")

if (msa) {
if (new_england) {
Expand Down
13 changes: 10 additions & 3 deletions tests/testthat/test-batch_csv_dump.R
Original file line number Diff line number Diff line change
Expand Up @@ -31,9 +31,16 @@ test_that("batch_csv_dump prints messages if verbose", {
})

test_that("batch_csv_dump passes arguments to write.csv", {
df <- dummy_df()
df$value[1:3] <- NA_real_
# remember batch_csv_dump uses write.csv, not readr::write_csv!
df <- data.frame(
region = rep(c("A", "B", "C"), each = 2),
value = c(NA_real_, runif(5))
)
dir <- tempdir()
set_na <- batch_csv_dump(df, split_by = region, path = dir, base_name = "set_na", na = "")
no_names <- batch_csv_dump(df, split_by = region, path = dir, base_name = "no_names")

# should have blank at end of line
set_na_read <- stringr::str_remove_all(readLines(file.path(dir, "set_na_A.csv")), '\"')
expect_true(grepl(",$", set_na_read[2]))
expect_false(grepl(",$", set_na_read[3]))
})
3 changes: 0 additions & 3 deletions tests/testthat/test-multi_geo_fetch.R
Original file line number Diff line number Diff line change
@@ -1,6 +1,3 @@
library(cwi)
library(testthat)

# since there's a function that preps but doesn't make API calls, can use that for testing without doing full calls.
test_that("multi_geo_* validates state names and FIPS codes", {
expect_error(multi_test(state = NULL), "Must supply")
Expand Down
10 changes: 10 additions & 0 deletions tests/testthat/test-printouts.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
test_that("geo_printout handles counties vs COGs", {
expect_message(multi_test(year = 2021), "Counties: Fairfield County,")
expect_message(multi_test(year = 2022), "COGs: Capitol COG, ")

expect_message(multi_test(year = 2021), "all towns in all counties")
expect_message(multi_test(year = 2022), "all towns in all COGs")

expect_message(multi_test(year = 2021, counties = "Fairfield County"), "all towns in Fairfield County")
expect_message(multi_test(year = 2022, counties = "Capitol COG"), "all towns in Capitol COG")
})

0 comments on commit 8714ca2

Please sign in to comment.