Skip to content

Commit

Permalink
missing imports from stats
Browse files Browse the repository at this point in the history
  • Loading branch information
mikabr committed Oct 28, 2016
1 parent a492591 commit 9d500a0
Show file tree
Hide file tree
Showing 3 changed files with 12 additions and 12 deletions.
6 changes: 3 additions & 3 deletions R/ggcorplot.R
Expand Up @@ -67,9 +67,9 @@ ggcorplot <- function(data,
y <- data[,j]
x_mid <- min(x) + diff(range(x)) / 2
y_mid <- min(y) + diff(range(y)) / 2
this_cor <- cor(x,y)
this_cor <- stats::cor(x,y)
this_cor.test <- 0
this_cor.test <- cor.test(x, y)
this_cor.test <- stats::cor.test(x, y)
this_col <- ifelse(this_cor.test$p.value < .05, "<.05", ">.05")
this_size <- (this_cor) ^ 2
cor_text <- ifelse(this_cor > 0,
Expand Down Expand Up @@ -152,7 +152,7 @@ ggcorplot <- function(data,
#' ezLev(x, c(3,1,2))
ezLev <- function(x, new_order){
for (i in rev(new_order)) {
x <- relevel(x, ref = i)
x <- stats::relevel(x, ref = i)
}
return(x)
}
12 changes: 6 additions & 6 deletions R/multiboot.R
Expand Up @@ -43,7 +43,7 @@ multi_boot.numeric <- function(data,

if (length(statistics_functions) == 1) {
all_samples <- all_samples %>%
dplyr::rename_(.dots = setNames("sample", statistics_functions))
dplyr::rename_(.dots = stats::setNames("sample", statistics_functions))
}

return(all_samples)
Expand Down Expand Up @@ -140,7 +140,7 @@ multi_boot.data.frame <- function(data,
fun = as.name(summary_function),
arg = as.name(column)))
call_summary_function <- function(df) {
dplyr::summarise_(df, .dots = setNames(summary_dots, "summary"))
dplyr::summarise_(df, .dots = stats::setNames(summary_dots, "summary"))
}
}

Expand Down Expand Up @@ -184,8 +184,8 @@ multi_boot.data.frame <- function(data,
if (typeof(statistics_functions) == "character" &
length(statistics_functions) == 1) {
booted_vals <- dplyr::rename_(booted_vals,
.dots = setNames("summary",
statistics_functions))
.dots = stats::setNames("summary",
statistics_functions))
}

return(booted_vals)
Expand Down Expand Up @@ -251,7 +251,7 @@ multi_boot_standard <- function(data, column, na.rm = NULL,
}

call_empirical_function <- function(df) {
dplyr::summarise_(df, .dots = setNames(empirical_dots, "summary"))
dplyr::summarise_(df, .dots = stats::setNames(empirical_dots, "summary"))
}

booted_data <- multi_boot(data, summary_function = call_empirical_function,
Expand All @@ -260,7 +260,7 @@ multi_boot_standard <- function(data, column, na.rm = NULL,

call_empirical_function(data) %>%
dplyr::left_join(booted_data) %>%
dplyr::rename_(.dots = setNames("summary", empirical_function))
dplyr::rename_(.dots = stats::setNames("summary", empirical_function))
}

#' Non-parametric bootstrap with multiple sample statistics
Expand Down
6 changes: 3 additions & 3 deletions R/util.R
Expand Up @@ -16,7 +16,7 @@ sem <- function(x, na.rm = FALSE) {
} else {
n <- length(x)
}
sd(x, na.rm = na.rm) / sqrt(n)
stats::sd(x, na.rm = na.rm) / sqrt(n)
}

#' Confidence interval (lower)
Expand All @@ -32,7 +32,7 @@ sem <- function(x, na.rm = FALSE) {
#' ci_lower(x)
#' @export
ci_lower <- function(x, na.rm = FALSE) {
quantile(x, 0.025, na.rm)
stats::quantile(x, 0.025, na.rm)
}

#' Confidence interval (upper)
Expand All @@ -48,7 +48,7 @@ ci_lower <- function(x, na.rm = FALSE) {
#' ci_upper(x)
#' @export
ci_upper <- function(x, na.rm = FALSE) {
quantile(x, 0.975, na.rm)
stats::quantile(x, 0.975, na.rm)
}

#' Significance stars
Expand Down

0 comments on commit 9d500a0

Please sign in to comment.