Skip to content

Commit

Permalink
Merge pull request #11 from wurli/tidyverse-message
Browse files Browse the repository at this point in the history
Special message for `library(tidyverse)`
  • Loading branch information
wurli authored Mar 3, 2024
2 parents ba50930 + ccc644a commit aa067b8
Show file tree
Hide file tree
Showing 19 changed files with 350 additions and 249 deletions.
4 changes: 2 additions & 2 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ Title: Informative Messages About Outdated Packages
Version: 0.1.0
Authors@R: person("Jacob", "Scott", email = "[email protected]", role = c("aut", "cre"))
Description: When a package is loaded, the source repository is checked for
new versions. A message is show in the console indicating whether the
new versions and a message is show in the console indicating whether the
package is out of date.
License: MIT + file LICENSE
Encoding: UTF-8
Expand All @@ -13,7 +13,7 @@ URL: https://github.com/wurli/updateme, https://wurli.github.io/updateme/
BugReports: https://github.com/wurli/updateme/issues
Imports:
cachem,
cli,
cli (>= 3.6.0),
curl,
memoise,
rlang,
Expand Down
3 changes: 3 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
# updateme 0.1.0

* Added a `NEWS.md` file to track changes to the package.
3 changes: 2 additions & 1 deletion R/available_version.R
Original file line number Diff line number Diff line change
Expand Up @@ -217,6 +217,7 @@ desc_from_git <- function(username, repo, pkg = repo, type = c("github", "gitlab
curl::handle_setheaders(handle, .list = auth_header)

con <- curl::curl(file_url, handle = handle)
on.exit(try(close(con), silent = TRUE))

tryCatch(
readLines(con, warn = FALSE),
Expand All @@ -232,7 +233,7 @@ desc_from_git <- function(username, repo, pkg = repo, type = c("github", "gitlab
i = private_repo_msg,
i = paste(
"Is the repo private? Perhaps you need to configure",
"an {.topic [access token](updateme::updateme_set_sources)}."
"an {.topic [access token](updateme::updateme_sources_set)}."
)
)
} else if (grepl("302", msg)) {
Expand Down
2 changes: 1 addition & 1 deletion R/bioc.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ bioc_version <- function(pkg = NULL) {
return(vn[, 1:2])
}

vn <- try(packageVersion("BiocVersion"), silent = TRUE)
vn <- installed_version("BiocVersion")
if (inherits(vn, "numeric_version"))
return(vn[, 1:2])

Expand Down
13 changes: 0 additions & 13 deletions R/capture_tidyverse_startup_message.R

This file was deleted.

89 changes: 61 additions & 28 deletions R/inform_load.R
Original file line number Diff line number Diff line change
@@ -1,27 +1,52 @@
inform_load <- function(pkg, inform_if_ahead = NULL) {
inform_load <- function(pkg, extra_attachments = NULL) {

if (!is_interactive() || !updateme_is_on()) {
return(invisible(NULL))
}

if (identical(pkg, "tidyverse")) {
cli::cat_line(tidyverse_attach_message(extra_attachments))

if (!is_attached("conflicted"))
print(get("tidyverse_conflicts", asNamespace("tidyverse"))())

return(invisible(NULL))
}

is_loaded <- paste0("package:", pkg) %in% search()

cli::cli_alert_info(paste0(
if (is_loaded) "Using " else "Loading ",
"{.pkg {pkg}} ",
package_version_describe(pkg)
))

invisible(NULL)

}

package_version_describe <- function(pkg, inform_if_ahead = NULL, template = NULL) {

installation_info <- package_installation_info(pkg)
current <- packageVersion(pkg)
remote_vn_info <- available_version(installation_info)
available <- remote_vn_info[["Source_Version"]]
source <- remote_vn_info[["Source_Name"]]
source_url <- remote_vn_info[["Source_URL"]]

installed_version <- packageVersion(pkg)
available <- available_version(installation_info)
repo_version <- available[["Source_Version"]]
inform_if_ahead <- inform_if_ahead %||% grepl("^Bioc", available[["Source_Name"]])
inform_if_ahead <- inform_if_ahead %||% grepl("^Bioc", source)

new_version_found <- !is.null(repo_version)
new_version_found <- !is.null(available)

currentness_unknown <- !new_version_found ||
!is.package_version(repo_version) ||
!is.package_version(installed_version)
currentness_is_unknown <- !new_version_found ||
!is.package_version(available) ||
!is.package_version(current)

currentness <- if (currentness_unknown)
currentness <- if (currentness_is_unknown)
"unknown"
else if (installed_version < repo_version)
else if (current < available)
"outdated"
else if (installed_version == repo_version)
else if (current == available)
"up_to_date"
else
"ahead"
Expand All @@ -33,31 +58,39 @@ inform_load <- function(pkg, inform_if_ahead = NULL) {
ahead = cli::col_br_magenta
)

src_name <- available[["Source_Name"]]
src_url <- available[["Source_URL"]]
show_extra_info <- currentness %in% c(
"outdated", "unknown", if (inform_if_ahead) "ahead"
)

extra_info <- if (new_version_found && currentness %in% c("outdated", "unknown", "ahead")) {
src_pretty <- if (is.null(src_url))
src_name
extra_info <- if (!new_version_found || !show_extra_info) {
""
} else {
src <- if (is.null(source_url))
source
else
cli::format_inline("{.href [{src_name}]({src_url})}")
cli::format_inline("{.href [{source}]({source_url})}")

vn <- available

cli::col_grey(cli::style_italic(cli::format_inline(switch(currentness,
outdated = ,
unknown = " ({repo_version} now available from {src_pretty})",
ahead = " ({repo_version} is the latest version on {src_pretty})"
unknown = template %||% "({vn} now available from {src})",
ahead = "({vn} is the latest version on {src})"
))))
}

cli::cli_alert_info(paste0(
"Loading ",
cli::format_inline("{.pkg {pkg}}"), " ",
fmt_currentness(installed_version),
extra_info
))

invisible(NULL)
paste(fmt_currentness(style_version(current)), extra_info)
}

style_version <- function(x) {
x <- as.character(x)
is_dev <- function(x) {
x <- suppressWarnings(as.numeric(x))
!is.na(x) & x >= 9000
}
pieces <- strsplit(x, ".", fixed = TRUE)
pieces <- lapply(pieces, function(x) ifelse(is_dev(x), cli::style_italic(x), x))
vapply(pieces, paste, collapse = ".", FUN.VALUE = character(1))
}

available_packages <- function(repos = getOption("repos")) {
Expand Down
Loading

0 comments on commit aa067b8

Please sign in to comment.