Skip to content

Commit

Permalink
Changed full_joins to left_joins
Browse files Browse the repository at this point in the history
improves #2
  • Loading branch information
DanChaltiel committed Sep 23, 2024
1 parent 2004f8e commit 5a9c1b9
Show file tree
Hide file tree
Showing 2 changed files with 8 additions and 8 deletions.
8 changes: 4 additions & 4 deletions R/ae_table_grade.R
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@
#' @inherit ae_table_soc seealso
#'
#' @return a crosstable
#' @importFrom dplyr arrange case_match case_when cur_group filter full_join mutate rename_with select summarise
#' @importFrom dplyr arrange case_match case_when cur_group filter left_join mutate rename_with select summarise
#' @importFrom forcats fct_relevel fct_reorder
#' @importFrom rlang check_dots_empty check_installed
#' @importFrom stringr str_remove str_starts str_subset
Expand Down Expand Up @@ -66,7 +66,7 @@ ae_table_grade = function(
mutate(arm=if(is.null(.env$arm)) default_arm else .data$arm)

df = df_enrol %>%
full_join(df_ae, by=tolower(subjid)) %>%
left_join(df_ae, by=tolower(subjid)) %>%
arrange(subjid) %>%
mutate(
grade = fix_grade(grade),
Expand Down Expand Up @@ -228,7 +228,7 @@ ae_plot_grade = function(
#'
#' @return a ggplot
#' @export
#' @importFrom dplyr across any_of arrange count full_join mutate rename_with select
#' @importFrom dplyr across any_of arrange count left_join mutate rename_with select
#' @importFrom forcats fct_infreq fct_rev
#' @importFrom ggplot2 aes element_blank facet_grid geom_col ggplot labs scale_fill_manual theme vars
#' @importFrom rlang check_dots_empty int
Expand Down Expand Up @@ -262,7 +262,7 @@ ae_plot_grade_sum = function(
select(subjid=tolower(subjid), arm=tolower(arm))

df = df_enrol %>%
full_join(df_ae, by=tolower(subjid)) %>%
left_join(df_ae, by=tolower(subjid)) %>%
mutate(grade = fix_grade(grade),
weight = weights[grade] %>% replace_na(0.1)) %>%
arrange(subjid)
Expand Down
8 changes: 4 additions & 4 deletions R/ae_table_soc.R
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@
#' @seealso [ae_table_grade()], [ae_table_soc()], [ae_plot_grade()], [ae_plot_grade_sum()], [butterfly_plot()]
#'
#' @importFrom cli cli_warn
#' @importFrom dplyr across any_of arrange count cur_group filter full_join if_else mutate pull rename select summarise
#' @importFrom dplyr across any_of arrange count cur_group filter left_join if_else mutate pull rename select summarise
#' @importFrom forcats fct_infreq
#' @importFrom glue glue
#' @importFrom purrr iwalk keep map
Expand Down Expand Up @@ -91,7 +91,7 @@ ae_table_soc = function(
mutate(arm_ = if(is.null(.env$arm)) default_arm else .data$arm_)

df = df_enrol %>%
full_join(df_ae, by="subjid_") %>%
left_join(df_ae, by="subjid_") %>%
arrange(subjid_) %>%
mutate(
arm_ = to_snake_case(arm_),
Expand Down Expand Up @@ -263,7 +263,7 @@ as_flextable.ae_table_soc = function(x,
#' @return a crosstable (dataframe)
#' @export
#' @importFrom cli cli_abort cli_warn
#' @importFrom dplyr any_of arrange count filter full_join left_join mutate select summarise
#' @importFrom dplyr any_of arrange count filter left_join mutate select summarise
#' @importFrom forcats fct_reorder
#' @importFrom ggplot2 aes facet_grid geom_blank geom_col ggplot labs scale_x_continuous theme unit vars
#' @importFrom glue glue
Expand Down Expand Up @@ -304,7 +304,7 @@ butterfly_plot = function(
df_enrol = df_enrol %>%
select(subjid_=any_of2(subjid), arm_=any_of2(arm))
df = df_ae %>%
full_join(df_enrol, by="subjid_") %>%
left_join(df_enrol, by="subjid_") %>%
filter(!is.na(soc_)) %>%
arrange(subjid_)

Expand Down

0 comments on commit 5a9c1b9

Please sign in to comment.