11# File src/library/base/R/datetime.R
22# Part of the R package, https://www.R-project.org
33#
4- # Copyright (C) 1995-2024 The R Core Team
4+ # Copyright (C) 1995-2025 The R Core Team
55#
66# This program is free software; you can redistribute it and/or modify
77# it under the terms of the GNU General Public License as published by
@@ -340,7 +340,7 @@ as.POSIXct.default <- function(x, tz = "", ...)
340340{
341341 if (inherits(x , " POSIXct" ))
342342 return (if (missing(tz )) x else .POSIXct(x , tz ))
343- if (is.null(x )) return (.POSIXct(numeric (), tz ))
343+ if (is.null(x )) return (.POSIXct(integer (), tz ))
344344 if (is.character(x ) || is.factor(x ))
345345 return (as.POSIXct(as.POSIXlt(x , tz , ... ), tz , ... ))
346346 if (is.logical(x ) && all(is.na(x )))
@@ -665,7 +665,7 @@ c.POSIXlt <- function(..., recursive = FALSE) {
665665ISOdatetime <- function (year , month , day , hour , min , sec , tz = " " )
666666{
667667 if (min(lengths(list (year , month , day , hour , min , sec ), use.names = FALSE )) == 0L )
668- .POSIXct(numeric (), tz = tz )
668+ .POSIXct(integer (), tz = tz )
669669 else {
670670 x <- paste(year , month , day , hour , min , sec , sep = " -" )
671671 as.POSIXct(strptime(x , " %Y-%m-%d-%H-%M-%OS" , tz = tz ), tz = tz )
@@ -736,9 +736,9 @@ as.difftime <- function(tim, format = "%X", units = "auto", tz = "UTC")
736736 nms <- names(tim )
737737 tim <- as.double(tim )
738738 names(tim ) <- nms
739- if (units == " auto" ) stop(" need explicit units for numeric conversion" )
739+ if (units == " auto" ) stop(" need explicit units for numeric conversion" )
740740 if (! (units %in% c(" secs" , " mins" , " hours" , " days" , " weeks" )))
741- stop(" invalid units specified" )
741+ stop(" invalid units specified" )
742742 .difftime(tim , units = units )
743743 }
744744}
@@ -945,39 +945,41 @@ function(x, value)
945945seq.POSIXt <-
946946function (from , to , by , length.out = NULL , along.with = NULL , ... )
947947{
948- if (missing(from )) stop(" 'from' must be specified" )
949- if (! inherits(from , " POSIXt" )) stop(" 'from' must be a \" POSIXt\" object" )
950- cfrom <- as.POSIXct(from )
951- if (length(cfrom ) != 1L ) stop(" 'from' must be of length 1" )
952- tz <- attr(cfrom , " tzone" )
953- if (! missing(to )) {
954- if (! inherits(to , " POSIXt" )) stop(" 'to' must be a \" POSIXt\" object" )
955- if (length(as.POSIXct(to )) != 1 ) stop(" 'to' must be of length 1" )
956- }
957948 if (! missing(along.with )) {
958949 length.out <- length(along.with )
959950 } else if (! is.null(length.out )) {
960- if (length(length.out ) != 1L ) stop(" 'length.out ' must be of length 1" )
951+ if (length(length.out ) != 1L ) stop(gettextf( " '%s ' must be of length 1" , " length.out " ), domain = NA )
961952 length.out <- ceiling(length.out )
962953 }
963- status <- c(! missing(to ), ! missing(by ), ! is.null(length.out ))
964- if (sum(status ) != 2L )
965- stop(" exactly two of 'to', 'by' and 'length.out' / 'along.with' must be specified" )
966- if (missing(by )) {
967- from <- unclass(cfrom )
968- to <- unclass(as.POSIXct(to ))
969- # # Till (and incl.) 1.6.0 :
970- # #- incr <- (to - from)/length.out
971- # #- res <- seq.default(from, to, incr)
954+ missing_arg <- names(which(c(from = missing(from ), to = missing(to ),
955+ length.out = is.null(length.out ), by = missing(by ))))
956+ if (length(missing_arg ) != 1L )
957+ stop(" exactly three of 'to', 'from', 'by' and 'length.out' / 'along.with' must be specified" )
958+ # NB: process 'to' first so that 'tz' is overwritten to that from 'from' unless missing(from)
959+ if (missing_arg != " to" ) {
960+ if (! inherits(to , " POSIXt" )) stop(gettextf(" '%s' must be a \" %s\" object" , " to" , " POSIXt" ), domain = NA )
961+ if (length(to ) != 1L ) stop(gettextf(" '%s' must be of length 1" , " to" ), domain = NA )
962+ cto <- as.POSIXct(to )
963+ tz <- attr(cto , " tzone" )
964+ }
965+ if (missing_arg != " from" ) {
966+ if (! inherits(from , " POSIXt" )) stop(gettextf(" '%s' must be a \" %s\" object" , " from" , " POSIXt" ), domain = NA )
967+ if (length(from ) != 1L ) stop(gettextf(" '%s' must be of length 1" , " from" ), domain = NA )
968+ cfrom <- as.POSIXct(from )
969+ tz <- attr(cfrom , " tzone" )
970+ }
971+ if (missing_arg == " by" ) {
972+ from <- unclass(as.POSIXct(from ))
973+ to <- unclass(as.POSIXct(to ))
972974 res <- seq.int(from , to , length.out = length.out )
973- return (.POSIXct(res , tz ))
975+ return (.POSIXct(res , tz = attr( from , " tzone " ) ))
974976 }
975-
976- if (length(by ) != 1L ) stop(" 'by ' must be of length 1" )
977+ # # else 'by' is not missing
978+ if (length(by ) != 1L ) stop(gettextf( " '%s ' must be of length 1" , " by " ), domain = NA )
977979 valid <- 0L
978980 if (inherits(by , " difftime" )) {
979- by <- switch (attr( by , " units " ), secs = 1 , mins = 60 , hours = 3600 ,
980- days = 86400 , weeks = 7 * 86400 ) * unclass (by )
981+ units( by ) <- " secs"
982+ by <- as.vector (by )
981983 } else if (is.character(by )) {
982984 by2 <- strsplit(by , " " , fixed = TRUE )[[1L ]]
983985 if (length(by2 ) > 2L || length(by2 ) < 1L )
@@ -989,57 +991,50 @@ function(from, to, by, length.out = NULL, along.with = NULL, ...)
989991 if (valid < = 5L ) {
990992 by <- c(1 , 60 , 3600 , 86400 , 7 * 86400 )[valid ]
991993 if (length(by2 ) == 2L ) by <- by * as.integer(by2 [1L ])
992- } else
993- by <- if (length(by2 ) == 2L ) as.integer(by2 [1L ]) else 1
994+ } else # months or longer
995+ by <- if (length(by2 ) == 2L ) as.integer(by2 [1L ]) else 1L
994996 } else if (! is.numeric(by )) stop(" invalid mode for 'by'" )
995997 if (is.na(by )) stop(" 'by' is NA" )
996998
997- if (valid < = 5L ) { # secs, mins, hours, days, weeks
998- from <- unclass(as.POSIXct(from ))
999- if (! is.null(length.out ))
1000- res <- seq.int(from , by = by , length.out = length.out )
1001- else {
1002- to0 <- unclass(as.POSIXct(to ))
1003- # # defeat test in seq.default
1004- res <- seq.int(0 , to0 - from , by ) + from
1005- }
1006- return (.POSIXct(res , tz ))
1007- } else { # months or years or DSTdays or quarters
1008- r1 <- as.POSIXlt(from )
1009- if (valid == 7L ) { # years
1010- if (missing(to )) { # years
1011- yr <- seq.int(r1 $ year , by = by , length.out = length.out )
1012- } else {
1013- to <- as.POSIXlt(to )
1014- yr <- seq.int(r1 $ year , to $ year , by )
1015- }
1016- r1 $ year <- yr
1017- } else if (valid %in% c(6L , 9L )) { # months or quarters
1018- if (valid == 9L ) by <- by * 3
1019- if (missing(to )) {
1020- mon <- seq.int(r1 $ mon , by = by , length.out = length.out )
1021- } else {
1022- to0 <- as.POSIXlt(to )
1023- mon <- seq.int(r1 $ mon , 12 * (to0 $ year - r1 $ year ) + to0 $ mon , by )
1024- }
1025- r1 $ mon <- mon
1026- } else if (valid == 8L ) { # DSTdays
1027- if (! missing(to )) {
1028- # # We might have a short day, so need to over-estimate.
1029- length.out <- 2L + floor((unclass(as.POSIXct(to )) -
1030- unclass(as.POSIXct(from )))/ (by * 86400 ))
1031- }
1032- r1 $ mday <- seq.int(r1 $ mday , by = by , length.out = length.out )
1033- }
1034- r1 $ isdst <- - 1L
1035- res <- as.POSIXct(r1 )
1036- # # now shorten if necessary.
1037- if (! missing(to )) {
1038- to <- as.POSIXct(to )
1039- res <- if (by > 0 ) res [res < = to ] else res [res > = to ]
999+ # if one of secs, mins, hours, days, or weeks
1000+ if (valid < = 5L ) { # days or weeks
1001+ res <- switch (missing_arg ,
1002+ from = seq.int(to = unclass(cto ), by = by , length.out = length.out ),
1003+ to = seq.int(from = unclass(cfrom ), by = by , length.out = length.out ),
1004+ length.out = seq.int(from = unclass(cfrom ), to = unclass(cto ), by = by )
1005+ )
1006+ return (.POSIXct(as.numeric(res ), tz ))
10401007 }
1041- res
1008+ lres <- as.POSIXlt(if (missing_arg != " from" ) from else to )
1009+ if (missing_arg == " length.out" ) lto <- as.POSIXlt(to )
1010+ if (valid == 7L ) { # years
1011+ lres $ year <- switch (missing_arg ,
1012+ from = seq.int(to = lres $ year , by = by , length.out = length.out ),
1013+ to = seq.int(from = lres $ year , by = by , length.out = length.out ),
1014+ length.out = seq.int(from = lres $ year , to = lto $ year , by = by )
1015+ )
1016+ } else if (valid %in% c(6L , 9L )) { # months or quarters
1017+ if (valid == 9L ) by <- by * 3
1018+ lres $ mon <- switch (missing_arg ,
1019+ from = seq.int(to = lres $ mon , by = by , length.out = length.out ),
1020+ to = seq.int(from = lres $ mon , by = by , length.out = length.out ),
1021+ length.out = seq.int(lres $ mon , 12 * (lto $ year - lres $ year ) + lto $ mon , by )
1022+ )
1023+ } else if (valid == 8L ) { # DSTdays
1024+ lres $ mday <- switch (missing_arg ,
1025+ from = seq.int(to = lres $ mday , by = by , length.out = length.out ),
1026+ to = seq.int(from = lres $ mday , by = by , length.out = length.out ),
1027+ # # We might have a short day, so need to over-estimate.
1028+ length.out = seq.int(lres $ mday , by = by ,
1029+ length.out = 2L + floor((unclass(cto ) - unclass(cfrom ))/ (by * 86400 )))
1030+ )
10421031 }
1032+ lres $ isdst <- - 1L
1033+ res <- as.POSIXct(lres )
1034+ if (missing_arg == " length.out" ) # shorten if necessary.
1035+ res [if (by > 0 ) res < = cto else res > = cto ]
1036+ else
1037+ res
10431038}
10441039
10451040# # *very* similar to cut.Date [ ./dates.R ] -- keep in sync!
@@ -1139,7 +1134,7 @@ julian <- function(x, ...) UseMethod("julian")
11391134julian.POSIXt <- function (x , origin = as.POSIXct(" 1970-01-01" , tz = " GMT" ), ... )
11401135{
11411136 origin <- as.POSIXct(origin )
1142- if (length(origin ) != 1L ) stop(" 'origin ' must be of length one " )
1137+ if (length(origin ) != 1L ) stop(gettextf( " '%s ' must be of length 1 " , " origin " ), domain = NA )
11431138 res <- difftime(as.POSIXct(x ), origin , units = " days" )
11441139 structure(res , " origin" = origin )
11451140}
0 commit comments