Skip to content

Commit

Permalink
seq.Date(*, by = <abbreviated>); docu+checks also for seq.POSIX
Browse files Browse the repository at this point in the history
git-svn-id: https://svn.r-project.org/R/trunk@87537 00db46b3-68df-0310-9c12-caf00c1e9a41
  • Loading branch information
maechler committed Jan 7, 2025
1 parent a7bff54 commit 3b64ce9
Show file tree
Hide file tree
Showing 6 changed files with 29 additions and 10 deletions.
3 changes: 3 additions & 0 deletions doc/NEWS.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -156,6 +156,9 @@
The \code{Date} method also works for \code{seq(from, to)}, when
\code{by} is missing and now defaults to \code{"1 days"}.
It is now documented (and tested) that the \code{by} string may be
\emph{abbreviated} in both \code{seq} methods.
Both methods return or keep internal type \code{"integer"} more
consistently now. Also, \code{as.POSIXct({})} is internally integer.
}
Expand Down
12 changes: 7 additions & 5 deletions src/library/base/R/dates.R
Original file line number Diff line number Diff line change
Expand Up @@ -270,13 +270,15 @@ seq.Date <- function(from, to, by, length.out = NULL, along.with = NULL, ...)
units(by) <- "days"
by <- as.vector(by)
} else if(is.character(by)) {
by2 <- strsplit(by, " ", fixed = TRUE)[[1L]]
if(length(by2) > 2L || length(by2) < 1L)
nby2 <- length(by2 <- strsplit(by, " ", fixed = TRUE)[[1L]])
if(nby2 > 2L || nby2 < 1L)
stop("invalid 'by' string")
valid <- pmatch(by2[length(by2)],
c("days", "weeks", "months", "quarters", "years"))
bys <- c("days", "weeks", "months", "quarters", "years")
valid <- pmatch(by2[nby2], bys)
if(is.na(valid)) stop("invalid string for 'by'")
by <- bys[valid] # had *partial* match
if(valid > 2L) { # seq.POSIXt handles the logic for non-arithmetic cases
if (nby2 == 2L) by <- paste(by2[1L], by)
res <- switch(missing_arg,
from = seq(to = as.POSIXlt(to), by = by, length.out = length.out),
to = seq(from = as.POSIXlt(from), by = by, length.out = length.out),
Expand All @@ -285,7 +287,7 @@ seq.Date <- function(from, to, by, length.out = NULL, along.with = NULL, ...)
return(as.Date(res))
}
by <- c(1L, 7L)[valid]
if (length(by2) == 2L) by <- by * as.integer(by2[1L])
if (nby2 == 2L) by <- by * as.integer(by2[1L])
}
else if(!is.numeric(by)) stop("invalid mode for 'by'")
if(is.na(by)) stop("'by' is NA")
Expand Down
1 change: 1 addition & 0 deletions src/library/base/R/datetime.R
Original file line number Diff line number Diff line change
Expand Up @@ -1004,6 +1004,7 @@ function(from, to, by, length.out = NULL, along.with = NULL, ...)
)
return(.POSIXct(res, tz))
}
## months or longer --> via POSIXlt
lres <- as.POSIXlt(if (missing_arg != "from") from else to)
if (missing_arg == "length.out") lto <- as.POSIXlt(to)
if(valid == 7L) { # years
Expand Down
11 changes: 8 additions & 3 deletions src/library/base/man/seq.Date.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,8 @@
\item A number, taken to be in days.
\item A object of class \code{\link{difftime}}
\item A character string, containing one of \code{"day"},
\code{"week"}, \code{"month"}, \code{"quarter"} or \code{"year"}.
\code{"week"}, \code{"month"}, \code{"quarter"} or \code{"year"}, or a
\code{\link{pmatch}()}able abbreviaton of these.
This can optionally be preceded by a (positive or negative) integer
and a space, or followed by \code{"s"}.

Expand Down Expand Up @@ -55,11 +56,15 @@ seq(as.Date("2000/1/1"), as.Date("2003/1/1"), by = "quarter")
## 3-week period ending on a fixed date
seq(to = as.Date("2024-06-18"), by = "day", length.out = 21)

## find all 7th of the month between two dates, the last being a 7th.
## find all 7th of the month _strictly_ inside two dates, the last being a 7th.
st <- as.Date("1998-12-17")
en <- as.Date("2000-1-7")
ll <- seq(en, st, by = "-1 month")
rev(ll[ll > st & ll < en])
rev(ll[st < ll & ll < en])

## can abbreviate 'month' to 'm':
identical(seq(st, en, by = "m"),
seq(st, en, by = "1 month"))
}
\keyword{manip}
\keyword{chron}
3 changes: 2 additions & 1 deletion src/library/base/man/seq.POSIXt.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,8 @@
\item An object of class \code{\link{difftime}}
\item A character string, containing one of \code{"sec"},
\code{"min"}, \code{"hour"}, \code{"day"}, \code{"DSTday"},
\code{"week"}, \code{"month"}, \code{"quarter"} or \code{"year"}.
\code{"week"}, \code{"month"}, \code{"quarter"} or \code{"year"}, or a
\code{\link{pmatch}()}able abbreviaton of these.
This can optionally be preceded by a (positive or negative) integer
and a space, or followed by \code{"s"}.
}
Expand Down
9 changes: 8 additions & 1 deletion tests/datetime3.R
Original file line number Diff line number Diff line change
Expand Up @@ -683,6 +683,8 @@ All.eq0 <- function(x,y, ...) all.equal(x, y, tolerance = 0, ...)
stopifnot(exprs = {
## NB: use 'from' on LHS of reference to ensure the time zone of 'from' is used in the result
identical(seq(from, to, by=by), from + wks2sec*(0:4))
identical(seq(from, to, by=by),
seq(from, to, by="2 w")) # may abbreviate
identical(seq(from, to, length.out=length.out),
from + seq(0, difftime(to, from, units="secs"), length.out=length.out))
##
Expand Down Expand Up @@ -732,11 +734,16 @@ stopifnot(exprs = {
## variations on 'by'
identical(seq(from, to, by='2 months'), from + c(0, c(31+29)))
identical(seq(to, from, by='-2 months'), to - c(0, c(31+29)))
identical(seq(to, from, by='-2 m' ), to - c(0, c(31+29)))
identical(seq(from, to, by=as.difftime(30, units='days')), from + 30*(0:2))
identical(seq(from, to, by=30), from + 30*(0:2))
all.equal(seq(from, to, by = "1 week"), seq(from, by = "w", length.out = 9)) # TODO ident. ?
identical(seq(frI, toI, by = "1 week"), seq(from, by = "w", length.out = 9))
##
## missing from=
All.eq0 ( seq(to=to, by='day', length.out=6), to - (5:0))
identical(seq(to=to, by='day', length.out=6),
seq(to=to, length.out=6))
All.eq0 ( seq(to=to, length.out=6), to - (5:0))
All.eq0 ( seq(to=to, by='-3 days', length.out=6), to + 3*(5:0))
identical(seq(to=to, by='2 months',length.out=3), to - c(31+29+31+30, 31+29, 0))
identical(seq(to=to, by='quarter', length.out=3), to - c(31+29+31+30+31+30, 31+29+31, 0))
Expand Down

0 comments on commit 3b64ce9

Please sign in to comment.