is_nonna() and the nna*() functions
is_nonna.Rd
A set of functions for direct manipulation of the non-NA elements of an array-like object.
Arguments
- x
Typically (but not necessarily) an array-like object that is non-NA sparse, like an NaArray object.
However,
x
can also be an ordinary matrix or array, or any matrix-like or array-like object.- arr.ind
If
arr.ind=FALSE
(the default), the indices of the non-NA array elements are returned in a numeric vector (a.k.a. L-index). Otherwise, they're returned in an ordinary matrix (a.k.a. M-index).See
?Lindex
in the S4Arrays package for more information about L-index and M-index, and how to convert from one to the other.Note that using
arr.ind=TRUE
won't work ifnnacount(x)
is >=.Machine$integer.max
(= 2^31), because, in that case, the returned M-index would need to be a matrix with more rows than what is supported by base R.- value
A vector, typically of length
nnacount(x)
(or 1) and typetype(x)
.
Details
nnacount(x)
and nnawhich(x)
are equivalent to, but
typically more efficient than, sum(is_nonna(x))
and
which(is_nonna(x))
, respectively.
nnavals(x)
is equivalent to, but typically more efficient than,
x[nnawhich(x)]
(or x[is_nonna(x)]
).
nnavals(x) <- value
replaces the values of the non-NA array
elements in x
with the supplied values. It's equivalent to,
but typically more efficient than, x[nnawhich(x)] <- value
.
Note that nnavals(x) <- nnavals(x)
is guaranteed to be a no-op.
Value
is_nonna()
: An array-like object of type()
"logical"
and same dimensions as the input object.
nnacount()
: The number of non-NA array elements in x
.
nnawhich()
: The indices of the non-NA array elements in x
,
either as an L-index (if arr.ind
is FALSE
) or as
an M-index (if arr.ind
is TRUE
).
Note that the indices are returned sorted in strictly ascending order.
nnavals()
: A vector of the same type()
as x
and
containing the values of the non-NA array elements in x
.
Note that the returned vector is guaranteed to be parallel
to nnawhich(x)
.
See also
is_nonzero for
is_nonzero()
andnz*()
functionsnzcount()
,nzwhich()
, etc...NaArray objects.
Ordinary array objects in base R.
base::which
in base R.
Examples
a <- array(NA_integer_, dim=c(5, 12, 2))
a[sample(length(a), 20)] <- (-9):10
is_nonna(a)
#> , , 1
#>
#> [,1] [,2] [,3] [,4] [,5] [,6] [,7] [,8] [,9] [,10] [,11] [,12]
#> [1,] FALSE FALSE FALSE FALSE FALSE FALSE TRUE FALSE TRUE FALSE FALSE TRUE
#> [2,] FALSE FALSE FALSE FALSE FALSE FALSE TRUE FALSE FALSE FALSE FALSE TRUE
#> [3,] FALSE TRUE FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE TRUE TRUE
#> [4,] FALSE TRUE FALSE TRUE FALSE FALSE FALSE FALSE TRUE FALSE FALSE FALSE
#> [5,] FALSE FALSE FALSE FALSE FALSE TRUE TRUE FALSE TRUE FALSE FALSE FALSE
#>
#> , , 2
#>
#> [,1] [,2] [,3] [,4] [,5] [,6] [,7] [,8] [,9] [,10] [,11] [,12]
#> [1,] FALSE FALSE FALSE TRUE FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE
#> [2,] FALSE FALSE FALSE TRUE FALSE FALSE FALSE FALSE FALSE TRUE FALSE TRUE
#> [3,] FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE
#> [4,] FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE TRUE FALSE FALSE
#> [5,] FALSE FALSE FALSE FALSE FALSE FALSE FALSE FALSE TRUE FALSE FALSE FALSE
#>
## Get the number of non-NA array elements in 'a':
nnacount(a)
#> [1] 20
## nnawhich() returns the indices of the non-NA array elements in 'a'.
## Either as a "L-index" i.e. an integer (or numeric) vector of
## length 'nnacount(a)' containing "linear indices":
nnaidx <- nnawhich(a)
length(nnaidx)
#> [1] 20
head(nnaidx)
#> [1] 8 9 19 30 31 32
## Or as an "M-index" i.e. an integer matrix with 'nnacount(a)' rows
## and one column per dimension where the rows represent "array indices"
## (a.k.a. "array coordinates"):
Mnnaidx <- nnawhich(a, arr.ind=TRUE)
dim(Mnnaidx)
#> [1] 20 3
## Each row in the matrix is an n-tuple representing the "array
## coordinates" of a non-NA element in 'a':
head(Mnnaidx)
#> [,1] [,2] [,3]
#> [1,] 3 2 1
#> [2,] 4 2 1
#> [3,] 4 4 1
#> [4,] 5 6 1
#> [5,] 1 7 1
#> [6,] 2 7 1
tail(Mnnaidx)
#> [,1] [,2] [,3]
#> [15,] 1 4 2
#> [16,] 2 4 2
#> [17,] 5 9 2
#> [18,] 2 10 2
#> [19,] 4 10 2
#> [20,] 2 12 2
## Extract the values of the non-NA array elements in 'a' and return
## them in a vector "parallel" to 'nnawhich(a)':
a_nnavals <- nnavals(a) # equivalent to 'a[nnawhich(a)]'
length(a_nnavals)
#> [1] 20
head(a_nnavals)
#> [1] 5 -6 2 7 0 -4
nnavals(a) <- 10 ^ nnavals(a)
a
#> , , 1
#>
#> [,1] [,2] [,3] [,4] [,5] [,6] [,7] [,8] [,9] [,10] [,11] [,12]
#> [1,] NA NA NA NA NA NA 1e+00 NA 1e-01 NA NA 1e+03
#> [2,] NA NA NA NA NA NA 1e-04 NA NA NA NA 1e+08
#> [3,] NA 1e+05 NA NA NA NA NA NA NA NA 1e-05 1e+09
#> [4,] NA 1e-06 NA 100 NA NA NA NA 1e+06 NA NA NA
#> [5,] NA NA NA NA NA 1e+07 1e-07 NA 1e+10 NA NA NA
#>
#> , , 2
#>
#> [,1] [,2] [,3] [,4] [,5] [,6] [,7] [,8] [,9] [,10] [,11] [,12]
#> [1,] NA NA NA 1e+04 NA NA NA NA NA NA NA NA
#> [2,] NA NA NA 1e-09 NA NA NA NA NA 0.010 NA 1e-08
#> [3,] NA NA NA NA NA NA NA NA NA NA NA NA
#> [4,] NA NA NA NA NA NA NA NA NA 0.001 NA NA
#> [5,] NA NA NA NA NA NA NA NA 10 NA NA NA
#>
## Sanity checks:
stopifnot(
identical(nnaidx, which(!is.na(a))),
identical(Mnnaidx, which(!is.na(a), arr.ind=TRUE, useNames=FALSE)),
identical(nnavals(a), a[nnaidx]),
identical(nnavals(a), a[Mnnaidx]),
identical(`nnavals<-`(a, nnavals(a)), a)
)