New S4 woes in r-devel
@kurthornik emails to note the now two fails under r-devel (I had notived one of these a few days ago, I think those machines are not a full daily schedule). In a follow-up email he mentions that this is from r88019 and suggests liasing with @mmaechler as needed.
Ok, back from a morning run and with a little triage, I can get it to pass R 4.5.0 by skipping (for now) two segments (see below). I will probably commit this as we have a hard deadline here (April 15 or death) but we of course should also see if we can smarten the Ops up for R 4.5.0.
modified inst/tinytest/test_nanoduration.R
@@ -364,7 +364,7 @@ expect_error(as.nanoduration(1) | "a",
expect_error("a" & as.nanoduration(1),
"operations are possible only for numeric, logical or complex types")
-
+## N=129
## Math
##test_abs <- function() {
expect_identical(abs(as.nanoduration(-1)), as.nanoduration(1))
@@ -394,6 +394,7 @@ expect_error(as.nanoduration(1) < "a", "cannot parse nanoduration")
## > 1 == list(1)
## [1] TRUE
+# N=135
##test_Compare_ANY_nanoduration <- function() {
expect_error("a" < as.nanoduration(1), "cannot parse nanoduration")
@@ -410,20 +411,22 @@ expect_true("12:13:14.151617001" > as.nanoduration("12:13:14.151617"))
expect_false("12:13:14.151617" > as.nanoduration("12:13:14.151617001"))
expect_true("12:13:14.151617" >= as.nanoduration("12:13:14.151617"))
expect_false("12:13:14.151617" >= as.nanoduration("12:13:14.151617001"))
-
-##test_Compare_nanoduration_character <- function() {
-expect_true(as.nanoduration("12:13:14.151617") == "12:13:14.151617")
-expect_false(as.nanoduration("12:13:14.151617") == "12:13:14.151617001")
-expect_true(as.nanoduration("12:13:14.151617") != "12:13:14.151617001")
-expect_false(as.nanoduration("12:13:14.151617") != "12:13:14.151617")
-expect_true(as.nanoduration("12:13:14.151617") < "12:13:14.151617001")
-expect_false(as.nanoduration("12:13:14.151617001") < "12:13:14.151617")
-expect_true(as.nanoduration("12:13:14.151617") <= "12:13:14.151617")
-expect_false(as.nanoduration("12:13:14.151617001") <= "12:13:14.151617")
-expect_true(as.nanoduration("12:13:14.151617001") > "12:13:14.151617")
-expect_false(as.nanoduration("12:13:14.151617") > "12:13:14.151617001")
-expect_true(as.nanoduration("12:13:14.151617") >= "12:13:14.151617")
-expect_false(as.nanoduration("12:13:14.151617") >= "12:13:14.151617001")
+
+if (getRversion() < "4.5.0") {
+ ##test_Compare_nanoduration_character <- function() {
+ expect_true(as.nanoduration("12:13:14.151617") == "12:13:14.151617")
+ expect_false(as.nanoduration("12:13:14.151617") == "12:13:14.151617001")
+ expect_true(as.nanoduration("12:13:14.151617") != "12:13:14.151617001")
+ expect_false(as.nanoduration("12:13:14.151617") != "12:13:14.151617")
+ expect_true(as.nanoduration("12:13:14.151617") < "12:13:14.151617001")
+ expect_false(as.nanoduration("12:13:14.151617001") < "12:13:14.151617")
+ expect_true(as.nanoduration("12:13:14.151617") <= "12:13:14.151617")
+ expect_false(as.nanoduration("12:13:14.151617001") <= "12:13:14.151617")
+ expect_true(as.nanoduration("12:13:14.151617001") > "12:13:14.151617")
+ expect_false(as.nanoduration("12:13:14.151617") > "12:13:14.151617001")
+ expect_true(as.nanoduration("12:13:14.151617") >= "12:13:14.151617")
+ expect_false(as.nanoduration("12:13:14.151617") >= "12:13:14.151617001")
+}
## Arith
##test_Arith <- function() {
modified inst/tinytest/test_nanotime.R
@@ -513,6 +513,7 @@ expect_false(nanotime(1) >= nanotime(2))
expect_true(nanotime(1) < nanotime(2))
expect_false(nanotime(1) > nanotime(2))
+# N=172
## with character
expect_true(nanotime(1) == nanotime("1970-01-01T00:00:00.000000001+00"))
expect_true(nanotime("1970-01-01T00:00:00.000000001+00") != nanotime(2))
@@ -523,18 +524,20 @@ expect_false(nanotime("1970-01-01T00:00:00.000000001+00") >= nanotime(2))
expect_true(nanotime(1) < nanotime("1970-01-01T00:00:00.000000002+00"))
expect_false(nanotime("1970-01-01T00:00:00.000000001+00") > nanotime(2))
-## with POSIXt
-pt1 <- as.POSIXct(1, origin="1970-01-01", tz="UTC")
-pt2 <- as.POSIXct(2, origin="1970-01-01", tz="UTC")
-expect_true(pt1 == nanotime("1970-01-01T00:00:01+00"))
-expect_true(nanotime("1970-01-01T00:00:01+00") != pt2)
-expect_true(nanotime("1970-01-01T00:00:01+00") <= pt1)
-expect_true(nanotime("1970-01-01T00:00:01+00") >= pt1)
-expect_true(nanotime(1) <= nanotime("1970-01-01T00:00:02+00"))
-expect_false(nanotime("1970-01-01T00:00:01+00") >= pt2)
-expect_true(nanotime(1) < nanotime("1970-01-01T00:00:00.000000002+00"))
-expect_false(nanotime("1970-01-01T00:00:01+00") > pt2)
-
+# N=180
+if (getRversion() < "4.5.0") {
+ ## with POSIXt
+ pt1 <- as.POSIXct(1, origin="1970-01-01", tz="UTC")
+ pt2 <- as.POSIXct(2, origin="1970-01-01", tz="UTC")
+ expect_true(pt1 == nanotime("1970-01-01T00:00:01+00"))
+ expect_true(nanotime("1970-01-01T00:00:01+00") != pt2)
+ expect_true(nanotime("1970-01-01T00:00:01+00") <= pt1)
+ expect_true(nanotime("1970-01-01T00:00:01+00") >= pt1)
+ expect_true(nanotime(1) <= nanotime("1970-01-01T00:00:02+00"))
+ expect_false(nanotime("1970-01-01T00:00:01+00") >= pt2)
+ expect_true(nanotime(1) < nanotime("1970-01-01T00:00:00.000000002+00"))
+ expect_false(nanotime("1970-01-01T00:00:01+00") > pt2)
+}
## all.equal
##test_all.equal_nanotime_any <- function() {
Honestly, I'm baffled about the effect of that relatively small S4 / methods package change (I have authored). I'm busy almost all day (again), but am happy to help, as indeed, this effect is surprising to me. In case you can drill it down to "base+methods"-only, I'd be even happier to help ..
We can't do "base+methods" but this aims to be pretty standard (if extensive !!) S4 use. The package wraps both my RcppCCTZ (a C++ library used and developed at Google to modernize C/C++ level time operations down to nanoseconds, I packaged that maybe a decade ago and as CRAN allows it there are by now three or more needless vendored copies including at least twice in that *verse) as well as bit64 to allow us to use nanoseconds since epoch. Those are the building blocks.
@lsilvest took what I once wrote much more modestly in S3 and solidified it greatly with S4 semantics. But as you know, those can somewhat fragile under change so we have been updating these quite a bit over the years. The code is all in the R/ directory here.
Now, for the failing tests, in R-devel I see
> library(nanotime)
> as.nanoduration("12:13:14.151617")
[1] 12:13:14.151_617
>
which differs from the expected "12:13:14.151617" by the addition of an underscore. Does that ring a bell with you? I do not think we changed our formatting methods.
Ditto for the second test file:
> pt1 <- as.POSIXct(1, origin="1970-01-01", tz="UTC")
> pt1
[1] "1970-01-01 00:00:01 UTC"
> nt <- nanotime("1970-01-01T00:00:01+00")
> nt
[1] 1970-01-01T00:00:01+00:00
pt2 <- as.POSIXct(nt, tz="UTC")
> pt2
[1] "1970-01-01 00:00:01 UTC"
>
~which is another (suble) change in the formatting. Is that you, or did Kurt point the wrong finger?~ )Disregard that, now edited)
and it is not clear why the comparison fails. I may have to dig into that one line by line.
Under R-release all 1250 tests pass as expected.
edd@rob:~/git/nanotime(master)$ Rscript tests/tinytest.R
test_data.frame.R............. 16 tests OK 0.1s
test_data.table.R............. 16 tests OK 80ms
test_nanoduration.R........... 252 tests OK 0.2s
test_nanoival.R............... 304 tests OK 0.5s
test_nanoperiod.R............. 336 tests OK 0.1s
test_nanotime.R............... 267 tests OK 0.2s
test_ops.R.................... 58 tests OK 52ms
test_xts.R.................... 0 tests 1ms [Exited at #43: Skip xts tests for now]
test_zoo.R.................... 1 tests OK 8ms
All ok, 1250 results (1.3s)
edd@rob:~/git/nanotime(master)$
Turns out the underscore is us in routine to_string called from the converter duration_to_string_impl (both in src/duration.cpp). So maybe R 4.5.0 changes the dispatching flow and now we are getting what we were supposed to get all along? Weird. @lsilvest I will let you chime in :)
Yes, all this is strange. I'm taking a look.
@lsilvest : thank you in advance;
@jaganmn may be interested as in R Bugzilla's PR#18823 which lead to the methods package fix .. that seems to have "broken" nanotime (or on of its dependencies) somehow, puzzingly
Thanks, I will look today ...
Thank you @jaganmn -- it's all in the ticket here: nanotime implements S4 ops, and under r-devel two segments of our unit tests differ. (Underneath are RcppCCTZ for time/data ops in C++ and bit64 for the integer64 we need for all this).
So I can reproduce the error but the twist is that it only happens on the second function call. To recap, we have the following two S4 Compare functions for nanoduration (I added the print functions for debugging):
##' @rdname nanoduration
setMethod("Compare", c("nanoduration", "character"),
function(e1, e2) {
print('calling setMethod("Compare", c("nanoduration", "character")')
ne2 <- as.nanoduration(e2)
callNextMethod(e1, ne2)
})
##' @rdname nanoduration
setMethod("Compare", c("character", "nanoduration"),
function(e1, e2) {
print('calling setMethod("Compare", c("character", "nanoduration")')
ne1 <- as.nanoduration(e1)
callNextMethod(ne1, e2)
})
The issue is only with the "nanoduration", "character" function, and interestingly only on the second call:
R version 4.5.0 alpha (2025-03-24 r88048)
Copyright (C) 2025 The R Foundation for Statistical Computing
Platform: x86_64-pc-linux-gnu
R is free software and comes with ABSOLUTELY NO WARRANTY.
You are welcome to redistribute it under certain conditions.
Type 'license()' or 'licence()' for distribution details.
Natural language support but running in an English locale
R is a collaborative project with many contributors.
Type 'contributors()' for more information and
'citation()' on how to cite R or R packages in publications.
Type 'demo()' for some demos, 'help()' for on-line help, or
'help.start()' for an HTML browser interface to help.
Type 'q()' to quit R.
> library(nanotime)
> as.nanoduration("12:13:14.151617") == "12:13:14.151617"
[1] "calling setMethod(\"Compare\", c(\"nanoduration\", \"character\")"
[1] TRUE
attr(,".S3Class")
[1] "integer64"
> as.nanoduration("12:13:14.151617") == "12:13:14.151617"
[1] "calling setMethod(\"Compare\", c(\"nanoduration\", \"character\")"
Error in validObject(.Object) :
invalid class “MethodWithNext” object: invalid object for slot "nextMethod" in class "MethodWithNext": got class "NULL", should be or extend class "PossibleMethod"
I need to get deeper into the callNextMethod function, but wondering if the above behavior suggests anything?
I'm sorry if I am completely misunderstanding, but shouldn't those methods be calling callGeneric and not callNextMethod ... ??
Edit: Well, be that as it may, I see that there is a next method, so I'll continue digging into why callNextMethod is no longer behaving as before.
It does work with callGeneric, but the idea was it would be more efficient with callNextMethod because nanoduration is defined as setClass("nanoduration", contains = "integer64") and the understanding was that continuing the method resolution would yield the integer64 method. Up until now this has seemed to be a correct interpretation.
So specifically, we have:
Compare(character, nanoduration): callNextMethod seems to correctly reach Compare(character, integer64)
Compare(nanoduration, character): callNextMethod only reaches Compare(integer64, character) on the first call and fails on the second call.
I have also checked that this problem is also present for the class nanotime which also defines a Compare in that way.
Minimal example:
> setClass("zzz", contains = "character")
> setMethod("Compare", c(e1 = "zzz", e2 = "zzz"), function(e1, e2) callNextMethod(e1, getDataPart(e2)))
> setMethod("Compare", c(e1 = "zzz", e2 = "ANY"), function(e1, e2) callNextMethod(getDataPart(e1), e2))
> x <- new("zzz")
> x == x
logical(0)
> x == x
Error in validObject(.Object) :
invalid class "MethodWithNext" object: invalid object for slot "nextMethod" in class "MethodWithNext": got class "NULL", should be or extend class "PossibleMethod"
My feeling is that the patch for bug 18823 (r87971, r88019) needs further refinement and that no change should be required in nanotime. @mmaechler The cause seems to be that, currently, the method for loadMethod with signature method="MethodDefinition" assigns to .Generic the name of the group generic function ("Compare") instead of the name of the member generic function ("=="). This change breaks the second call to callNextMethod. (Note that it is documented that, due to method caching, the second call behaves differently.) We can discuss further by e-mail ...
Indeed, I've converged on a simple patch for R-devel that unbreaks nanotime, so you should be in the clear pending review/adjustment by Martin.
You. Are. The. Man.
Thanks so much for unclogging this!
Yes, @jaganmn's proposed change makes a lot of sense, just from code reading and does solve the problem.
So, nanotime is "good" again after my commit svn r88055 (the CRAN version , i.e., no need for Dirk's https://github.com/eddelbuettel/nanotime/issues/138#issuecomment-2751039974 ).
Rebuilt R-devel and can confirm CRAN nanotime behaves under the now-amended-and-refined R-devel.
Will leave this (now known as 'non-issue') open until the issue cleared at CRAN too and close it then as 'not planned'.
Dirk Eddelbuettel writes:
Thx: I just closed the CRAN issue.
Rebuilt R-devel and can confirm CRAN nanotime behaves under the now-amended-and-refined R-devel.
Will leave this (now known as 'non-issue') open until the issue cleared at CRAN too and close it then as 'not planned'.
— Reply to this email directly, view it on GitHub, or unsubscribe. You are receiving this because you were mentioned.Message ID: <eddelbuettel/ @.**>
ededdelbuettel left a comment (eddelbuettel/nanotime#138)
Rebuilt R-devel and can confirm CRAN nanotime behaves under the now-amended-and-refined R-devel.
Will leave this (now known as 'non-issue') open until the issue cleared at CRAN too and close it then as 'not planned'.
— Reply to this email directly, view it on GitHub, or unsubscribe. You are receiving this because you were mentioned.Message ID: <eddelbuettel/ @.**>
Thank you @kurthornik . When I checked last night I still had five fails, now down to four so that may be a lagging count. I need to update the package anyway for another small nag (on the demo/ being scanned now) but I may wait for this ERROR count to go down first.
Dirk Eddelbuettel writes:
Thank you @kurthornik . When I checked last night I still had five fails, now down to four so that may be a lagging count. I need to update the package anyway for another small nag (on the demo/ being scanned now) but I may wait for this ERROR count to go down first.
Thx. Yes, I know :-)
Best -k
— Reply to this email directly, view it on GitHub, or unsubscribe. You are receiving this because you were mentioned.Message ID: <eddelbuettel/ @.**>
ededdelbuettel left a comment (eddelbuettel/nanotime#138)
Thank you @kurthornik . When I checked last night I still had five fails, now down to four so that may be a lagging count. I need to update the package anyway for another small nag (on the demo/ being scanned now) but I may wait for this ERROR count to go down first.
— Reply to this email directly, view it on GitHub, or unsubscribe. You are receiving this because you were mentioned.Message ID: <eddelbuettel/ @.**>
Note that you may not see a resolution for every one of the check flavours because @mmaechler hasn't yet ported the patch (r88055) to R 4.5.0 beta. And, for whatever reason, the check output for r-devel-windows-x86_64 shows that it used R 4.5.0 alpha (r88060).
I did port it to R 4.5.0 beta 3 (three!) days ago (88070) .. but the 3 current failures still all use older versions of "R-pre-release".
Thanks for confirming that, @mmaechler. These days I keep an open tab with 'my' report aggregation and I saw it trailing. In a week's time, I hope, we can see it gone.
This got sorted out so the issue is now stale and can be closed.