[Rd] identical(0, -0)

Duncan Murdoch murdoch at stats.uwo.ca
Mon Aug 10 17:51:53 CEST 2009


For people who want to play with these, here are some functions that let 
you get or set the "payload" value in a NaN.  NaN and NA, Inf and -Inf 
are stored quite similarly; these functions don't distinguish which of 
those you're working with.  Regular finite values give NA for the 
payload value, and elements of x are unchanged if you try to set their 
payload to NA.

By the way, this also shows that R *can* distinguish different NaN 
values, but you need some byte-level manipulations.

Duncan Murdoch

showBytes <- function(x) {
     bytes <- rawConnection(raw(0), "w")
     on.exit(close(bytes))
     writeBin(x, bytes)
     rawConnectionValue(bytes)
}

NaNpayload <- function(x) {
     if (typeof(x) != "double") stop("Can only handle doubles")
     bytes <- as.integer(showBytes(x))
     base <- 1 + (seq_along(x)-1)*8
     S <- bytes[base + 7] %/% 128
     E <- (bytes[base + 7] %% 128)*16 + bytes[base + 6] %/% 16
     F <- bytes[base + 6] %% 16
     for (i in 5:0) {
     	F <- F*256 + bytes[base + i]
     }
     nan <- E == 2047 # Add " & F != 0 " if you don't want to include 
infinities
     ifelse(nan, (1-2*S)*F/2^52, NA)
}

"NaNpayload<-" <- function(x, value) {
     x <- as.double(x)
     payload <- value
     new <- payload[!is.na(payload)]
     if (any( new <= -1 | new >= 1 )) stop("The payload values must be 
between -1 and 1")
     payload <- rep(payload, len=max(length(x), length(payload)))
     x <- rep(x, len=length(payload))

     bytes <- as.integer(showBytes(x))
     base <- 1 + (seq_along(x)-1)*8
     base[is.na(payload)] <- NA
     F <- trunc(abs(payload)*2^52)
     for (i in 0:5) {
     	bytes[base + i] <- F %% 256
     	F <- F %/% 256
     }
     bytes[base + 6] <- F + 0xF0
     bytes[base + 7] <- (payload < 0)*128 + 0x7F
     con <- rawConnection(as.raw(bytes), "r")
     on.exit(close(con))
     readBin(con, "double", length(x))
}

Example:

 > x <- c(NA, NaN, 0, 1, Inf)
 > NaNpayload(x)
[1]  0.5 -0.5   NA   NA  0.0
 > NaNpayload(x) <- -0.4
 > x
[1] NaN NaN NaN NaN NaN
 > y <- x
 > NaNpayload(y) <- 0.6
 > y
[1] NaN NaN NaN NaN NaN
 > NaNpayload(x)
[1] -0.4 -0.4 -0.4 -0.4 -0.4
 > NaNpayload(y)
[1] 0.6 0.6 0.6 0.6 0.6
 > identical(x, y)
[1] TRUE



More information about the R-devel mailing list