Skip to content

Commit 2feac49

Browse files
yanboliangshivaram
authored andcommitted
[SPARK-12044][SPARKR] Fix usage of isnan, isNaN
1, Add ```isNaN``` to ```Column``` for SparkR. ```Column``` should has three related variable functions: ```isNaN, isNull, isNotNull```. 2, Replace ```DataFrame.isNaN``` with ```DataFrame.isnan``` at SparkR side. Because ```DataFrame.isNaN``` has been deprecated and will be removed at Spark 2.0. <del>3, Add ```isnull``` to ```DataFrame``` for SparkR. ```DataFrame``` should has two related functions: ```isnan, isnull```.<del> cc shivaram sun-rui felixcheung Author: Yanbo Liang <ybliang8@gmail.com> Closes #10037 from yanboliang/spark-12044. (cherry picked from commit b6e8e63) Signed-off-by: Shivaram Venkataraman <shivaram@cs.berkeley.edu>
1 parent 04dfaa6 commit 2feac49

File tree

4 files changed

+31
-11
lines changed

4 files changed

+31
-11
lines changed

R/pkg/R/column.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -56,7 +56,7 @@ operators <- list(
5656
"&" = "and", "|" = "or", #, "!" = "unary_$bang"
5757
"^" = "pow"
5858
)
59-
column_functions1 <- c("asc", "desc", "isNull", "isNotNull")
59+
column_functions1 <- c("asc", "desc", "isNaN", "isNull", "isNotNull")
6060
column_functions2 <- c("like", "rlike", "startsWith", "endsWith", "getField", "getItem", "contains")
6161

6262
createOperator <- function(op) {

R/pkg/R/functions.R

Lines changed: 19 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -537,19 +537,31 @@ setMethod("initcap",
537537
column(jc)
538538
})
539539

540-
#' isNaN
540+
#' is.nan
541541
#'
542-
#' Return true iff the column is NaN.
542+
#' Return true if the column is NaN, alias for \link{isnan}
543543
#'
544-
#' @rdname isNaN
545-
#' @name isNaN
544+
#' @rdname is.nan
545+
#' @name is.nan
546546
#' @family normal_funcs
547547
#' @export
548-
#' @examples \dontrun{isNaN(df$c)}
549-
setMethod("isNaN",
548+
#' @examples
549+
#' \dontrun{
550+
#' is.nan(df$c)
551+
#' isnan(df$c)
552+
#' }
553+
setMethod("is.nan",
554+
signature(x = "Column"),
555+
function(x) {
556+
isnan(x)
557+
})
558+
559+
#' @rdname is.nan
560+
#' @name isnan
561+
setMethod("isnan",
550562
signature(x = "Column"),
551563
function(x) {
552-
jc <- callJStatic("org.apache.spark.sql.functions", "isNaN", x@jc)
564+
jc <- callJStatic("org.apache.spark.sql.functions", "isnan", x@jc)
553565
column(jc)
554566
})
555567

R/pkg/R/generics.R

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -625,6 +625,10 @@ setGeneric("getField", function(x, ...) { standardGeneric("getField") })
625625
#' @export
626626
setGeneric("getItem", function(x, ...) { standardGeneric("getItem") })
627627

628+
#' @rdname column
629+
#' @export
630+
setGeneric("isNaN", function(x) { standardGeneric("isNaN") })
631+
628632
#' @rdname column
629633
#' @export
630634
setGeneric("isNull", function(x) { standardGeneric("isNull") })
@@ -808,9 +812,9 @@ setGeneric("initcap", function(x) { standardGeneric("initcap") })
808812
#' @export
809813
setGeneric("instr", function(y, x) { standardGeneric("instr") })
810814

811-
#' @rdname isNaN
815+
#' @rdname is.nan
812816
#' @export
813-
setGeneric("isNaN", function(x) { standardGeneric("isNaN") })
817+
setGeneric("isnan", function(x) { standardGeneric("isnan") })
814818

815819
#' @rdname kurtosis
816820
#' @export

R/pkg/inst/tests/test_sparkSQL.R

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -883,7 +883,7 @@ test_that("column functions", {
883883
c2 <- avg(c) + base64(c) + bin(c) + bitwiseNOT(c) + cbrt(c) + ceil(c) + cos(c)
884884
c3 <- cosh(c) + count(c) + crc32(c) + exp(c)
885885
c4 <- explode(c) + expm1(c) + factorial(c) + first(c) + floor(c) + hex(c)
886-
c5 <- hour(c) + initcap(c) + isNaN(c) + last(c) + last_day(c) + length(c)
886+
c5 <- hour(c) + initcap(c) + last(c) + last_day(c) + length(c)
887887
c6 <- log(c) + (c) + log1p(c) + log2(c) + lower(c) + ltrim(c) + max(c) + md5(c)
888888
c7 <- mean(c) + min(c) + month(c) + negate(c) + quarter(c)
889889
c8 <- reverse(c) + rint(c) + round(c) + rtrim(c) + sha1(c)
@@ -894,6 +894,10 @@ test_that("column functions", {
894894
c13 <- lead("col", 1) + lead(c, 1) + lag("col", 1) + lag(c, 1)
895895
c14 <- cume_dist() + ntile(1) + corr(c, c1)
896896
c15 <- dense_rank() + percent_rank() + rank() + row_number()
897+
c16 <- is.nan(c) + isnan(c) + isNaN(c)
898+
899+
# Test if base::is.nan() is exposed
900+
expect_equal(is.nan(c("a", "b")), c(FALSE, FALSE))
897901

898902
# Test if base::rank() is exposed
899903
expect_equal(class(rank())[[1]], "Column")

0 commit comments

Comments
 (0)