Skip to content

Commit

Permalink
print.POSIX*t(.., digits = *) passed to format...()
Browse files Browse the repository at this point in the history
git-svn-id: https://svn.r-project.org/R/trunk@87363 00db46b3-68df-0310-9c12-caf00c1e9a41
  • Loading branch information
maechler committed Nov 22, 2024
1 parent 75f3824 commit 36b2f1f
Show file tree
Hide file tree
Showing 4 changed files with 37 additions and 12 deletions.
10 changes: 8 additions & 2 deletions doc/NEWS.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -121,6 +121,12 @@
\item The \code{sunspot.month} data have been updated to Oct 2024;
because of recalibration also historical numbers are changed, and we
keep the previous data as \code{sunspot.m2014} for reproducibility.

\item The \code{print()} method for date-time objects (\code{POSIX.t})
gets an optional \code{digits} argument for \emph{fractional}
seconds, passed to improved \code{format.POSIXlt()}; consequently,
\code{print(<date.time>, digits = n)} allows to print fractions of
seconds.
}
}

Expand Down Expand Up @@ -369,11 +375,11 @@

\item \code{debug()} and \code{debugonce(fun)} now also accept a
string \code{fun} when it names an S4 generic, fixing \PR{18822}
thanks to \I{Michael Jagan}.
thanks to \I{Mikael Jagan}.

\item \code{debugonce(<S4-simple-body>, signature=*)} now works
correctly when \dQuote{called twice}, fixing \PR{18824} thanks to
\I{Michael Jagan}.
\I{Mikael Jagan}.

\item \code{format(dtime, digits=* / format=*)} is more consistent
when the \code{POSIXt} date-time object \code{dtime} has fractional
Expand Down
7 changes: 4 additions & 3 deletions src/library/base/R/datetime.R
Original file line number Diff line number Diff line change
Expand Up @@ -426,12 +426,13 @@ format.POSIXct <- function(x, format = "", tz = "", usetz = FALSE, ...)

## keep in sync with print.Date() in ./dates.R
print.POSIXct <-
print.POSIXlt <- function(x, tz = "", usetz = TRUE, max = NULL, ...)
print.POSIXlt <- function(x, tz = "", usetz = TRUE, max = NULL,
digits = getOption("digits.secs"), ...)
{
if(is.null(max)) max <- getOption("max.print", 9999L)
FORM <- if(missing(tz))
function(z) format(z, usetz = usetz)
else function(z) format(z, tz = tz, usetz = usetz)
function(z) format(z, usetz=usetz, digits=digits)
else function(z) format(z, tz=tz, usetz=usetz, digits=digits)
if(max < length(x)) {
print(FORM(x[seq_len(max)]), max=max+1, ...)
cat(" [ reached 'max' / getOption(\"max.print\") -- omitted",
Expand Down
13 changes: 7 additions & 6 deletions src/library/base/man/DateTimeClasses.Rd
Original file line number Diff line number Diff line change
Expand Up @@ -60,7 +60,8 @@
representing calendar dates and times.
}
\usage{
\method{print}{POSIXct}(x, tz = "", usetz = TRUE, max = NULL, \dots)
\method{print}{POSIXct}(x, tz = "", usetz = TRUE, max = NULL,
digits = getOption("digits.prec"), \dots)

\method{summary}{POSIXct}(object, digits = 15, \dots)

Expand All @@ -76,7 +77,9 @@
\item{max}{numeric or \code{NULL}, specifying the maximal number of
entries to be printed. By default, when \code{NULL},
\code{\link{getOption}("max.print")} used.}
\item{digits}{number of significant digits for the computations:
\item{digits}{number of digits to format fractional seconds in the case
of \code{print()};
number of \emph{significant} digits for the computations:
should be high enough to represent the least important time unit
exactly.}
\item{\dots}{further arguments to be passed from or to other methods.}
Expand Down Expand Up @@ -337,16 +340,14 @@
must not be changed, as several C-based conversion methods rely on the
order for efficiency.
}
\examples{
\dontdiff{
\examples{\dontdiff{
(z <- Sys.time()) # the current date, as class "POSIXct"

Sys.time() - 3600 # an hour ago

as.POSIXlt(Sys.time(), "GMT") # the current time in GMT
format(.leap.seconds) # the leap seconds in your time zone
format(.leap.seconds) # the leap seconds in your time zone}
print(.leap.seconds, tz = "America/Los_Angeles") # and in Seattle's
}

## look at *internal* representation of "POSIXlt" :
leapS <- as.POSIXlt(.leap.seconds)
Expand Down
19 changes: 18 additions & 1 deletion tests/datetime3.R
Original file line number Diff line number Diff line change
Expand Up @@ -622,7 +622,7 @@ stopifnot(identical(fx, format(x.))) # *are* the same (for a while now)
fD.OS <- function(d) format(x, format = paste0("%Y-%m-%d %H:%M:%OS", if(d=="_") "" else d))
f.OSss <- vapply(c("_",0:6), fD.OS, character(length(x)))
t(f.OSss) |> print(width=111, quote=FALSE) # shows 'trunc()' instead of 'round()'
stopifnot(identical(f.OSss[,"_"], f.OSss[,"6"])) # by option digits.secs
stopifnot(identical(f.OSss[,"_"], f.OSss[,"6"])) # by option digits.secs
(secDig <- sub(".*:59", '', f.OSss)) ## [,"1"] is *.0 *.0 *.2 *.2 - "bad" from using trunc() by design
## ___________ ___ __ __ "factory fresh" default
options(digits.secs = NULL, scipen = 0, digits = 7)
Expand All @@ -638,6 +638,23 @@ stopifnot(exprs = {
options(op)
## Number of digits used differed in several cases in R <= 4.4.z

## print(*, digits = n) now works, too -- compatibly with format()
print(x, digits = 6) # shows full digits
xx <- as.POSIXct("2009-08-03 12:01:59") + 0:8/8 # rare exact dbl prec
j <- 2L*(1:4) -1L # 1,3,5,7
(fxx2 <- format(xx, digits = 2)[j])
print(xx, digits = 5, usetz=FALSE)# needs only 3 digits
pxx <- capture.output(split = TRUE,
print(xx[j], digits = 5, width=140)) # 2 digits suffice
stopifnot(exprs = {
identical(format(x, digits = 6) |> paste(collapse=' '), sub('^\\[1\\] ', '', gsub('"', '', capture.output(
print (x, digits = 6, usetz = FALSE, width = 120)))))
is.integer(nf2 <- nchar(fxx2))
substr (fxx2, nf2-1L, nf2) == c("00", "25", "50", "75")
identical(fxx2, sub(" [A-Z].*$", '',
strsplit(split = "@",
gsub('" "', '@', sub(".$", '', sub('^\\[1\\] "', '', pxx))))[[1L]]))
})


## keep at end
Expand Down

0 comments on commit 36b2f1f

Please sign in to comment.