Skip to content

Commit

Permalink
range() method replaces CFrange() function
Browse files Browse the repository at this point in the history
  • Loading branch information
pvanlaake committed May 15, 2024
1 parent 2e01094 commit 2fdd561
Show file tree
Hide file tree
Showing 10 changed files with 46 additions and 54 deletions.
2 changes: 1 addition & 1 deletion NAMESPACE
Expand Up @@ -5,7 +5,6 @@ export(CFfactor_coverage)
export(CFfactor_units)
export(CFmonth_days)
export(CFparse)
export(CFrange)
export(CFtime)
export(CFtimestamp)
export(calendar)
Expand All @@ -28,3 +27,4 @@ exportMethods(cut)
exportMethods(format)
exportMethods(indexOf)
exportMethods(length)
exportMethods(range)
7 changes: 4 additions & 3 deletions NEWS.md
Expand Up @@ -25,9 +25,10 @@ limited to month names and no weekday information can be generated. The `CFrange
function has a new "format" parameter to support the same functionality.
* `as.character()` and `length()` methods added that return a vector of timestamps
or the number of offsets in a CFtime instance, respectively.
* Several methods have been renamed (most notably `CFcomplete()` to `is_complete()`
and `CFsubset()` to `slab()`) to be more consistent with the R universe. Some
datum methods (deep down where regular mortals do not dwell) have been deleted.
* Several methods have been renamed (most notably `CFcomplete()` to `is_complete()`,
`CFrange()` to the standard generic `range()`, and `CFsubset()` to `slab()`) to
be more consistent with the R universe. Some datum methods (deep down where regular
mortals do not dwell) have been deleted.
* Minor code fixes, see GitHub commits.
* Documentation updated, with description of new functions.

Expand Down
13 changes: 7 additions & 6 deletions R/CFformat.R
Expand Up @@ -44,15 +44,12 @@ CFtimestamp <- function(cf, format = NULL, asPOSIX = FALSE) {
if (nrow(time) == 0L) return()

if (is.null(format)) format <- ifelse(cf@datum@unit < 4L || .has_time(time), "timestamp", "date")
else if (!(format %in% c("date", "time", "timestamp"))) stop("Format specifier not recognized")
else if (!(format %in% c("date", "timestamp"))) stop("Format specifier not recognized")

if (asPOSIX) {
if (format == "date") ISOdate(time$year, time$month, time$day, 0L)
else ISOdatetime(time$year, time$month, time$day, time$hour, time$minute, time$second, "UTC")
} else {
if (format == "date") sprintf("%04d-%02d-%02d", time$year, time$month, time$day)
else sprintf("%04d-%02d-%02dT%s", time$year, time$month, time$day, .format_time(time))
}
} else .format_format(time, timezone(cf), format)
}

#' Formatting of time strings from time elements
Expand Down Expand Up @@ -96,10 +93,14 @@ CFtimestamp <- function(cf, format = NULL, asPOSIX = FALSE) {
#'
#' @param ts data.frame of decomposed offsets.
#' @param tz character. Time zone character string.
#' @param format character. A character string with the format specifiers.
#' @param format character. A character string with the format specifiers, or
#' "date" or "timestamp".
#' @returns Character vector of formatted timestamps.
#' @noRd
.format_format <- function(ts, tz, format) {
if (format == "date") return(sprintf("%04d-%02d-%02d", ts$year, ts$month, ts$day))
else if (format == "timestamp") return(sprintf("%04d-%02d-%02d %s", ts$year, ts$month, ts$day, .format_time(ts)))

# Expand any composite specifiers
format <- stringr::str_replace_all(format, c("%F" = "%Y-%m-%d", "%R" = "%H:%M", "%T" = "%H:%M:%S"))

Expand Down
2 changes: 1 addition & 1 deletion R/CFtime-package.R
Expand Up @@ -25,7 +25,7 @@
#' * [`Merge`][CFtime-merge] two CFtime instances
#' * [`Append`][CFtime-append] additional time steps to a CFtime instance
#' * [CFtimestamp()] and [format()]: Generate a vector of character or `POSIXct` timestamps from a CFtime instance
#' * [CFrange()]: Timestamps of the two endpoints in the time series
#' * [range()]: Timestamps of the two endpoints in the time series
#' * [is_complete()]: Does the CFtime instance have a complete time series between endpoints?
#' * [CFmonth_days()]: How many days are there in a month using the CFtime calendar?
#'
Expand Down
34 changes: 14 additions & 20 deletions R/CFtime.R
Expand Up @@ -288,7 +288,7 @@ setMethod("format", "CFtime", function(x, format) {
#' When `breaks` is a vector of character timestamps a factor is produced with a
#' level for every interval between timestamps. The last timestamp, therefore,
#' is only used to close the interval started by the pen-ultimate timestamp -
#' use a distant timestamp (e.g. `CFrange(x)[2]`) to ensure that all offsets to
#' use a distant timestamp (e.g. `range(x)[2]`) to ensure that all offsets to
#' the end of the CFtime time series are included, if so desired. The last
#' timestamp will become the upper bound in the CFtime instance that is returned
#' as an attribute to this function so a sensible value for the last timestamp
Expand Down Expand Up @@ -457,25 +457,22 @@ setMethod("indexOf", c("ANY", "CFtime"), function(x, cf, method = "constant") {
intv
})

#' @aliases CFrange
#'
#' @title Extreme time series values
#'
#' @description Character representation of the extreme values in the time series
#'
#' @param x An instance of the `CFtime` class.
#' @param format A character string with format specifiers, optional.
#' @param ... Ignored.
#' @param na.rm Ignored.
#'
#' @returns character. Vector of two character representations of the extremes of the time series.
#' @export
#' @examples
#' cf <- CFtime("days since 1850-01-01", "julian", 0:364)
#' CFrange(cf)
#' CFrange(cf, "%Y-%b-%e")
setGeneric("CFrange", function(x, format = "") standardGeneric("CFrange"))

#' @describeIn CFrange Extreme values of the time series
setMethod("CFrange", "CFtime", function(x, format = "") .ts_extremes(x, format))
#' range(cf)
#' range(cf, "%Y-%b-%e")
setMethod("range", "CFtime", function(x, format = "", ..., na.rm = FALSE) .ts_extremes(x, format, ..., na.rm))

#' Indicates if the time series is complete
#'
Expand Down Expand Up @@ -686,8 +683,8 @@ setMethod("+", c("CFtime", "numeric"), function(e1, e2) {
#' package.
#'
#' @param x CFtime. The time series to operate on.
#' @param format character. Optional character string that specifies
#' alternate format.
#' @param format character. Value of "date" or "timestamp". Optionally, a
#' character string that specifies an alternate format.
#'
#' @returns Vector of two character strings that represent the starting and
#' ending timestamps in the time series. If a `format` is supplied, that
Expand All @@ -696,21 +693,18 @@ setMethod("+", c("CFtime", "numeric"), function(e1, e2) {
#' otherwise the full timestamp (without any time zone information).
#'
#' @noRd
.ts_extremes <- function(x, format = "") {
.ts_extremes <- function(x, format = "", ..., na.rm) {
if (length(x@offsets) == 0L) return(c(NA_character_, NA_character_))
if (!missing(format) && ((!is.character(format)) || length(format) != 1))
stop("`format` parameter, when present, must be a character string with formatting specifiers")

time <- .offsets2time(range(x@offsets), x@datum)

if (nchar(format) > 0)
.format_format(time, tz(x@datum), format)
else if (sum(time$hour, time$minute, time$second) == 0) # all times are 00:00:00
sprintf("%04d-%02d-%02d", time$year, time$month, time$day)
else {
t <- .format_time(time)
sprintf("%04d-%02d-%02d %s", time$year, time$month, time$day, t)
}
if (format == "") format <- "timestamp"
if (format == "timestamp" && sum(time$hour, time$minute, time$second) == 0)
format <- "date"

.format_format(time, tz(x@datum), format)
}

#' Which time steps fall within two extreme values
Expand Down
2 changes: 1 addition & 1 deletion man/CFtime-package.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion man/cut-CFtime-method.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

22 changes: 9 additions & 13 deletions man/CFrange.Rd → man/range-CFtime-method.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

14 changes: 7 additions & 7 deletions tests/testthat/test-CFtime.R
Expand Up @@ -47,12 +47,12 @@ test_that("test all variants of creating a CFtime object and useful functions",

# Character offsets
cf <- CFtime("hours since 2023-01-01", "360_day", "2023-04-30T23:00")
expect_equal(CFrange(cf), c("2023-01-01 00:00:00", "2023-04-30 23:00:00"))
expect_equal(range(cf), c("2023-01-01 00:00:00", "2023-04-30 23:00:00"))
expect_equal(length(CFtimestamp(cf, "timestamp")), 4 * 30 * 24)

expect_error(CFtime("days since 2023-01-01", "366_day", c("2021-01-01", "2021-04-13")))
cf <- CFtime("days since 2023-01-01", "366_day", c("2023-01-01", "2023-04-13", "2023-10-30", "2023-05-12"))
expect_equal(CFrange(cf), c("2023-01-01", "2023-10-30"))
expect_equal(range(cf), c("2023-01-01", "2023-10-30"))

# Merge two CFtime instances / extend offsets
cf1 <- CFtime("hours since 2001-01-01", "360_day", 0:99)
Expand Down Expand Up @@ -95,16 +95,16 @@ test_that("test all variants of creating a CFtime object and useful functions",

# Range
cf <- CFtime("days since 2001-01-01")
expect_equal(CFrange(cf), c(NA_character_, NA_character_))
expect_equal(range(cf), c(NA_character_, NA_character_))
cf <- cf + 0:1
expect_error(CFrange(cf, 123))
expect_error(CFrange(cf, c("asd %d", "%F")))
expect_equal(CFrange(cf, "%Y-%B-%Od"), c("2001-January-01", "2001-January-02"))
expect_error(range(cf, 123))
expect_error(range(cf, c("asd %d", "%F")))
expect_equal(range(cf, "%Y-%B-%Od"), c("2001-January-01", "2001-January-02"))

# Range on unsorted offsets
random <- runif(100, min = 1, max = 99)
cf <- CFtime("days since 2001-01-01", offsets = c(0, random[1:50], 100, random[51:100]))
expect_equal(CFrange(cf), c("2001-01-01", paste0(as.Date("2001-01-01") + 100)))
expect_equal(range(cf), c("2001-01-01", paste0(as.Date("2001-01-01") + 100)))

# Subsetting
cf <- CFtime("hours since 2023-01-01 00:00:00", "standard", 0:239)
Expand Down
2 changes: 1 addition & 1 deletion vignettes/CFtime.Rmd
Expand Up @@ -176,7 +176,7 @@ dates[1:10]
...as well as the full range of the time series:

```{r}
CFrange(cf)
range(cf)
```

Note that in this latter case, if any of the timestamps in the time series have a time that is
Expand Down

0 comments on commit 2fdd561

Please sign in to comment.