Skip to content

Commit

Permalink
Don't call fix_cogs within functions
Browse files Browse the repository at this point in the history
  • Loading branch information
camille-s committed Dec 8, 2023
1 parent bb88663 commit 4462c81
Show file tree
Hide file tree
Showing 3 changed files with 8 additions and 7 deletions.
10 changes: 7 additions & 3 deletions R/validate_geos.R
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,10 @@ county_x_state <- function(st, counties) {
}
out <- dplyr::select(out, state = state_name, county_geoid, county)
# TODO: hopefully calling fix_cogs works with census api
out$county <- fix_cogs(out$county)
if (st == "09") {
out$county <- ifelse(grepl("^091", out$county_geoid), paste(out$county, "COG"), out$county) # if cog, paste COG on name
}
# out$county <- fix_cogs(out$county)
out
}

Expand Down Expand Up @@ -58,7 +61,7 @@ get_county_fips <- function(state, counties, use_cogs) {
!grepl("\\d", counties) & !grepl(" County$", counties) & !use_cogs ~ paste(counties, "County"),
TRUE ~ counties
)
counties <- fix_cogs(counties)
# counties <- fix_cogs(counties)

cty_from_name <- xw[xw$county %in% counties, ]
cty_from_fips <- xw[xw$county_geoid %in% counties, ]
Expand All @@ -80,7 +83,8 @@ get_county_fips <- function(state, counties, use_cogs) {
}
}
if (use_cogs) {
cli::cli_inform(c("i" = "Note that starting with the 2022 release, ACS data uses COGs instead of counties."))
cli::cli_inform(c("i" = "Note that starting with the 2022 release, ACS data uses COGs instead of counties."),
.frequency = "once", .frequency_id = "cog")
}
counties
}
Expand Down
3 changes: 0 additions & 3 deletions tests/testthat/test-multi_geo_fetch.R
Original file line number Diff line number Diff line change
Expand Up @@ -102,6 +102,3 @@ test_that("multi_geo_* handles survey codes", {
expect_error(multi_test("decennial", "P1", 2020, dataset = "sf1"))
})

test_that("multi_geo_acs gives notice about COGs", {
expect_message(multi_test(year = 2022), "COGs instead of counties")
})
2 changes: 1 addition & 1 deletion tests/testthat/test-validate_geos.R
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,6 @@ test_that("get_county_fips matches & returns FIPS codes", {
expect_equal(get_county_fips("09", c("09009", "09001", "Fairfield"), FALSE), correct)

correct_cog <- c("09120", "09190")
expect_equal(get_county_fips("09", c("Western Connecticut", "Greater Bridgeport"), TRUE), correct_cog)
expect_equal(get_county_fips("09", c("Western Connecticut COG", "Greater Bridgeport COG"), TRUE), correct_cog)
expect_equal(get_county_fips("09", c("120", "190"), TRUE), correct_cog)
})
Expand All @@ -37,3 +36,4 @@ test_that("get_state_fips matches & returns FIPS codes", {
expect_equal(get_state_fips("CT"), correct)
expect_equal(get_state_fips("Connecticut"), correct)
})

0 comments on commit 4462c81

Please sign in to comment.