Skip to content

Commit

Permalink
Drop prettyunits dependency
Browse files Browse the repository at this point in the history
  • Loading branch information
gaborcsardi committed Nov 20, 2023
1 parent 1944f50 commit 6f6f5cc
Show file tree
Hide file tree
Showing 5 changed files with 116 additions and 13 deletions.
3 changes: 1 addition & 2 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -17,8 +17,7 @@ BugReports: https://github.com/r-hub/pkgsearch/issues
Imports:
curl,
jsonlite,
parsedate (>= 1.3.0),
prettyunits
parsedate (>= 1.3.0)
Suggests:
mockery,
covr,
Expand Down
1 change: 0 additions & 1 deletion NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -24,5 +24,4 @@ importFrom(jsonlite,unbox)
importFrom(parsedate,format_iso_8601)
importFrom(parsedate,parse_date)
importFrom(parsedate,parse_iso_8601)
importFrom(prettyunits,time_ago)
importFrom(utils,capture.output)
2 changes: 1 addition & 1 deletion R/addin.R
Original file line number Diff line number Diff line change
Expand Up @@ -714,7 +714,7 @@ format_pkg <- function(record, id, num, from) {
", by ",
record$maintainer_name,
", ",
time_ago(record$date)
format_time_ago$time_ago(record$date)
)
urls <- find_urls(record$url)
shiny::p(
Expand Down
15 changes: 6 additions & 9 deletions R/print.R
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ summary.pkg_search_result <- function(object, ...) {
package = object$package,
version = object$version,
by = object$maintainer_name,
" @" = time_ago(object$date, format = "terse")
" @" = format_time_ago$time_ago(object$date, format = "terse")
)

w <- max(nchar(capture.output(print(pkgs, row.names = FALSE))))
Expand Down Expand Up @@ -59,16 +59,14 @@ print.pkg_search_result <- function(x, ...) {
}
}

#' @importFrom prettyunits time_ago

cat_hit <- function(x, no) {

cat("\n")

pkg <- x[no, ]

## Header
ago <- time_ago(pkg$date)
ago <- format_time_ago$time_ago(pkg$date)
pkg_ver <- as.character(meta(x)$from + no - 1) %+% " " %+%
pkg$package %+% " @ " %+% as.character(pkg$version)
cat(left_right(pkg_ver, pkg$maintainer_name %+% ", " %+% ago), sep = "\n")
Expand Down Expand Up @@ -156,12 +154,11 @@ summary.cran_event_list <- function(object, ...) {
#' @rdname cran_events
#' @param x Object to print.
#' @param ... Additional arguments are ignored currently.
#' @importFrom prettyunits time_ago
#' @importFrom parsedate parse_date

print.cran_event_list <- function(x, ...) {
cat_fill("CRAN events (" %+% attr(x, "mode") %+% ")")
when <- time_ago(format = "short", parse_date(sapply(x, "[[", "date")))
when <- format_time_ago$time_ago(format = "short", parse_date(sapply(x, "[[", "date")))
pkgs <- data.frame(
stringsAsFactors = FALSE, check.names = FALSE,
"." = ifelse(sapply(x, "[[", "event") == "released", "+", "-"),
Expand All @@ -170,7 +167,7 @@ print.cran_event_list <- function(x, ...) {
Version = sapply(x, function(xx) xx$package$Version),
RTitle = gsub("\\s+", " ", sapply(x, function(xx) xx$package$Title))
)

tw <- getOption("width") - 7 - 3 -
max(nchar("When"), max(nchar(pkgs$When))) -
max(nchar("Package"), max(nchar(pkgs$Package))) -
Expand All @@ -179,9 +176,9 @@ print.cran_event_list <- function(x, ...) {
pkgs$Title <- ifelse(pkgs$Title == pkgs$RTitle, pkgs$Title,
paste0(pkgs$Title, "..."))
pkgs$RTitle <- NULL

print.data.frame(pkgs, row.names = FALSE, right = FALSE)

invisible(x)
}

Expand Down
108 changes: 108 additions & 0 deletions R/time-ago.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,108 @@

format_time_ago <- local({

e <- expression

`%s%` <- function(lhs, rhs) {
assert_string(lhs)
do.call(
sprintf,
c(list(lhs), as.list(rhs))
)
}

assert_string <- function(x) {
stopifnot(is.character(x), length(x) == 1L)
}

assert_diff_time <- function(x) {
stopifnot(inherits(x, "difftime"))
}

vague_dt_default <- list(
list(c = e(seconds < 10), s = "moments ago"),
list(c = e(seconds < 45), s = "less than a minute ago"),
list(c = e(seconds < 90), s = "about a minute ago"),
list(c = e(minutes < 45), s = e("%d minutes ago" %s% round(minutes))),
list(c = e(minutes < 90), s = "about an hour ago"),
list(c = e(hours < 24), s = e("%d hours ago" %s% round(hours))),
list(c = e(hours < 42), s = "a day ago"),
list(c = e(days < 30), s = e("%d days ago" %s% round(days))),
list(c = e(days < 45), s = "about a month ago"),
list(c = e(days < 335), s = e("%d months ago" %s% round(days / 30))),
list(c = e(years < 1.5), s = "about a year ago"),
list(c = TRUE, s = e("%d years ago" %s% round(years)))
)

vague_dt_short <- list(
list(c = e(seconds < 50), s = "<1 min"),
list(c = e(minutes < 50), s = e("%d min" %s% round(minutes))),
list(c = e(hours < 1.5), s = "1 hour"),
list(c = e(hours < 18), s = e("%d hours" %s% round(hours))),
list(c = e(hours < 42), s = "1 day"),
list(c = e(days < 30), s = e("%d day" %s% round(days))),
list(c = e(days < 45), s = "1 mon"),
list(c = e(days < 335), s = e("%d mon" %s% round(days / 30))),
list(c = e(years < 1.5), s = "1 year"),
list(c = TRUE, s = e("%d years" %s% round(years)))
)

vague_dt_terse <- list(
list(c = e(seconds < 50), s = e("%2ds" %s% round(seconds))),
list(c = e(minutes < 50), s = e("%2dm" %s% round(minutes))),
list(c = e(hours < 18), s = e("%2dh" %s% round(hours))),
list(c = e(days < 30), s = e("%2dd" %s% round(days))),
list(c = e(days < 335), s = e("%2dM" %s% round(days / 30))),
list(c = TRUE, s = e("%2dy" %s% round(years)))
)

vague_dt_formats <- list(
"default" = vague_dt_default,
"short" = vague_dt_short,
"terse" = vague_dt_terse
)

time_ago <- function(date, format = c("default", "short", "terse")) {

date <- as.POSIXct(date)

if (length(date) > 1) return(sapply(date, time_ago, format = format))

seconds <- difftime(Sys.time(), date, units = "secs")

vague_dt(seconds, format = format)
}

vague_dt <- function(dt, format = c("default", "short", "terse")) {

assert_diff_time(dt)

units(dt) <- "secs"
seconds <- as.vector(dt)

## Simplest to quit here for empty input
if (!length(seconds)) return(character())

pieces <- list(
minutes = seconds / 60,
hours = seconds / 60 / 60,
days = seconds / 60 / 60 / 24,
years = seconds / 60 / 60 / 24 / 365.25
)

format <- match.arg(format)

for (p in vague_dt_formats[[format]]) {
if (eval(p$c, pieces)) return(eval(p$s, pieces))
}
}

structure(
list(
.internal = environment(),
time_ago = time_ago,
vague_dt = vague_dt
),
class = c("standalone_time_ago", "standalone")
)
})

0 comments on commit 6f6f5cc

Please sign in to comment.