From c4a3de19724f7cd14f436b806410fb0dbe014744 Mon Sep 17 00:00:00 2001 From: "Baer, Travis" Date: Fri, 1 Apr 2022 13:53:52 -0400 Subject: [PATCH 01/10] addresses #578 - use dplyr::select insstead of select_ --- R/ggsurvplot_combine.R | 7 +++---- tests/testthat/test-ggsurvplot_combine.R | 18 ++++++++++++++++++ 2 files changed, 21 insertions(+), 4 deletions(-) create mode 100644 tests/testthat/test-ggsurvplot_combine.R diff --git a/R/ggsurvplot_combine.R b/R/ggsurvplot_combine.R index 1ec7717..b8af1cf 100644 --- a/R/ggsurvplot_combine.R +++ b/R/ggsurvplot_combine.R @@ -114,7 +114,7 @@ ggsurvplot_combine <- function(fit, data, all.levels <- c(all.levels, .levels(ss$strata)) # convert strata into character before binding # avoid this warning: Unequal factor levels: coercing to character - grouped.d$survsummary <- map(grouped.d$survsummary, + grouped.d$survsummary <- purrr::map(grouped.d$survsummary, function(x){ x$strata <- as.character(x$strata) x @@ -161,9 +161,8 @@ ggsurvplot_combine <- function(fit, data, survtable$strata <- paste(fitname, "::", survtable$strata, sep = "") %>% factor(levels = strata.levels) survtable %>% - dplyr::select_( .dots = c("strata", "time", "n.risk", "pct.risk", - "n.event", "cum.n.event", "n.censor", - "cum.n.censor", "strata_size")) + dplyr::select(strata, time, n.risk, pct.risk, n.event, cum.n.event, + n.censor, cum.n.censor, strata_size))) } grouped.d <- grouped.d %>% diff --git a/tests/testthat/test-ggsurvplot_combine.R b/tests/testthat/test-ggsurvplot_combine.R new file mode 100644 index 0000000..f0814e8 --- /dev/null +++ b/tests/testthat/test-ggsurvplot_combine.R @@ -0,0 +1,18 @@ +context("test-ggsurvplot_combine") + +library(dplyr) +library(survival) +data("lung") +start_time <- 250 +fit1 <- survfit(Surv(time, status) ~ sex, data = lung) +fit2 <- survfit(Surv(time, status) ~ sex, data = lung, start.time=start_time) + +test_that("survplot_combine plots successfully into 4 lines; second 2 fits have only (0,1) before start_time", { + p <- ggsurvplot_combine(list( + original=fit1, conditional=fit2 + ), data = lung) + .build <- ggplot_build(p$plot) + .build_data <- .build$data[[1]] + expect_equal(length(unique(.build_data[['group']])), 4) + expect_lt(nrow(.build_data[(.build_data[['group']] >= 3) & (.build_data[['x']] < start_time), ]), 3) +}) From 359c0c0812133be80a119ec05fe740f0a2b03448 Mon Sep 17 00:00:00 2001 From: Baer Date: Tue, 5 Apr 2022 18:53:11 -0400 Subject: [PATCH 02/10] #578 update tests and replace a few select and as.tibbles --- R/ggsurvplot_combine.R | 6 +++--- R/ggsurvplot_facet.R | 4 ++-- tests/testthat/test-ggsurvplot_combine.R | 17 ++++++++++------- tests/testthat/test-ggsurvplot_facet.R | 21 +++++++++++++++++++++ 4 files changed, 36 insertions(+), 12 deletions(-) create mode 100644 tests/testthat/test-ggsurvplot_facet.R diff --git a/R/ggsurvplot_combine.R b/R/ggsurvplot_combine.R index b8af1cf..d634022 100644 --- a/R/ggsurvplot_combine.R +++ b/R/ggsurvplot_combine.R @@ -162,7 +162,7 @@ ggsurvplot_combine <- function(fit, data, factor(levels = strata.levels) survtable %>% dplyr::select(strata, time, n.risk, pct.risk, n.event, cum.n.event, - n.censor, cum.n.censor, strata_size))) + n.censor, cum.n.censor, strata_size) } grouped.d <- grouped.d %>% @@ -198,8 +198,8 @@ ggsurvplot_combine <- function(fit, data, #:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::: if(keep.data){ - res$data.survplot <- tibble::as.tibble(all.survsummary) - res$data.survtable <- tibble::as.tibble(all.survtable) + res$data.survplot <- tibble::as_tibble(all.survsummary) + res$data.survtable <- tibble::as_tibble(all.survtable) } diff --git a/R/ggsurvplot_facet.R b/R/ggsurvplot_facet.R index e1f0f0d..4e00f82 100644 --- a/R/ggsurvplot_facet.R +++ b/R/ggsurvplot_facet.R @@ -179,10 +179,10 @@ ggsurvplot_facet <- function(fit, data, facet.by, pvalue <- surv_pvalue(grouped.d$fit, grouped.d$data, pval.coord = pval.coord, pval.method.coord = pval.method.coord,...) %>% dplyr::bind_rows() %>% - tibble::as.tibble() + tibble::as_tibble() # Select the grouping variable columns and cbind the corresponding pvalue pvals.df <- grouped.d %>% - dplyr::select_( .dots = facet.by) %>% + dplyr::select(!!!syms(facet.by)) %>% dplyr::bind_cols(pvalue) pval.x <- pval.y <- pval.txt <- method.x <- method.y <- method <- NULL p <- p + diff --git a/tests/testthat/test-ggsurvplot_combine.R b/tests/testthat/test-ggsurvplot_combine.R index f0814e8..09e7c11 100644 --- a/tests/testthat/test-ggsurvplot_combine.R +++ b/tests/testthat/test-ggsurvplot_combine.R @@ -1,11 +1,6 @@ -context("test-ggsurvplot_combine") - -library(dplyr) -library(survival) -data("lung") start_time <- 250 fit1 <- survfit(Surv(time, status) ~ sex, data = lung) -fit2 <- survfit(Surv(time, status) ~ sex, data = lung, start.time=start_time) +fit2 <- survfit(Surv(time, status) ~ sex, data = lung, start.time = start_time) test_that("survplot_combine plots successfully into 4 lines; second 2 fits have only (0,1) before start_time", { p <- ggsurvplot_combine(list( @@ -14,5 +9,13 @@ test_that("survplot_combine plots successfully into 4 lines; second 2 fits have .build <- ggplot_build(p$plot) .build_data <- .build$data[[1]] expect_equal(length(unique(.build_data[['group']])), 4) - expect_lt(nrow(.build_data[(.build_data[['group']] >= 3) & (.build_data[['x']] < start_time), ]), 3) + expect_lt(nrow(.build_data[(.build_data[['group']] >= 3) & + (.build_data[['x']] < start_time), ]), 3) +}) + +test_that("survplot_combine includes dataframes when keep.data==TRUE", { + p <- ggsurvplot_combine(list( + original=fit1, conditional=fit2 + ), data = lung, keep.data = TRUE) + expect_equal(length(names(p)), 3) }) diff --git a/tests/testthat/test-ggsurvplot_facet.R b/tests/testthat/test-ggsurvplot_facet.R new file mode 100644 index 0000000..dd88862 --- /dev/null +++ b/tests/testthat/test-ggsurvplot_facet.R @@ -0,0 +1,21 @@ +test_that("ggsurvplot_facet creates the correct quanitty of subplots", { + fit <- survfit(Surv(time, status) ~ sex, data=kidney) + p <- ggsurvplot_facet(fit, kidney, facet.by='disease') + .build <- ggplot_build(p) + expect_equal(nrow(.build$data[[2]]), + length(unique(kidney[['disease']]))) + + fit <- survfit(Surv(time, status) ~ disease, data=kidney) + p <- ggsurvplot_facet(fit, kidney, facet.by='sex') + .build <- ggplot_build(p) + expect_equal(nrow(.build$data[[2]]), + length(unique(kidney[['sex']]))) +}) + +test_that("ggsurvplot_facet calculates pvalue for each facet", { + fit <- survfit(Surv(time, status) ~ sex, data=kidney) + p <- ggsurvplot_facet(fit, kidney, facet.by='disease', pval = TRUE) + .build <- ggplot_build(p) + expect_equal(nrow(.build$plot$layer[[4]][['data']]), + length(unique(kidney[['disease']]))) +}) From be678e68213d4c54d19468125f5b8b530c9ab9db Mon Sep 17 00:00:00 2001 From: Travis Baer Date: Tue, 5 Apr 2022 18:57:42 -0400 Subject: [PATCH 03/10] #509 replace select_ with select in surv_median --- R/surv_median.R | 2 +- tests/testthat/test-surv_median.R | 6 ++++++ 2 files changed, 7 insertions(+), 1 deletion(-) create mode 100644 tests/testthat/test-surv_median.R diff --git a/R/surv_median.R b/R/surv_median.R index 6ec63f6..afc16e0 100644 --- a/R/surv_median.R +++ b/R/surv_median.R @@ -59,7 +59,7 @@ surv_median <- function(fit, combine = FALSE){ .table$strata <- rownames(.table) .table <- .table %>% - dplyr::select_(.dots = c("strata", "median", "`0.95LCL`", "`0.95UCL`")) + dplyr::select(strata, median, `0.95LCL`, `0.95UCL`) colnames(.table) <- c("strata", "median", "lower", "upper") rownames(.table) <- NULL .table diff --git a/tests/testthat/test-surv_median.R b/tests/testthat/test-surv_median.R new file mode 100644 index 0000000..560c310 --- /dev/null +++ b/tests/testthat/test-surv_median.R @@ -0,0 +1,6 @@ +test_that("surv_median calculates medians", { + df_medians <- surv_median(survfit(Surv(time, status) ~ sex, + data=lung)) + expect_equal(df_medians[['median']], c(270,426)) + expect_lt(df_medians[['lower']][2], 426) +}) From b35b1cbab1a2bdf7dcf7c90275078d6b76b293fd Mon Sep 17 00:00:00 2001 From: Travis Baer Date: Fri, 8 Apr 2022 18:29:06 -0400 Subject: [PATCH 04/10] #577 replace deprecated function with superceded function --- R/ggcoxdiagnostics.R | 6 +++--- tests/testthat/setup-load_data.R | 2 ++ tests/testthat/test-ggcoxdiagnostics.R | 16 ++++++++++++++++ 3 files changed, 21 insertions(+), 3 deletions(-) create mode 100644 tests/testthat/setup-load_data.R create mode 100644 tests/testthat/test-ggcoxdiagnostics.R diff --git a/R/ggcoxdiagnostics.R b/R/ggcoxdiagnostics.R index 986ebc1..62d2c35 100644 --- a/R/ggcoxdiagnostics.R +++ b/R/ggcoxdiagnostics.R @@ -99,9 +99,9 @@ ggcoxdiagnostics <- function (fit, else col_names <- names(stats::coef(fit)) colnames(res) <- col_names res$xval <- xval - data2plot <- tidyr::gather_(res, - key_col = "covariate", value_col = "res", - gather_col = col_names) + data2plot <- tidyr::gather(res, + key = "covariate", value = "res", + col_names) gplot <- ggplot(aes(xval, res), data = data2plot) + geom_point(col = point.col, shape = point.shape, diff --git a/tests/testthat/setup-load_data.R b/tests/testthat/setup-load_data.R new file mode 100644 index 0000000..175865c --- /dev/null +++ b/tests/testthat/setup-load_data.R @@ -0,0 +1,2 @@ +library(survival) +data('cancer') diff --git a/tests/testthat/test-ggcoxdiagnostics.R b/tests/testthat/test-ggcoxdiagnostics.R new file mode 100644 index 0000000..eb173f1 --- /dev/null +++ b/tests/testthat/test-ggcoxdiagnostics.R @@ -0,0 +1,16 @@ +test_that('ggcoxdiagnostics creates plot with all the observations', { + cph <- coxph(Surv(futime, fustat) ~ rx + age, data=ovarian) + p <- ggcoxdiagnostics(cph, type="deviance") + .build <- ggplot_build(p) + expect_equal(nrow(.build$data[[1]]), nrow(ovarian)) +}) + +test_that('ggcoxdiagnostics with second type two rows for each observed event*term', { + cph <- coxph(Surv(futime, fustat) ~ rx + age, data=ovarian) + qty_terms <- length(attr(terms(cph$formula), "term.labels")) + qty_events <- sum(ovarian$fustat==1) + p <- ggcoxdiagnostics(cph, type="schoenfeld") + .build <- ggplot_build(p) + expect_equal(nrow(.build$data[[1]]), qty_terms*qty_events) +}) + From 68c99696c0114619b540f69c8988ebca886348a4 Mon Sep 17 00:00:00 2001 From: Alboukadel Kassambara Date: Mon, 13 Feb 2023 21:35:54 +0100 Subject: [PATCH 05/10] doc updated --- DESCRIPTION | 4 ++-- man/ggcoxdiagnostics.Rd | 4 ++-- man/ggcoxfunctional.Rd | 4 ++-- man/ggcoxzph.Rd | 4 ++-- man/ggsurvplot_df.Rd | 10 ++-------- man/ggsurvtable.Rd | 16 +++++----------- man/ggsurvtheme.Rd | 6 +++--- 7 files changed, 18 insertions(+), 30 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 012539b..8cd2a59 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -43,9 +43,9 @@ Suggests: testthat, rmarkdown VignetteBuilder: knitr -URL: https://rpkgs.datanovia.com/survminer/index.html +URL: https://rpkgs.datanovia.com/survminer/index.html BugReports: https://github.com/kassambara/survminer/issues -RoxygenNote: 7.1.1 +RoxygenNote: 7.2.3 Collate: 'BMT.R' 'BRCAOV.survInfo.R' diff --git a/man/ggcoxdiagnostics.Rd b/man/ggcoxdiagnostics.Rd index 01579c6..ebe406e 100644 --- a/man/ggcoxdiagnostics.Rd +++ b/man/ggcoxdiagnostics.Rd @@ -79,9 +79,9 @@ can be calculated with \link{coxph} function. } \section{Functions}{ \itemize{ -\item \code{ggcoxdiagnostics}: Diagnostic Plots for Cox Proportional Hazards Model with \pkg{ggplot2} -}} +\item \code{ggcoxdiagnostics()}: Diagnostic Plots for Cox Proportional Hazards Model with \pkg{ggplot2} +}} \examples{ library(survival) diff --git a/man/ggcoxfunctional.Rd b/man/ggcoxfunctional.Rd index c6f5e2f..e655d2b 100644 --- a/man/ggcoxfunctional.Rd +++ b/man/ggcoxfunctional.Rd @@ -67,9 +67,9 @@ should be linear to satisfy cox proportional hazards model assumptions. } \section{Functions}{ \itemize{ -\item \code{ggcoxfunctional}: Functional Form of Continuous Variable in Cox Proportional Hazards Model. -}} +\item \code{ggcoxfunctional()}: Functional Form of Continuous Variable in Cox Proportional Hazards Model. +}} \examples{ library(survival) diff --git a/man/ggcoxzph.Rd b/man/ggcoxzph.Rd index b7bc53c..a967d64 100644 --- a/man/ggcoxzph.Rd +++ b/man/ggcoxzph.Rd @@ -74,9 +74,9 @@ Displays a graph of the scaled Schoenfeld residuals, along with a } \section{Functions}{ \itemize{ -\item \code{ggcoxzph}: Graphical Test of Proportional Hazards using ggplot2. -}} +\item \code{ggcoxzph()}: Graphical Test of Proportional Hazards using ggplot2. +}} \examples{ library(survival) diff --git a/man/ggsurvplot_df.Rd b/man/ggsurvplot_df.Rd index a397f2f..1269947 100644 --- a/man/ggsurvplot_df.Rd +++ b/man/ggsurvplot_df.Rd @@ -111,15 +111,9 @@ censors. Default value is "+" (3), a sensible choice is "|" (124).} \item{censor.size}{numveric value specifying the point size of censors. Default is 4.5.} -\item{title}{main title and axis labels} +\item{title, xlab, ylab}{main title and axis labels} -\item{xlab}{main title and axis labels} - -\item{ylab}{main title and axis labels} - -\item{xlim}{x and y axis limits e.g. xlim = c(0, 1000), ylim = c(0, 1).} - -\item{ylim}{x and y axis limits e.g. xlim = c(0, 1000), ylim = c(0, 1).} +\item{xlim, ylim}{x and y axis limits e.g. xlim = c(0, 1000), ylim = c(0, 1).} \item{axes.offset}{logical value. Default is TRUE. If FALSE, set the plot axes to start at the origin.} diff --git a/man/ggsurvtable.Rd b/man/ggsurvtable.Rd index c3e7a7d..00eeb3e 100644 --- a/man/ggsurvtable.Rd +++ b/man/ggsurvtable.Rd @@ -97,8 +97,6 @@ function \link[grDevices]{palette}.} \item{break.time.by}{numeric value controlling time axis breaks. Default value is NULL.} -\item{xlim}{x and y axis limits e.g. xlim = c(0, 1000), ylim = c(0, 1).} - \item{xscale}{numeric or character value specifying x-axis scale. \itemize{ \item If numeric, the value is used to divide the labels on the x axis. For example, a value of 365.25 will give labels in years instead of the original @@ -107,10 +105,6 @@ days. \item If character, allowed options include one of c("d_m", "d_y", example, xscale = "d_m" will transform labels from days to months; xscale = "m_y", will transform labels from months to years.}} -\item{xlab}{main title and axis labels} - -\item{ylab}{main title and axis labels} - \item{xlog}{logical value. If TRUE, x axis is tansformed into log scale.} \item{legend}{character specifying legend position. Allowed values are one of @@ -163,15 +157,15 @@ Normally, users don't need to use this function directly. Internally used by the } \section{Functions}{ \itemize{ -\item \code{ggrisktable}: Plot the number at risk table. +\item \code{ggrisktable()}: Plot the number at risk table. -\item \code{ggcumevents}: Plot the cumulative number of events table +\item \code{ggcumevents()}: Plot the cumulative number of events table -\item \code{ggcumcensor}: Plot the cumulative number of censor table +\item \code{ggcumcensor()}: Plot the cumulative number of censor table -\item \code{ggsurvtable}: Generic function to plot survival tables: risk.table, cumevents and cumcensor -}} +\item \code{ggsurvtable()}: Generic function to plot survival tables: risk.table, cumevents and cumcensor +}} \examples{ # Fit survival curves #::::::::::::::::::::::::::::::::::::::::::::::: diff --git a/man/ggsurvtheme.Rd b/man/ggsurvtheme.Rd index e93236a..aa2f412 100644 --- a/man/ggsurvtheme.Rd +++ b/man/ggsurvtheme.Rd @@ -45,13 +45,13 @@ Default theme for plots generated with survminer. } \section{Functions}{ \itemize{ -\item \code{theme_survminer}: Default theme for survminer plots. A theme similar to theme_classic() with large font size. +\item \code{theme_survminer()}: Default theme for survminer plots. A theme similar to theme_classic() with large font size. -\item \code{theme_cleantable}: theme for drawing a clean risk table and cumulative +\item \code{theme_cleantable()}: theme for drawing a clean risk table and cumulative number of events table. A theme similar to theme_survminer() without i) axis lines and, ii) x axis ticks and title. -}} +}} \examples{ # Fit survival curves From 761a2e9fdfa60e4ec60463bdafdd6a6383df5b3b Mon Sep 17 00:00:00 2001 From: Alboukadel Kassambara Date: Thu, 16 Feb 2023 07:58:28 +0100 Subject: [PATCH 06/10] fix for dplyr:select() --- R/ggsurvplot_combine.R | 5 +++-- R/surv_median.R | 2 +- 2 files changed, 4 insertions(+), 3 deletions(-) diff --git a/R/ggsurvplot_combine.R b/R/ggsurvplot_combine.R index d634022..32aaca8 100644 --- a/R/ggsurvplot_combine.R +++ b/R/ggsurvplot_combine.R @@ -161,8 +161,9 @@ ggsurvplot_combine <- function(fit, data, survtable$strata <- paste(fitname, "::", survtable$strata, sep = "") %>% factor(levels = strata.levels) survtable %>% - dplyr::select(strata, time, n.risk, pct.risk, n.event, cum.n.event, - n.censor, cum.n.censor, strata_size) + dplyr::select( dplyr::all_of(c("strata", "time", "n.risk", "pct.risk", + "n.event", "cum.n.event", "n.censor", + "cum.n.censor", "strata_size"))) } grouped.d <- grouped.d %>% diff --git a/R/surv_median.R b/R/surv_median.R index afc16e0..f1caee4 100644 --- a/R/surv_median.R +++ b/R/surv_median.R @@ -59,7 +59,7 @@ surv_median <- function(fit, combine = FALSE){ .table$strata <- rownames(.table) .table <- .table %>% - dplyr::select(strata, median, `0.95LCL`, `0.95UCL`) + dplyr::select(dplyr::all_of(c("strata", "median", "0.95LCL", "0.95UCL"))) colnames(.table) <- c("strata", "median", "lower", "upper") rownames(.table) <- NULL .table From 7c4ad1571a1aede654028685bf6cfb28451cc940 Mon Sep 17 00:00:00 2001 From: Alboukadel Kassambara Date: Thu, 16 Feb 2023 07:59:01 +0100 Subject: [PATCH 07/10] fix lung data not found in unit test --- tests/testthat/test-ggsurvtable.R | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/tests/testthat/test-ggsurvtable.R b/tests/testthat/test-ggsurvtable.R index d7d6da9..d8566cd 100644 --- a/tests/testthat/test-ggsurvtable.R +++ b/tests/testthat/test-ggsurvtable.R @@ -1,11 +1,12 @@ context("test-ggsurvtable") -library(dplyr) -library("survival") -data("lung") -fit <- survfit(Surv(time, status) ~ sex, data = lung) + test_that("survtable y axis label colors work", { + library(dplyr) + library("survival") + #data("lung", package = "survival") + fit <- survfit(Surv(time, status) ~ sex, data = lung) p <- ggrisktable(fit, data = lung, color = "strata") .build <- ggplot_build(p) .build_data <- .build$data[[1]] From eb7f42df2ac03f5b8cc7e91191937c7133760470 Mon Sep 17 00:00:00 2001 From: Alboukadel Kassambara Date: Tue, 29 Oct 2024 15:48:41 +0000 Subject: [PATCH 08/10] ggplot2 minimum version set to 3.4.0 --- DESCRIPTION | 2 +- NEWS.md | 1 + 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index f423982..866110a 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -16,7 +16,7 @@ License: GPL-2 LazyData: TRUE Encoding: UTF-8 Depends: - ggplot2, + ggplot2(>= 3.4.0), ggpubr(>= 0.1.6) Imports: grid, diff --git a/NEWS.md b/NEWS.md index 2997f43..42721f4 100644 --- a/NEWS.md +++ b/NEWS.md @@ -7,6 +7,7 @@ ## Minor changes - R-ADDICT website is no longer live, so updating links in README (#622) +- ggplot2 minimum version is now 3.4.0 ## Bug fixes From c7ff6282b297da4a3070b334a68219ac53cf8873 Mon Sep 17 00:00:00 2001 From: Alboukadel Kassambara Date: Tue, 29 Oct 2024 15:49:13 +0000 Subject: [PATCH 09/10] gather replaced by pivot_longer() --- R/ggcoxdiagnostics.R | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/R/ggcoxdiagnostics.R b/R/ggcoxdiagnostics.R index 8f5676f..62b64e7 100644 --- a/R/ggcoxdiagnostics.R +++ b/R/ggcoxdiagnostics.R @@ -99,19 +99,20 @@ ggcoxdiagnostics <- function (fit, else col_names <- names(stats::coef(fit)) colnames(res) <- col_names res$xval <- xval - data2plot <- tidyr::gather(res, - key = "covariate", value = "res", - col_names) + data2plot <- tidyr::pivot_longer( + data = res, cols = dplyr::all_of(col_names), + names_to = "covariate", values_to = "res" + ) gplot <- ggplot(aes(xval, res), data = data2plot) + geom_point(col = point.col, shape = point.shape, size = point.size, alpha = point.alpha) if (hline) gplot <- gplot + geom_hline(yintercept=hline.yintercept, col = hline.col, - size = hline.size, lty = hline.lty, alpha = hline.alpha) + linewidth = hline.size, lty = hline.lty, alpha = hline.alpha) if (sline) gplot <- gplot + geom_smooth(col = sline.col, se = sline.se, method = "loess", - size = sline.size, lty = sline.lty, alpha = sline.alpha) + linewidth = sline.size, lty = sline.lty, alpha = sline.alpha) gplot <- gplot + labs(x = xlabel, y = ylabel, title = title, subtitle = subtitle, caption = caption) + ggtheme # customization From b7c4fae968640548253a0b81e3d278edf883b1af Mon Sep 17 00:00:00 2001 From: Alboukadel Kassambara Date: Tue, 29 Oct 2024 15:50:10 +0000 Subject: [PATCH 10/10] deprecated aes_string() replaced by aes() --- NAMESPACE | 2 ++ R/ggsurvplot_df.R | 2 +- R/utilities.R | 1 + man/ggsurvplot_df.Rd | 1 - 4 files changed, 4 insertions(+), 2 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index 66e0e14..3402bea 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -53,6 +53,8 @@ importFrom(grDevices,axisTicks) importFrom(magrittr,"%>%") importFrom(methods,is) importFrom(purrr,map) +importFrom(rlang,"!!") +importFrom(rlang,sym) importFrom(rlang,syms) importFrom(stats,anova) importFrom(stats,approx) diff --git a/R/ggsurvplot_df.R b/R/ggsurvplot_df.R index 1fb6a50..5f0eb64 100644 --- a/R/ggsurvplot_df.R +++ b/R/ggsurvplot_df.R @@ -176,7 +176,7 @@ ggsurvplot_df <- function(fit, fun = NULL, #:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::: df[, .strata.var] <- factor( df[, .strata.var], levels = .levels(.strata), labels = legend.labs) - p <- ggplot2::ggplot(df, ggplot2::aes_string("time", "surv")) + + p <- ggplot2::ggplot(df, ggplot2::aes(x = !!sym("time"), y = !!sym("surv"))) + ggpubr::geom_exec(surv.geom, data = df, size = size, color = color, linetype = linetype, ...) + ggplot2::scale_y_continuous(breaks = y.breaks, labels = scale_labels, limits = ylim, expand = .expand) + ggplot2::coord_cartesian(xlim = xlim)+ diff --git a/R/utilities.R b/R/utilities.R index 9049585..ebd5818 100644 --- a/R/utilities.R +++ b/R/utilities.R @@ -10,6 +10,7 @@ #' @importFrom stats pchisq #' @importFrom survMisc ten comp #' @importFrom utils capture.output +#' @importFrom rlang !! sym # Count the number of ggplots in a list diff --git a/man/ggsurvplot_df.Rd b/man/ggsurvplot_df.Rd index f0e22eb..8d64341 100644 --- a/man/ggsurvplot_df.Rd +++ b/man/ggsurvplot_df.Rd @@ -111,7 +111,6 @@ censors. Default value is "+" (3), a sensible choice is "|" (124).} \item{censor.size}{numveric value specifying the point size of censors. Default is 4.5.} - \item{title}{main title} \item{xlab}{x axis label}