Skip to content

Commit 0c8144e

Browse files
committed
lint: increase lintr happiness
1 parent 68c027b commit 0c8144e

31 files changed

+443
-284
lines changed

R/archive.R

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,10 @@
11
# We use special features of data.table's `[`. The data.table package has a
22
# compatibility feature that disables some/all of these features if it thinks we
33
# might expect `data.frame`-compatible behavior instead. We can signal that we
4-
# want the special behavior via `.datatable.aware = TRUE` or by importing any
4+
# want the special behavior via `.datatable_aware = TRUE` or by importing any
55
# `data.table` package member. Do both to prevent surprises if we decide to use
66
# `data.table::` everywhere and not importing things.
7-
.datatable.aware <- TRUE
7+
.datatable_aware <- TRUE
88

99
#' Validate a version bound arg
1010
#'
@@ -79,6 +79,7 @@ max_version_with_row_in <- function(x) {
7979
version_bound <- max(version_col)
8080
}
8181
}
82+
version_bound
8283
}
8384

8485
#' Get the next possible value greater than `x` of the same type
@@ -343,7 +344,7 @@ epi_archive <-
343344
# then the call to as.data.table() will fail to set keys, so we
344345
# need to check this, then do it manually if needed
345346
key_vars <- c("geo_value", "time_value", other_keys, "version")
346-
DT <- as.data.table(x, key = key_vars)
347+
DT <- as.data.table(x, key = key_vars) # nolint: object_name_linter
347348
if (!identical(key_vars, key(DT))) setkeyv(DT, cols = key_vars)
348349

349350
maybe_first_duplicate_key_row_index <- anyDuplicated(DT, by = key(DT))
@@ -381,7 +382,7 @@ epi_archive <-
381382
# Runs compactify on data frame
382383
if (is.null(compactify) || compactify == TRUE) {
383384
elim <- keep_locf(DT)
384-
DT <- rm_locf(DT)
385+
DT <- rm_locf(DT) # nolint: object_name_linter
385386
} else {
386387
# Create empty data frame for nrow(elim) to be 0
387388
elim <- tibble::tibble()
@@ -543,7 +544,7 @@ epi_archive <-
543544
validate_version_bound(fill_versions_end, self$DT, na_ok = FALSE)
544545
how <- arg_match(how)
545546
if (self$versions_end < fill_versions_end) {
546-
new_DT <- switch(how,
547+
new_DT <- switch(how, # nolint: object_name_linter
547548
"na" = {
548549
# old DT + a version consisting of all NA observations
549550
# immediately after the last currently/actually-observed
@@ -567,7 +568,7 @@ epi_archive <-
567568
if (identical(address(self$DT), address(nonversion_key_vals_ever_recorded))) {
568569
nonversion_key_vals_ever_recorded <- copy(nonversion_key_vals_ever_recorded)
569570
}
570-
next_version_DT <- nonversion_key_vals_ever_recorded[
571+
next_version_DT <- nonversion_key_vals_ever_recorded[ # nolint: object_name_linter
571572
, version := next_version_tag
572573
][
573574
# this makes the class of these columns logical (`NA` is a

R/autoplot.R

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -112,14 +112,14 @@ autoplot.epi_df <- function(
112112
dplyr::mutate(
113113
.colours = switch(.color_by,
114114
all_keys = interaction(!!!all_keys, sep = "/"),
115-
geo_value = geo_value,
115+
geo_value = .data$geo_value,
116116
other_keys = interaction(!!!other_keys, sep = "/"),
117117
all = interaction(!!!all_avail, sep = "/"),
118118
NULL
119119
),
120120
.facets = switch(.facet_by,
121121
all_keys = interaction(!!!all_keys, sep = "/"),
122-
geo_value = as.factor(geo_value),
122+
geo_value = as.factor(.data$geo_value),
123123
other_keys = interaction(!!!other_keys, sep = "/"),
124124
all = interaction(!!!all_avail, sep = "/"),
125125
NULL
@@ -130,10 +130,10 @@ autoplot.epi_df <- function(
130130
n_facets <- nlevels(object$.facets)
131131
if (n_facets > .max_facets) {
132132
top_n <- levels(as.factor(object$.facets))[seq_len(.max_facets)]
133-
object <- dplyr::filter(object, .facets %in% top_n) %>%
134-
dplyr::mutate(.facets = droplevels(.facets))
133+
object <- dplyr::filter(object, .data$.facets %in% top_n) %>%
134+
dplyr::mutate(.facets = droplevels(.data$.facets))
135135
if (".colours" %in% names(object)) {
136-
object <- dplyr::mutate(object, .colours = droplevels(.colours))
136+
object <- dplyr::mutate(object, .colours = droplevels(.data$.colours))
137137
}
138138
}
139139
}

R/correlation.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -75,7 +75,7 @@
7575
#' cor_by = geo_value,
7676
#' dt1 = -2
7777
#' )
78-
epi_cor <- function(x, var1, var2, dt1 = 0, dt2 = 0, shift_by = geo_value,
78+
epi_cor <- function(x, var1, var2, dt1 = 0, dt2 = 0, shift_by = geo_value, # nolint: object_usage_linter
7979
cor_by = geo_value, use = "na.or.complete",
8080
method = c("pearson", "kendall", "spearman")) {
8181
assert_class(x, "epi_df")

R/data.R

Lines changed: 74 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -20,12 +20,15 @@
2020
#' COVID-19 cases, daily}
2121
#' }
2222
#' @source This object contains a modified part of the
23-
#' \href{https://github.com/CSSEGISandData/COVID-19}{COVID-19 Data Repository by the Center for Systems Science and Engineering (CSSE) at Johns Hopkins University}
24-
#' as \href{https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html}{republished in the COVIDcast Epidata API}.
25-
#' This data set is licensed under the terms of the
26-
#' \href{https://creativecommons.org/licenses/by/4.0/}{Creative Commons Attribution 4.0 International license}
27-
#' by the Johns Hopkins University on behalf of its Center for Systems Science
28-
#' in Engineering. Copyright Johns Hopkins University 2020.
23+
#' \href{https://github.com/CSSEGISandData/COVID-19}{COVID-19 Data Repository
24+
#' by the Center for Systems Science and Engineering (CSSE) at Johns Hopkins
25+
#' University} as
26+
#' \href{https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html}{republished
27+
#' in the COVIDcast Epidata API}. This data set is licensed under the terms of
28+
#' the \href{https://creativecommons.org/licenses/by/4.0/}{Creative Commons
29+
#' Attribution 4.0 International license} by the Johns Hopkins University on
30+
#' behalf of its Center for Systems Science in Engineering. Copyright Johns
31+
#' Hopkins University 2020.
2932
#'
3033
#' Modifications:
3134
#' * \href{https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html}{From
@@ -54,19 +57,34 @@
5457
#' \item{geo_value}{the geographic value associated with each row of measurements.}
5558
#' \item{time_value}{the time value associated with each row of measurements.}
5659
#' \item{version}{the time value specifying the version for each row of measurements. }
57-
#' \item{percent_cli}{percentage of doctor’s visits with CLI (COVID-like illness) computed from medical insurance claims}
58-
#' \item{case_rate_7d_av}{7-day average signal of number of new confirmed deaths due to COVID-19 per 100,000 population, daily}
60+
#' \item{percent_cli}{percentage of doctor’s visits with CLI (COVID-like
61+
#' illness) computed from medical insurance claims}
62+
#' \item{case_rate_7d_av}{7-day average signal of number of new confirmed
63+
#' deaths due to COVID-19 per 100,000 population, daily}
5964
#' }
6065
#' @source
61-
#' This object contains a modified part of the \href{https://github.com/CSSEGISandData/COVID-19}{COVID-19 Data Repository by the Center for Systems Science and Engineering (CSSE) at Johns Hopkins University} as \href{https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html}{republished in the COVIDcast Epidata API}. This data set is licensed under the terms of the
62-
#' \href{https://creativecommons.org/licenses/by/4.0/}{Creative Commons Attribution 4.0 International license}
63-
#' by Johns Hopkins University on behalf of its Center for Systems Science in Engineering.
64-
#' Copyright Johns Hopkins University 2020.
66+
#' This object contains a modified part of the
67+
#' \href{https://github.com/CSSEGISandData/COVID-19}{COVID-19 Data Repository by
68+
#' the Center for Systems Science and Engineering (CSSE) at Johns Hopkins
69+
#' University} as
70+
#' \href{https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html}{republished
71+
#' in the COVIDcast Epidata API}. This data set is licensed under the terms of
72+
#' the \href{https://creativecommons.org/licenses/by/4.0/}{Creative Commons
73+
#' Attribution 4.0 International license} by Johns Hopkins University on behalf
74+
#' of its Center for Systems Science in Engineering. Copyright Johns Hopkins
75+
#' University 2020.
6576
#'
6677
#' Modifications:
67-
#' * \href{https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/doctor-visits.html}{From the COVIDcast Doctor Visits API}: The signal `percent_cli` is taken directly from the API without changes.
68-
#' * \href{https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html}{From the COVIDcast Epidata API}: `case_rate_7d_av` signal was computed by Delphi from the original JHU-CSSE data by calculating moving averages of the preceding 7 days, so the signal for June 7 is the average of the underlying data for June 1 through 7, inclusive.
69-
#' * Furthermore, the data is a subset of the full dataset, the signal names slightly altered, and formatted into a tibble.
78+
#' * \href{https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/doctor-visits.html}{From
79+
#' the COVIDcast Doctor Visits API}: The signal `percent_cli` is taken
80+
#' directly from the API without changes.
81+
#' * \href{https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html}{From
82+
#' the COVIDcast Epidata API}: `case_rate_7d_av` signal was computed by Delphi
83+
#' from the original JHU-CSSE data by calculating moving averages of the
84+
#' preceding 7 days, so the signal for June 7 is the average of the underlying
85+
#' data for June 1 through 7, inclusive.
86+
#' * Furthermore, the data is a subset of the full dataset, the signal names
87+
#' slightly altered, and formatted into a tibble.
7088
#'
7189
#' @export
7290
"archive_cases_dv_subset"
@@ -128,19 +146,19 @@ some_package_is_being_unregistered <- function(parent_n = 0L) {
128146
#'
129147
#' @noRd
130148
delayed_assign_with_unregister_awareness <- function(x, value,
131-
eval.env = rlang::caller_env(),
132-
assign.env = rlang::caller_env()) {
133-
value_quosure <- rlang::as_quosure(rlang::enexpr(value), eval.env)
149+
eval_env = rlang::caller_env(),
150+
assign_env = rlang::caller_env()) {
151+
value_quosure <- rlang::as_quosure(rlang::enexpr(value), eval_env)
134152
this_env <- environment()
135-
delayedAssign(x, eval.env = this_env, assign.env = assign.env, value = {
153+
delayedAssign(x, eval.env = this_env, assign.env = assign_env, value = {
136154
if (some_package_is_being_unregistered()) {
137155
withCallingHandlers(
138156
# `rlang::eval_tidy(value_quosure)` is shorter and would sort of work,
139157
# but doesn't give the same `ls`, `rm`, and top-level `<-` behavior as
140158
# we'd have with `delayedAssign`; it doesn't seem to actually evaluate
141159
# quosure's expr in the quosure's env. Using `rlang::eval_bare` instead
142160
# seems to do the trick. (We also could have just used a `value_expr`
143-
# and `eval.env` together rather than introducing `value_quosure` at
161+
# and `eval_env` together rather than introducing `value_quosure` at
144162
# all.)
145163
rlang::eval_bare(rlang::quo_get_expr(value_quosure), rlang::quo_get_env(value_quosure)),
146164
error = function(err) {
@@ -193,7 +211,10 @@ delayed_assign_with_unregister_awareness <- function(x, value,
193211
# binding may have been created with the same name as the package promise, and
194212
# this binding will stick around even when the package is reloaded, and will
195213
# need to be `rm`-d to easily access the refreshed package promise.
196-
delayed_assign_with_unregister_awareness("archive_cases_dv_subset", as_epi_archive(archive_cases_dv_subset_dt, compactify = FALSE))
214+
delayed_assign_with_unregister_awareness(
215+
"archive_cases_dv_subset",
216+
as_epi_archive(archive_cases_dv_subset_dt, compactify = FALSE)
217+
)
197218

198219
#' Subset of JHU daily cases from California and Florida
199220
#'
@@ -210,15 +231,24 @@ delayed_assign_with_unregister_awareness("archive_cases_dv_subset", as_epi_archi
210231
#' \item{time_value}{the time value associated with each row of measurements.}
211232
#' \item{cases}{Number of new confirmed COVID-19 cases, daily}
212233
#' }
213-
#' @source This object contains a modified part of the \href{https://github.com/CSSEGISandData/COVID-19}{COVID-19 Data Repository by the Center for Systems Science and Engineering (CSSE) at Johns Hopkins University} as \href{https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html}{republished in the COVIDcast Epidata API}. This data set is licensed under the terms of the
214-
#' \href{https://creativecommons.org/licenses/by/4.0/}{Creative Commons Attribution 4.0 International license}
215-
#' by the Johns Hopkins University on behalf of its Center for Systems Science in Engineering.
216-
#' Copyright Johns Hopkins University 2020.
234+
#' @source This object contains a modified part of the
235+
#' \href{https://github.com/CSSEGISandData/COVID-19}{COVID-19 Data Repository by
236+
#' the Center for Systems Science and Engineering (CSSE) at Johns Hopkins
237+
#' University} as
238+
#' \href{https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html}{republished
239+
#' in the COVIDcast Epidata API}. This data set is licensed under the terms of
240+
#' the \href{https://creativecommons.org/licenses/by/4.0/}{Creative Commons
241+
#' Attribution 4.0 International license} by the Johns Hopkins University on
242+
#' behalf of its Center for Systems Science in Engineering. Copyright Johns
243+
#' Hopkins University 2020.
217244
#'
218245
#' Modifications:
219-
#' * \href{https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html}{From the COVIDcast Epidata API}:
220-
#' These signals are taken directly from the JHU CSSE \href{https://github.com/CSSEGISandData/COVID-19}{COVID-19 GitHub repository} without changes.
221-
#' * Furthermore, the data has been limited to a very small number of rows, the signal names slightly altered, and formatted into a tibble.
246+
#' * \href{https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html}{From
247+
#' the COVIDcast Epidata API}: These signals are taken directly from the JHU
248+
#' CSSE \href{https://github.com/CSSEGISandData/COVID-19}{COVID-19 GitHub
249+
#' repository} without changes.
250+
#' * Furthermore, the data has been limited to a very small number of rows, the
251+
#' signal names slightly altered, and formatted into a tibble.
222252
"incidence_num_outlier_example"
223253

224254
#' Subset of JHU daily cases from counties in Massachusetts and Vermont
@@ -237,12 +267,25 @@ delayed_assign_with_unregister_awareness("archive_cases_dv_subset", as_epi_archi
237267
#' \item{county_name}{the name of the county}
238268
#' \item{state_name}{the full name of the state}
239269
#' }
240-
#' @source This object contains a modified part of the \href{https://github.com/CSSEGISandData/COVID-19}{COVID-19 Data Repository by the Center for Systems Science and Engineering (CSSE) at Johns Hopkins University} as \href{https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html}{republished in the COVIDcast Epidata API}. This data set is licensed under the terms of the
270+
#' @source This object contains a modified part of the
271+
#' \href{https://github.com/CSSEGISandData/COVID-19}{COVID-19 Data Repository by
272+
#' the Center for Systems Science and Engineering (CSSE) at Johns Hopkins
273+
#' University} as
274+
#' \href{https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html}{republished
275+
#' in the COVIDcast Epidata API}. This data set is licensed under the terms of
276+
#' the
241277
#' \href{https://creativecommons.org/licenses/by/4.0/}{Creative Commons Attribution 4.0 International license}
242278
#' by the Johns Hopkins University on behalf of its Center for Systems Science in Engineering.
243279
#' Copyright Johns Hopkins University 2020.
244280
#'
245281
#' Modifications:
246-
#' * \href{https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html}{From the COVIDcast Epidata API}: These signals are taken directly from the JHU CSSE \href{https://github.com/CSSEGISandData/COVID-19}{COVID-19 GitHub repository} without changes. The 7-day average signals are computed by Delphi by calculating moving averages of the preceding 7 days, so the signal for June 7 is the average of the underlying data for June 1 through 7, inclusive.
247-
#' * Furthermore, the data has been limited to a very small number of rows, the signal names slightly altered, and formatted into a tibble.
282+
#' * \href{https://cmu-delphi.github.io/delphi-epidata/api/covidcast-signals/jhu-csse.html}{From
283+
#' the COVIDcast Epidata API}: These signals are taken directly from the JHU
284+
#' CSSE \href{https://github.com/CSSEGISandData/COVID-19}{COVID-19 GitHub
285+
#' repository} without changes. The 7-day average signals are computed by
286+
#' Delphi by calculating moving averages of the preceding 7 days, so the
287+
#' signal for June 7 is the average of the underlying data for June 1 through
288+
#' 7, inclusive.
289+
#' * Furthermore, the data has been limited to a very small number of rows, the
290+
#' signal names slightly altered, and formatted into a tibble.
248291
"jhu_csse_county_level_subset"

R/epi_df.R

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -134,20 +134,20 @@ new_epi_df <- function(x = tibble::tibble(), geo_type, time_type, as_of,
134134
# If as_of is missing, then try to guess it
135135
if (missing(as_of)) {
136136
# First check the metadata for an as_of field
137-
if ("metadata" %in% names(attributes(x)) &&
138-
"as_of" %in% names(attributes(x)$metadata)) {
137+
if (
138+
"metadata" %in% names(attributes(x)) &&
139+
"as_of" %in% names(attributes(x)$metadata)
140+
) {
139141
as_of <- attributes(x)$metadata$as_of
140-
}
141-
142-
# Next check for as_of, issue, or version columns
143-
else if ("as_of" %in% names(x)) {
142+
} else if ("as_of" %in% names(x)) {
143+
# Next check for as_of, issue, or version columns
144144
as_of <- max(x$as_of)
145145
} else if ("issue" %in% names(x)) {
146146
as_of <- max(x$issue)
147147
} else if ("version" %in% names(x)) {
148148
as_of <- max(x$version)
149-
} # If we got here then we failed
150-
else {
149+
} else {
150+
# If we got here then we failed
151151
as_of <- Sys.time()
152152
} # Use the current day-time
153153
}

0 commit comments

Comments
 (0)