Skip to content

Commit

Permalink
Set default na_str to NA_character_
Browse files Browse the repository at this point in the history
  • Loading branch information
edelarua committed Sep 29, 2023
1 parent 3452a84 commit cad02b6
Show file tree
Hide file tree
Showing 67 changed files with 83 additions and 77 deletions.
2 changes: 1 addition & 1 deletion R/abnormal.R
Original file line number Diff line number Diff line change
Expand Up @@ -140,7 +140,7 @@ a_count_abnormal <- make_afun(
#' @export
count_abnormal <- function(lyt,
var,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
table_names = var,
Expand Down
2 changes: 1 addition & 1 deletion R/abnormal_by_marked.R
Original file line number Diff line number Diff line change
Expand Up @@ -196,7 +196,7 @@ a_count_abnormal_by_marked <- make_afun(
#' @export
count_abnormal_by_marked <- function(lyt,
var,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
.stats = NULL,
Expand Down
2 changes: 1 addition & 1 deletion R/abnormal_by_worst_grade.R
Original file line number Diff line number Diff line change
Expand Up @@ -164,7 +164,7 @@ a_count_abnormal_by_worst_grade <- make_afun( # nolint
#' @export
count_abnormal_by_worst_grade <- function(lyt,
var,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
.stats = NULL,
Expand Down
2 changes: 1 addition & 1 deletion R/abnormal_by_worst_grade_worsen.R
Original file line number Diff line number Diff line change
Expand Up @@ -356,7 +356,7 @@ a_count_abnormal_lab_worsen_by_baseline <- make_afun( # nolint
#' @export
count_abnormal_lab_worsen_by_baseline <- function(lyt, # nolint
var,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
table_names = NULL,
Expand Down
4 changes: 2 additions & 2 deletions R/analyze_variables.R
Original file line number Diff line number Diff line change
Expand Up @@ -466,7 +466,7 @@ a_summary <- function(x,
.indent_mods = NULL,
na.rm = TRUE, # nolint
na_level = lifecycle::deprecated(),
na_str = "NA",
na_str = NA_character_,
...) {
if (lifecycle::is_present(na_level)) {
lifecycle::deprecate_warn("0.9.1", "a_summary(na_level)", "a_summary(na_str)")
Expand Down Expand Up @@ -677,7 +677,7 @@ analyze_vars <- function(lyt,
vars,
var_labels = vars,
na_level = lifecycle::deprecated(),
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
na.rm = TRUE, # nolint
Expand Down
4 changes: 2 additions & 2 deletions R/analyze_vars_in_cols.R
Original file line number Diff line number Diff line change
Expand Up @@ -159,7 +159,7 @@ analyze_vars_in_cols <- function(lyt,
cache = FALSE,
.indent_mods = NULL,
na_level = lifecycle::deprecated(),
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
.formats = NULL,
.aligns = NULL) {
Expand All @@ -168,7 +168,7 @@ analyze_vars_in_cols <- function(lyt,
na_str <- na_level
}

checkmate::assert_string(na_str, null.ok = TRUE)
checkmate::assert_string(na_str, na.ok = TRUE, null.ok = TRUE)
checkmate::assert_character(row_labels, null.ok = TRUE)
checkmate::assert_int(.indent_mods, null.ok = TRUE)
checkmate::assert_flag(nested)
Expand Down
2 changes: 1 addition & 1 deletion R/compare_variables.R
Original file line number Diff line number Diff line change
Expand Up @@ -369,7 +369,7 @@ compare_vars <- function(lyt,
vars,
var_labels = vars,
na_level = lifecycle::deprecated(),
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
na.rm = TRUE, # nolint
Expand Down
2 changes: 1 addition & 1 deletion R/count_cumulative.R
Original file line number Diff line number Diff line change
Expand Up @@ -151,7 +151,7 @@ count_cumulative <- function(lyt,
vars,
var_labels = vars,
show_labels = "visible",
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
table_names = vars,
Expand Down
2 changes: 1 addition & 1 deletion R/count_missed_doses.R
Original file line number Diff line number Diff line change
Expand Up @@ -112,7 +112,7 @@ count_missed_doses <- function(lyt,
vars,
var_labels = vars,
show_labels = "visible",
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
table_names = vars,
Expand Down
2 changes: 1 addition & 1 deletion R/count_occurrences.R
Original file line number Diff line number Diff line change
Expand Up @@ -170,7 +170,7 @@ count_occurrences <- function(lyt,
var_labels = vars,
show_labels = "hidden",
riskdiff = FALSE,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
table_names = vars,
Expand Down
4 changes: 2 additions & 2 deletions R/count_occurrences_by_grade.R
Original file line number Diff line number Diff line change
Expand Up @@ -269,7 +269,7 @@ count_occurrences_by_grade <- function(lyt,
var_labels = var,
show_labels = "default",
riskdiff = FALSE,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
table_names = var,
Expand Down Expand Up @@ -342,7 +342,7 @@ count_occurrences_by_grade <- function(lyt,
#' @export
summarize_occurrences_by_grade <- function(lyt,
var,
na_str = "NA",
na_str = NA_character_,
...,
.stats = NULL,
.formats = NULL,
Expand Down
2 changes: 1 addition & 1 deletion R/count_patients_events_in_cols.R
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,7 @@ s_count_patients_and_multiple_events <- function(df, # nolint
summarize_patients_events_in_cols <- function(lyt, # nolint
id = "USUBJID",
filters_list = list(),
na_str = "NA",
na_str = NA_character_,
...,
.stats = c(
"unique",
Expand Down
2 changes: 1 addition & 1 deletion R/count_patients_with_event.R
Original file line number Diff line number Diff line change
Expand Up @@ -145,7 +145,7 @@ a_count_patients_with_event <- make_afun(
count_patients_with_event <- function(lyt,
vars,
riskdiff = FALSE,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
table_names = vars,
Expand Down
2 changes: 1 addition & 1 deletion R/count_patients_with_flags.R
Original file line number Diff line number Diff line change
Expand Up @@ -158,7 +158,7 @@ count_patients_with_flags <- function(lyt,
var_labels = var,
show_labels = "hidden",
riskdiff = FALSE,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
table_names = paste0("tbl_flags_", var),
Expand Down
2 changes: 1 addition & 1 deletion R/count_values.R
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,7 @@ a_count_values <- make_afun(
count_values <- function(lyt,
vars,
values,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
table_names = vars,
Expand Down
2 changes: 1 addition & 1 deletion R/estimate_multinomial_rsp.R
Original file line number Diff line number Diff line change
Expand Up @@ -146,7 +146,7 @@ a_length_proportion <- make_afun(
#' @export
estimate_multinomial_response <- function(lyt,
var,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
show_labels = "hidden",
Expand Down
2 changes: 1 addition & 1 deletion R/estimate_proportion.R
Original file line number Diff line number Diff line change
Expand Up @@ -162,7 +162,7 @@ a_proportion <- make_afun(
#' @export
estimate_proportion <- function(lyt,
vars,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
show_labels = "hidden",
Expand Down
2 changes: 1 addition & 1 deletion R/h_biomarkers_subgroups.R
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@
h_tab_one_biomarker <- function(df,
afuns,
colvars,
na_str = "NA",
na_str = NA_character_,
.indent_mods = 0L) {
lyt <- basic_table()

Expand Down
2 changes: 1 addition & 1 deletion R/incidence_rate.R
Original file line number Diff line number Diff line change
Expand Up @@ -133,7 +133,7 @@ a_incidence_rate <- make_afun(
#' @export
estimate_incidence_rate <- function(lyt,
vars,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
show_labels = "hidden",
Expand Down
2 changes: 1 addition & 1 deletion R/logistic_regression.R
Original file line number Diff line number Diff line change
Expand Up @@ -334,7 +334,7 @@ logistic_regression_cols <- function(lyt,
#' @return A content function.
#'
#' @export
logistic_summary_by_flag <- function(flag_var, na_str = "NA", .indent_mods = NULL) {
logistic_summary_by_flag <- function(flag_var, na_str = NA_character_, .indent_mods = NULL) {
checkmate::assert_string(flag_var)
function(lyt) {
cfun_list <- list(
Expand Down
2 changes: 1 addition & 1 deletion R/odds_ratio.R
Original file line number Diff line number Diff line change
Expand Up @@ -188,7 +188,7 @@ a_odds_ratio <- make_afun(
#' @export
estimate_odds_ratio <- function(lyt,
vars,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
show_labels = "hidden",
Expand Down
2 changes: 1 addition & 1 deletion R/prop_diff.R
Original file line number Diff line number Diff line change
Expand Up @@ -191,7 +191,7 @@ a_proportion_diff <- make_afun(
#' @export
estimate_proportion_diff <- function(lyt,
vars,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
var_labels = vars,
Expand Down
2 changes: 1 addition & 1 deletion R/prop_diff_test.R
Original file line number Diff line number Diff line change
Expand Up @@ -135,7 +135,7 @@ a_test_proportion_diff <- make_afun(
#' @export
test_proportion_diff <- function(lyt,
vars,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
var_labels = vars,
Expand Down
2 changes: 1 addition & 1 deletion R/summarize_ancova.R
Original file line number Diff line number Diff line change
Expand Up @@ -244,7 +244,7 @@ a_ancova <- make_afun(
summarize_ancova <- function(lyt,
vars,
var_labels,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
show_labels = "visible",
Expand Down
2 changes: 1 addition & 1 deletion R/summarize_change.R
Original file line number Diff line number Diff line change
Expand Up @@ -120,7 +120,7 @@ a_change_from_baseline <- make_afun(
#' @export
summarize_change <- function(lyt,
vars,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
table_names = vars,
Expand Down
2 changes: 1 addition & 1 deletion R/summarize_colvars.R
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,7 @@
summarize_colvars <- function(lyt,
...,
na_level = lifecycle::deprecated(),
na_str = "NA",
na_str = NA_character_,
.stats = c("n", "mean_sd", "median", "range", "count_fraction"),
.formats = NULL,
.labels = NULL,
Expand Down
2 changes: 1 addition & 1 deletion R/summarize_glm_count.R
Original file line number Diff line number Diff line change
Expand Up @@ -399,7 +399,7 @@ a_glm_count <- make_afun(
summarize_glm_count <- function(lyt,
vars,
var_labels,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
show_labels = "visible",
Expand Down
4 changes: 2 additions & 2 deletions R/summarize_num_patients.R
Original file line number Diff line number Diff line change
Expand Up @@ -137,7 +137,7 @@ c_num_patients <- make_afun(
#' @export
summarize_num_patients <- function(lyt,
var,
na_str = "NA",
na_str = NA_character_,
.stats = NULL,
.formats = NULL,
.labels = c(
Expand Down Expand Up @@ -219,7 +219,7 @@ summarize_num_patients <- function(lyt,
#' @export
analyze_num_patients <- function(lyt,
vars,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
.stats = NULL,
.formats = NULL,
Expand Down
2 changes: 1 addition & 1 deletion R/summarize_patients_exposure_in_cols.R
Original file line number Diff line number Diff line change
Expand Up @@ -176,7 +176,7 @@ a_count_patients_sum_exposure <- function(df,
#' @export
summarize_patients_exposure_in_cols <- function(lyt, # nolint
var,
na_str = "NA",
na_str = NA_character_,
...,
.stats = c("n_patients", "sum_exposure"),
.labels = c(n_patients = "Patients", sum_exposure = "Person time"),
Expand Down
2 changes: 1 addition & 1 deletion R/survival_coxph_pairwise.R
Original file line number Diff line number Diff line change
Expand Up @@ -165,7 +165,7 @@ a_coxph_pairwise <- make_afun(
#' @export
coxph_pairwise <- function(lyt,
vars,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
var_labels = "CoxPH",
Expand Down
2 changes: 1 addition & 1 deletion R/survival_duration_subgroups.R
Original file line number Diff line number Diff line change
Expand Up @@ -244,7 +244,7 @@ tabulate_survival_subgroups <- function(lyt,
df,
vars = c("n_tot_events", "n_events", "median", "hr", "ci"),
time_unit = NULL,
na_str = "NA") {
na_str = NA_character_) {
conf_level <- df$hr$conf_level[1]
method <- df$hr$pval_label[1]

Expand Down
2 changes: 1 addition & 1 deletion R/survival_time.R
Original file line number Diff line number Diff line change
Expand Up @@ -123,7 +123,7 @@ a_surv_time <- make_afun(
#' @export
surv_time <- function(lyt,
vars,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
var_labels = "Time to Event",
Expand Down
2 changes: 1 addition & 1 deletion R/survival_timepoint.R
Original file line number Diff line number Diff line change
Expand Up @@ -232,7 +232,7 @@ a_surv_timepoint_diff <- make_afun(
#' @export
surv_timepoint <- function(lyt,
vars,
na_str = "NA",
na_str = NA_character_,
nested = TRUE,
...,
table_names_suffix = "",
Expand Down
2 changes: 1 addition & 1 deletion man/abnormal.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/abnormal_by_marked.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/abnormal_by_worst_grade.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/abnormal_by_worst_grade_worsen.Rd

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

4 changes: 2 additions & 2 deletions man/analyze_variables.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/analyze_vars_in_cols.Rd

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

Loading

0 comments on commit cad02b6

Please sign in to comment.