[GitHub] spark pull request #17783: [SPARK-20490][SPARKR][WIP] Add R wrappers for eqN...

2017-04-29 Thread felixcheung
Github user felixcheung commented on a diff in the pull request:

https://github.com/apache/spark/pull/17783#discussion_r114067173
  
--- Diff: R/pkg/R/column.R ---
@@ -302,3 +301,56 @@ setMethod("otherwise",
 jc <- callJMethod(x@jc, "otherwise", value)
 column(jc)
   })
+
+#' \%<=>\%
+#'
+#' Equality test that is safe for null values.
+#'
+#' Can be used, unlike standard equality operator, to perform null-safe 
joins.
+#' Equivalent to Scala \code{Column.<=>} and \code{Column.eqNullSafe}.
+#'
+#' @param x a Column
+#' @param value a value to compare
+#' @rdname eq_null_safe
+#' @name %<=>%
+#' @aliases %<=>%,Column-method
+#' @export
+#' @examples
+#' \dontrun{
+#' df1 <- createDataFrame(data.frame(
+#'   x = c(1, NA, 3, NA), y = c(2, 6, 3, NA)
+#' ))
+#'
+#' head(select(df1, df1$x == df1$y, df1$x %<=>% df1$y))
+#'
+#' df2 <- createDataFrame(data.frame(y = c(3, NA)))
+#' count(join(df1, df2, df1$y == df2$y))
+#'
+#' count(join(df1, df2, df1$y %<=>% df2$y))
+#' }
+#' @note \%<=>\% since 2.3.0
+setMethod("%<=>%",
+  signature(x = "Column", value = "ANY"),
+  function(x, value) {
+value <- if (class(value) == "Column") { value@jc } else { 
value }
+jc <- callJMethod(x@jc, "eqNullSafe", value)
+column(jc)
+  })
+
+#' !
+#'
+#' Inversion of boolean expression.
+#'
+#' @rdname not
+#' @name not
+#' @aliases !,Column-method
+#' @export
+#' @examples
+#' \dontrun{
+#' df <- createDataFrame(data.frame(x = c(-1, 0, 1)))
+#'
+#' head(select(df, !column("x") > 0))
+#' }
+#' @note ! since 2.3.0
+#' @seealso \link{not}
--- End diff --

we don't need this since `@rdname not` - they both go to the same html page


---
If your project is set up for it, you can reply to this email and have your
reply appear on GitHub as well. If your project does not have this feature
enabled and wishes so, or if the feature is enabled but not working, please
contact infrastructure at infrastruct...@apache.org or file a JIRA ticket
with INFRA.
---

-
To unsubscribe, e-mail: reviews-unsubscr...@spark.apache.org
For additional commands, e-mail: reviews-h...@spark.apache.org



[GitHub] spark pull request #17783: [SPARK-20490][SPARKR][WIP] Add R wrappers for eqN...

2017-04-29 Thread felixcheung
Github user felixcheung commented on a diff in the pull request:

https://github.com/apache/spark/pull/17783#discussion_r114058191
  
--- Diff: R/pkg/R/column.R ---
@@ -67,8 +67,7 @@ operators <- list(
   "+" = "plus", "-" = "minus", "*" = "multiply", "/" = "divide", "%%" = 
"mod",
   "==" = "equalTo", ">" = "gt", "<" = "lt", "!=" = "notEqual", "<=" = 
"leq", ">=" = "geq",
   # we can not override `&&` and `||`, so use `&` and `|` instead
-  "&" = "and", "|" = "or", #, "!" = "unary_$bang"
-  "^" = "pow"
+  "&" = "and", "|" = "or", "^" = "pow"
--- End diff --

actually, let me back track... it looks like `"!" = "unary_$bang"` has 
always been commented out. the `#, ` does that
I agree we don't need to leave that comment here


---
If your project is set up for it, you can reply to this email and have your
reply appear on GitHub as well. If your project does not have this feature
enabled and wishes so, or if the feature is enabled but not working, please
contact infrastructure at infrastruct...@apache.org or file a JIRA ticket
with INFRA.
---

-
To unsubscribe, e-mail: reviews-unsubscr...@spark.apache.org
For additional commands, e-mail: reviews-h...@spark.apache.org



[GitHub] spark pull request #17783: [SPARK-20490][SPARKR][WIP] Add R wrappers for eqN...

2017-04-28 Thread zero323
Github user zero323 commented on a diff in the pull request:

https://github.com/apache/spark/pull/17783#discussion_r113992412
  
--- Diff: R/pkg/R/column.R ---
@@ -67,8 +67,7 @@ operators <- list(
   "+" = "plus", "-" = "minus", "*" = "multiply", "/" = "divide", "%%" = 
"mod",
   "==" = "equalTo", ">" = "gt", "<" = "lt", "!=" = "notEqual", "<=" = 
"leq", ">=" = "geq",
   # we can not override `&&` and `||`, so use `&` and `|` instead
-  "&" = "and", "|" = "or", #, "!" = "unary_$bang"
-  "^" = "pow"
+  "&" = "and", "|" = "or", "^" = "pow"
--- End diff --

Since this PR implements `!` I think it is just confusing, don't you? Not 
to mention that `createOperator` didn't work with `!`. I can restore it if you 
believe it serves some purpose.


---
If your project is set up for it, you can reply to this email and have your
reply appear on GitHub as well. If your project does not have this feature
enabled and wishes so, or if the feature is enabled but not working, please
contact infrastructure at infrastruct...@apache.org or file a JIRA ticket
with INFRA.
---

-
To unsubscribe, e-mail: reviews-unsubscr...@spark.apache.org
For additional commands, e-mail: reviews-h...@spark.apache.org



[GitHub] spark pull request #17783: [SPARK-20490][SPARKR][WIP] Add R wrappers for eqN...

2017-04-28 Thread zero323
Github user zero323 commented on a diff in the pull request:

https://github.com/apache/spark/pull/17783#discussion_r113991432
  
--- Diff: R/pkg/inst/tests/testthat/test_sparkSQL.R ---
@@ -1478,6 +1481,13 @@ test_that("column functions", {
 lapply(
   list(list(x = 1, y = -1, z = -2), list(x = 2, y = 3,  z = 5)),
   as.environment))
+
+  df <- as.DataFrame(data.frame(is_true = c(TRUE, FALSE, NA)))
+  expect_equal(
+collect(select(df, alias(SparkR::not(df$is_true), "is_false"))),
--- End diff --

Initially I experienced some shading issues with `testthat::not`, but I 
cannot reproduce this any longer. Removed.


---
If your project is set up for it, you can reply to this email and have your
reply appear on GitHub as well. If your project does not have this feature
enabled and wishes so, or if the feature is enabled but not working, please
contact infrastructure at infrastruct...@apache.org or file a JIRA ticket
with INFRA.
---

-
To unsubscribe, e-mail: reviews-unsubscr...@spark.apache.org
For additional commands, e-mail: reviews-h...@spark.apache.org



[GitHub] spark pull request #17783: [SPARK-20490][SPARKR][WIP] Add R wrappers for eqN...

2017-04-28 Thread zero323
Github user zero323 commented on a diff in the pull request:

https://github.com/apache/spark/pull/17783#discussion_r113927479
  
--- Diff: R/pkg/R/column.R ---
@@ -302,3 +301,65 @@ setMethod("otherwise",
 jc <- callJMethod(x@jc, "otherwise", value)
 column(jc)
   })
+
+#' \%<=>\%
+#'
+#' Equality test that is safe for null values.
+#'
+#' Can be used, unlike standard equality operator, to perform null-safe 
joins.
+#' Equivalent to Scala \code{Column.<=>} and \code{Column.eqNullSafe}.
+#'
+#' @param x a Column
+#' @param value a value to compare
+#' @rdname eq_null_safe
+#' @name %<=>%
+#' @aliases %<=>%,Column-method
+#' @export
+#' @examples
+#' \dontrun{
+#' df1 <- createDataFrame(data.frame(
+#'   x = c(1, NA, 3, NA), y = c(2, 6, 3, NA)
+#' ))
+#'
+#' head(select(df1, df1$x == df1$y, df1$x %<=>% df1$y))
+#' ##  (x = y) (x <=> y)
+#' ##1   FALSE FALSE
+#' ##2  NA FALSE
+#' ##3TRUE  TRUE
+#' ##4  NA  TRUE
+#'
+#' df2 <- createDataFrame(data.frame(y = c(3, NA)))
+#' count(join(df1, df2, df1$y == df2$y))
+#' ## [1] 1
+#'
+#' count(join(df1, df2, df1$y %<=>% df2$y))
+#' ## [1] 2
+#' }
+#' @note \%<=>\% since 2.3.0
+setMethod("%<=>%",
+  signature(x = "Column", value = "ANY"),
+  function(x, value) {
+value <- if (class(value) == "Column") { value@jc } else { 
value }
+jc <- callJMethod(x@jc, "eqNullSafe", value)
+column(jc)
+  })
+
+#' !
+#'
+#' @rdname not
+#' @aliases !,Column-method
+#' @export
+#' @examples
+#' \dontrun{
+#' df <- createDataFrame(data.frame(x = c(-1, 0, 1)))
+#'
+#' head(select(df, !column("x") > 0))
+#' ##  (NOT (x > 0.0))
+#' ##1TRUE
+#' ##2TRUE
+#' ##3   FALSE
+#' }
+#' @note ! since 2.3.0
+setMethod("!",
--- End diff --

https://cran.r-project.org/web/packages/lintr/, do we use something else 
here?


---
If your project is set up for it, you can reply to this email and have your
reply appear on GitHub as well. If your project does not have this feature
enabled and wishes so, or if the feature is enabled but not working, please
contact infrastructure at infrastruct...@apache.org or file a JIRA ticket
with INFRA.
---

-
To unsubscribe, e-mail: reviews-unsubscr...@spark.apache.org
For additional commands, e-mail: reviews-h...@spark.apache.org



[GitHub] spark pull request #17783: [SPARK-20490][SPARKR][WIP] Add R wrappers for eqN...

2017-04-27 Thread felixcheung
Github user felixcheung commented on a diff in the pull request:

https://github.com/apache/spark/pull/17783#discussion_r113849536
  
--- Diff: R/pkg/inst/tests/testthat/test_sparkSQL.R ---
@@ -1478,6 +1481,13 @@ test_that("column functions", {
 lapply(
   list(list(x = 1, y = -1, z = -2), list(x = 2, y = 3,  z = 5)),
   as.environment))
+
+  df <- as.DataFrame(data.frame(is_true = c(TRUE, FALSE, NA)))
+  expect_equal(
+collect(select(df, alias(SparkR::not(df$is_true), "is_false"))),
--- End diff --

we need `SparkR::` here?


---
If your project is set up for it, you can reply to this email and have your
reply appear on GitHub as well. If your project does not have this feature
enabled and wishes so, or if the feature is enabled but not working, please
contact infrastructure at infrastruct...@apache.org or file a JIRA ticket
with INFRA.
---

-
To unsubscribe, e-mail: reviews-unsubscr...@spark.apache.org
For additional commands, e-mail: reviews-h...@spark.apache.org



[GitHub] spark pull request #17783: [SPARK-20490][SPARKR][WIP] Add R wrappers for eqN...

2017-04-27 Thread felixcheung
Github user felixcheung commented on a diff in the pull request:

https://github.com/apache/spark/pull/17783#discussion_r113849200
  
--- Diff: R/pkg/R/column.R ---
@@ -67,8 +67,7 @@ operators <- list(
   "+" = "plus", "-" = "minus", "*" = "multiply", "/" = "divide", "%%" = 
"mod",
   "==" = "equalTo", ">" = "gt", "<" = "lt", "!=" = "notEqual", "<=" = 
"leq", ">=" = "geq",
   # we can not override `&&` and `||`, so use `&` and `|` instead
-  "&" = "and", "|" = "or", #, "!" = "unary_$bang"
-  "^" = "pow"
+  "&" = "and", "|" = "or", "^" = "pow"
--- End diff --

what happens with `#, `?


---
If your project is set up for it, you can reply to this email and have your
reply appear on GitHub as well. If your project does not have this feature
enabled and wishes so, or if the feature is enabled but not working, please
contact infrastructure at infrastruct...@apache.org or file a JIRA ticket
with INFRA.
---

-
To unsubscribe, e-mail: reviews-unsubscr...@spark.apache.org
For additional commands, e-mail: reviews-h...@spark.apache.org



[GitHub] spark pull request #17783: [SPARK-20490][SPARKR][WIP] Add R wrappers for eqN...

2017-04-27 Thread felixcheung
Github user felixcheung commented on a diff in the pull request:

https://github.com/apache/spark/pull/17783#discussion_r113849582
  
--- Diff: R/pkg/inst/tests/testthat/test_sparkSQL.R ---
@@ -1965,6 +1975,16 @@ test_that("filter() on a DataFrame", {
 
   # Test stats::filter is working
   #expect_true(is.ts(filter(1:100, rep(1, 3 # nolint
+
+  # test suites for %<=>%
--- End diff --

can you move this before `# Test stats::filter is working` block


---
If your project is set up for it, you can reply to this email and have your
reply appear on GitHub as well. If your project does not have this feature
enabled and wishes so, or if the feature is enabled but not working, please
contact infrastructure at infrastruct...@apache.org or file a JIRA ticket
with INFRA.
---

-
To unsubscribe, e-mail: reviews-unsubscr...@spark.apache.org
For additional commands, e-mail: reviews-h...@spark.apache.org



[GitHub] spark pull request #17783: [SPARK-20490][SPARKR][WIP] Add R wrappers for eqN...

2017-04-27 Thread felixcheung
Github user felixcheung commented on a diff in the pull request:

https://github.com/apache/spark/pull/17783#discussion_r113849285
  
--- Diff: R/pkg/R/column.R ---
@@ -302,3 +301,65 @@ setMethod("otherwise",
 jc <- callJMethod(x@jc, "otherwise", value)
 column(jc)
   })
+
+#' \%<=>\%
+#'
+#' Equality test that is safe for null values.
+#'
+#' Can be used, unlike standard equality operator, to perform null-safe 
joins.
+#' Equivalent to Scala \code{Column.<=>} and \code{Column.eqNullSafe}.
+#'
+#' @param x a Column
+#' @param value a value to compare
+#' @rdname eq_null_safe
+#' @name %<=>%
+#' @aliases %<=>%,Column-method
+#' @export
+#' @examples
+#' \dontrun{
+#' df1 <- createDataFrame(data.frame(
+#'   x = c(1, NA, 3, NA), y = c(2, 6, 3, NA)
+#' ))
+#'
+#' head(select(df1, df1$x == df1$y, df1$x %<=>% df1$y))
+#' ##  (x = y) (x <=> y)
+#' ##1   FALSE FALSE
+#' ##2  NA FALSE
+#' ##3TRUE  TRUE
+#' ##4  NA  TRUE
+#'
+#' df2 <- createDataFrame(data.frame(y = c(3, NA)))
+#' count(join(df1, df2, df1$y == df2$y))
+#' ## [1] 1
+#'
+#' count(join(df1, df2, df1$y %<=>% df2$y))
+#' ## [1] 2
+#' }
+#' @note \%<=>\% since 2.3.0
+setMethod("%<=>%",
+  signature(x = "Column", value = "ANY"),
+  function(x, value) {
+value <- if (class(value) == "Column") { value@jc } else { 
value }
+jc <- callJMethod(x@jc, "eqNullSafe", value)
+column(jc)
+  })
+
+#' !
+#'
+#' @rdname not
+#' @aliases !,Column-method
+#' @export
+#' @examples
+#' \dontrun{
+#' df <- createDataFrame(data.frame(x = c(-1, 0, 1)))
+#'
+#' head(select(df, !column("x") > 0))
+#' ##  (NOT (x > 0.0))
+#' ##1TRUE
+#' ##2TRUE
+#' ##3   FALSE
+#' }
+#' @note ! since 2.3.0
+setMethod("!",
+  signature(x = "Column"),
+  function(x) not(x))
--- End diff --

maybe this should be single line?
```
setMethod("!", signature(x = "Column"), function(x) not(x))
```


---
If your project is set up for it, you can reply to this email and have your
reply appear on GitHub as well. If your project does not have this feature
enabled and wishes so, or if the feature is enabled but not working, please
contact infrastructure at infrastruct...@apache.org or file a JIRA ticket
with INFRA.
---

-
To unsubscribe, e-mail: reviews-unsubscr...@spark.apache.org
For additional commands, e-mail: reviews-h...@spark.apache.org



[GitHub] spark pull request #17783: [SPARK-20490][SPARKR][WIP] Add R wrappers for eqN...

2017-04-27 Thread felixcheung
Github user felixcheung commented on a diff in the pull request:

https://github.com/apache/spark/pull/17783#discussion_r113849107
  
--- Diff: R/pkg/R/column.R ---
@@ -302,3 +301,65 @@ setMethod("otherwise",
 jc <- callJMethod(x@jc, "otherwise", value)
 column(jc)
   })
+
+#' \%<=>\%
+#'
+#' Equality test that is safe for null values.
+#'
+#' Can be used, unlike standard equality operator, to perform null-safe 
joins.
+#' Equivalent to Scala \code{Column.<=>} and \code{Column.eqNullSafe}.
+#'
+#' @param x a Column
+#' @param value a value to compare
+#' @rdname eq_null_safe
+#' @name %<=>%
+#' @aliases %<=>%,Column-method
+#' @export
+#' @examples
+#' \dontrun{
+#' df1 <- createDataFrame(data.frame(
+#'   x = c(1, NA, 3, NA), y = c(2, 6, 3, NA)
+#' ))
+#'
+#' head(select(df1, df1$x == df1$y, df1$x %<=>% df1$y))
+#' ##  (x = y) (x <=> y)
+#' ##1   FALSE FALSE
+#' ##2  NA FALSE
+#' ##3TRUE  TRUE
+#' ##4  NA  TRUE
+#'
+#' df2 <- createDataFrame(data.frame(y = c(3, NA)))
+#' count(join(df1, df2, df1$y == df2$y))
+#' ## [1] 1
+#'
+#' count(join(df1, df2, df1$y %<=>% df2$y))
+#' ## [1] 2
+#' }
+#' @note \%<=>\% since 2.3.0
+setMethod("%<=>%",
+  signature(x = "Column", value = "ANY"),
+  function(x, value) {
+value <- if (class(value) == "Column") { value@jc } else { 
value }
+jc <- callJMethod(x@jc, "eqNullSafe", value)
+column(jc)
+  })
+
+#' !
+#'
+#' @rdname not
+#' @aliases !,Column-method
+#' @export
+#' @examples
+#' \dontrun{
+#' df <- createDataFrame(data.frame(x = c(-1, 0, 1)))
+#'
+#' head(select(df, !column("x") > 0))
+#' ##  (NOT (x > 0.0))
+#' ##1TRUE
+#' ##2TRUE
+#' ##3   FALSE
+#' }
+#' @note ! since 2.3.0
+setMethod("!",
--- End diff --

which lintr? the current release is 0.2.0?
but I don't think we have a pattern for including output in example doc. 

I think you could try
```
#' #  (x = y) (x <=> y)
```

or
```
#'  (x = y) (x <=> y)
```


---
If your project is set up for it, you can reply to this email and have your
reply appear on GitHub as well. If your project does not have this feature
enabled and wishes so, or if the feature is enabled but not working, please
contact infrastructure at infrastruct...@apache.org or file a JIRA ticket
with INFRA.
---

-
To unsubscribe, e-mail: reviews-unsubscr...@spark.apache.org
For additional commands, e-mail: reviews-h...@spark.apache.org



[GitHub] spark pull request #17783: [SPARK-20490][SPARKR][WIP] Add R wrappers for eqN...

2017-04-27 Thread zero323
Github user zero323 commented on a diff in the pull request:

https://github.com/apache/spark/pull/17783#discussion_r113777544
  
--- Diff: R/pkg/R/column.R ---
@@ -302,3 +301,65 @@ setMethod("otherwise",
 jc <- callJMethod(x@jc, "otherwise", value)
 column(jc)
   })
+
+#' \%<=>\%
+#'
+#' Equality test that is safe for null values.
+#'
+#' Can be used, unlike standard equality operator, to perform null-safe 
joins.
+#' Equivalent to Scala \code{Column.<=>} and \code{Column.eqNullSafe}.
+#'
+#' @param x a Column
+#' @param value a value to compare
+#' @rdname eq_null_safe
+#' @name %<=>%
+#' @aliases %<=>%,Column-method
+#' @export
+#' @examples
+#' \dontrun{
+#' df1 <- createDataFrame(data.frame(
+#'   x = c(1, NA, 3, NA), y = c(2, 6, 3, NA)
+#' ))
+#'
+#' head(select(df1, df1$x == df1$y, df1$x %<=>% df1$y))
+#' ##  (x = y) (x <=> y)
+#' ##1   FALSE FALSE
+#' ##2  NA FALSE
+#' ##3TRUE  TRUE
+#' ##4  NA  TRUE
+#'
+#' df2 <- createDataFrame(data.frame(y = c(3, NA)))
+#' count(join(df1, df2, df1$y == df2$y))
+#' ## [1] 1
+#'
+#' count(join(df1, df2, df1$y %<=>% df2$y))
+#' ## [1] 2
+#' }
+#' @note \%<=>\% since 2.3.0
+setMethod("%<=>%",
+  signature(x = "Column", value = "ANY"),
+  function(x, value) {
+value <- if (class(value) == "Column") { value@jc } else { 
value }
+jc <- callJMethod(x@jc, "eqNullSafe", value)
+column(jc)
+  })
+
+#' !
+#'
+#' @rdname not
+#' @aliases !,Column-method
+#' @export
+#' @examples
+#' \dontrun{
+#' df <- createDataFrame(data.frame(x = c(-1, 0, 1)))
+#'
+#' head(select(df, !column("x") > 0))
+#' ##  (NOT (x > 0.0))
+#' ##1TRUE
+#' ##2TRUE
+#' ##3   FALSE
+#' }
+#' @note ! since 2.3.0
+setMethod("!",
--- End diff --

Do you have any thoughts about providing an example output in the docs. I 
see it makes Jenkins unhappy 

> R/column.R:325:5: style: Commented code should be removed.

but I believe this is an internal requirement. 


---
If your project is set up for it, you can reply to this email and have your
reply appear on GitHub as well. If your project does not have this feature
enabled and wishes so, or if the feature is enabled but not working, please
contact infrastructure at infrastruct...@apache.org or file a JIRA ticket
with INFRA.
---

-
To unsubscribe, e-mail: reviews-unsubscr...@spark.apache.org
For additional commands, e-mail: reviews-h...@spark.apache.org



[GitHub] spark pull request #17783: [SPARK-20490][SPARKR][WIP] Add R wrappers for eqN...

2017-04-27 Thread zero323
Github user zero323 commented on a diff in the pull request:

https://github.com/apache/spark/pull/17783#discussion_r113773816
  
--- Diff: R/pkg/R/column.R ---
@@ -302,3 +301,65 @@ setMethod("otherwise",
 jc <- callJMethod(x@jc, "otherwise", value)
 column(jc)
   })
+
+#' \%<=>\%
+#'
+#' Equality test that is safe for null values.
+#'
+#' Can be used, unlike standard equality operator, to perform null-safe 
joins.
+#' Equivalent to Scala \code{Column.<=>} and \code{Column.eqNullSafe}.
+#'
+#' @param x a Column
+#' @param value a value to compare
+#' @rdname eq_null_safe
+#' @name %<=>%
+#' @aliases %<=>%,Column-method
+#' @export
+#' @examples
+#' \dontrun{
+#' df1 <- createDataFrame(data.frame(
+#'   x = c(1, NA, 3, NA), y = c(2, 6, 3, NA)
+#' ))
+#'
+#' head(select(df1, df1$x == df1$y, df1$x %<=>% df1$y))
+#' ##  (x = y) (x <=> y)
+#' ##1   FALSE FALSE
+#' ##2  NA FALSE
+#' ##3TRUE  TRUE
+#' ##4  NA  TRUE
+#'
+#' df2 <- createDataFrame(data.frame(y = c(3, NA)))
+#' count(join(df1, df2, df1$y == df2$y))
+#' ## [1] 1
+#'
+#' count(join(df1, df2, df1$y %<=>% df2$y))
+#' ## [1] 2
+#' }
+#' @note \%<=>\% since 2.3.0
+setMethod("%<=>%",
+  signature(x = "Column", value = "ANY"),
+  function(x, value) {
+value <- if (class(value) == "Column") { value@jc } else { 
value }
+jc <- callJMethod(x@jc, "eqNullSafe", value)
+column(jc)
+  })
+
+#' !
+#'
+#' @rdname not
+#' @aliases !,Column-method
+#' @export
+#' @examples
+#' \dontrun{
+#' df <- createDataFrame(data.frame(x = c(-1, 0, 1)))
+#'
+#' head(select(df, !column("x") > 0))
+#' ##  (NOT (x > 0.0))
+#' ##1TRUE
+#' ##2TRUE
+#' ##3   FALSE
+#' }
+#' @note ! since 2.3.0
+setMethod("!",
--- End diff --

`!` is S4 generic. It is not different than `&` and `|` which we already 
support. I believe it hasn't been added so far just because it didn't fit into 
autogenerate template. 



---
If your project is set up for it, you can reply to this email and have your
reply appear on GitHub as well. If your project does not have this feature
enabled and wishes so, or if the feature is enabled but not working, please
contact infrastructure at infrastruct...@apache.org or file a JIRA ticket
with INFRA.
---

-
To unsubscribe, e-mail: reviews-unsubscr...@spark.apache.org
For additional commands, e-mail: reviews-h...@spark.apache.org



[GitHub] spark pull request #17783: [SPARK-20490][SPARKR][WIP] Add R wrappers for eqN...

2017-04-27 Thread zero323
Github user zero323 commented on a diff in the pull request:

https://github.com/apache/spark/pull/17783#discussion_r113772682
  
--- Diff: R/pkg/R/functions.R ---
@@ -3803,3 +3803,41 @@ setMethod("repeat_string",
 jc <- callJStatic("org.apache.spark.sql.functions", "repeat", 
x@jc, numToInt(n))
 column(jc)
   })
+#' not
+#'
+#' Inversion of boolean expression.
+#'
+#' \code{not} and \code{!} cannot be applied directly to numerical column.
+#' To achieve R-like truthiness column has to be casted to 
\code{BooleanType}.
+#'
+#' @param x Column to compute on
+#' @rdname not
+#' @name not
+#' @aliases not,Column-method
+#' @export
+#' @examples \dontrun{
+#' df <- createDataFrame(data.frame(
+#'   is_true = c(TRUE, FALSE, NA),
+#'   flag = c(1, 0,  1)
+#' ))
+#'
+#' head(select(df, not(df$is_true)))
+#' ##  (NOT is_true)
+#' ##1 FALSE
+#' ##2  TRUE
+#' ##3NA
+#'
+#' # Explicit cast is required when working with numeric column
+#' head(select(df, not(cast(df$flag, "boolean"
+#' ##   (NOT CAST(flag AS BOOLEAN))
+#' ## 1   FALSE
+#' ## 2TRUE
+#' ## 3   FALSE
+#' }
+#' @note not since 2.3.0
+setMethod("not",
--- End diff --

It is, but `testthat::not` is deprecated anyway.


---
If your project is set up for it, you can reply to this email and have your
reply appear on GitHub as well. If your project does not have this feature
enabled and wishes so, or if the feature is enabled but not working, please
contact infrastructure at infrastruct...@apache.org or file a JIRA ticket
with INFRA.
---

-
To unsubscribe, e-mail: reviews-unsubscr...@spark.apache.org
For additional commands, e-mail: reviews-h...@spark.apache.org



[GitHub] spark pull request #17783: [SPARK-20490][SPARKR][WIP] Add R wrappers for eqN...

2017-04-27 Thread felixcheung
Github user felixcheung commented on a diff in the pull request:

https://github.com/apache/spark/pull/17783#discussion_r113754078
  
--- Diff: R/pkg/R/column.R ---
@@ -302,3 +301,65 @@ setMethod("otherwise",
 jc <- callJMethod(x@jc, "otherwise", value)
 column(jc)
   })
+
+#' \%<=>\%
+#'
+#' Equality test that is safe for null values.
+#'
+#' Can be used, unlike standard equality operator, to perform null-safe 
joins.
+#' Equivalent to Scala \code{Column.<=>} and \code{Column.eqNullSafe}.
+#'
+#' @param x a Column
+#' @param value a value to compare
+#' @rdname eq_null_safe
+#' @name %<=>%
+#' @aliases %<=>%,Column-method
+#' @export
+#' @examples
+#' \dontrun{
+#' df1 <- createDataFrame(data.frame(
+#'   x = c(1, NA, 3, NA), y = c(2, 6, 3, NA)
+#' ))
+#'
+#' head(select(df1, df1$x == df1$y, df1$x %<=>% df1$y))
+#' ##  (x = y) (x <=> y)
+#' ##1   FALSE FALSE
+#' ##2  NA FALSE
+#' ##3TRUE  TRUE
+#' ##4  NA  TRUE
+#'
+#' df2 <- createDataFrame(data.frame(y = c(3, NA)))
+#' count(join(df1, df2, df1$y == df2$y))
+#' ## [1] 1
+#'
+#' count(join(df1, df2, df1$y %<=>% df2$y))
+#' ## [1] 2
+#' }
+#' @note \%<=>\% since 2.3.0
+setMethod("%<=>%",
+  signature(x = "Column", value = "ANY"),
+  function(x, value) {
+value <- if (class(value) == "Column") { value@jc } else { 
value }
+jc <- callJMethod(x@jc, "eqNullSafe", value)
+column(jc)
+  })
+
+#' !
+#'
+#' @rdname not
+#' @aliases !,Column-method
+#' @export
+#' @examples
+#' \dontrun{
+#' df <- createDataFrame(data.frame(x = c(-1, 0, 1)))
+#'
+#' head(select(df, !column("x") > 0))
+#' ##  (NOT (x > 0.0))
+#' ##1TRUE
+#' ##2TRUE
+#' ##3   FALSE
+#' }
+#' @note ! since 2.3.0
+setMethod("!",
--- End diff --

does this not conflict with any existing R operator?


---
If your project is set up for it, you can reply to this email and have your
reply appear on GitHub as well. If your project does not have this feature
enabled and wishes so, or if the feature is enabled but not working, please
contact infrastructure at infrastruct...@apache.org or file a JIRA ticket
with INFRA.
---

-
To unsubscribe, e-mail: reviews-unsubscr...@spark.apache.org
For additional commands, e-mail: reviews-h...@spark.apache.org



[GitHub] spark pull request #17783: [SPARK-20490][SPARKR][WIP] Add R wrappers for eqN...

2017-04-27 Thread felixcheung
Github user felixcheung commented on a diff in the pull request:

https://github.com/apache/spark/pull/17783#discussion_r113753986
  
--- Diff: R/pkg/R/functions.R ---
@@ -3803,3 +3803,41 @@ setMethod("repeat_string",
 jc <- callJStatic("org.apache.spark.sql.functions", "repeat", 
x@jc, numToInt(n))
 column(jc)
   })
+#' not
+#'
+#' Inversion of boolean expression.
+#'
+#' \code{not} and \code{!} cannot be applied directly to numerical column.
+#' To achieve R-like truthiness column has to be casted to 
\code{BooleanType}.
+#'
+#' @param x Column to compute on
+#' @rdname not
+#' @name not
+#' @aliases not,Column-method
+#' @export
+#' @examples \dontrun{
+#' df <- createDataFrame(data.frame(
+#'   is_true = c(TRUE, FALSE, NA),
+#'   flag = c(1, 0,  1)
+#' ))
+#'
+#' head(select(df, not(df$is_true)))
+#' ##  (NOT is_true)
+#' ##1 FALSE
+#' ##2  TRUE
+#' ##3NA
+#'
+#' # Explicit cast is required when working with numeric column
+#' head(select(df, not(cast(df$flag, "boolean"
+#' ##   (NOT CAST(flag AS BOOLEAN))
+#' ## 1   FALSE
+#' ## 2TRUE
+#' ## 3   FALSE
+#' }
+#' @note not since 2.3.0
+setMethod("not",
--- End diff --

I think this conflict with testthat..


---
If your project is set up for it, you can reply to this email and have your
reply appear on GitHub as well. If your project does not have this feature
enabled and wishes so, or if the feature is enabled but not working, please
contact infrastructure at infrastruct...@apache.org or file a JIRA ticket
with INFRA.
---

-
To unsubscribe, e-mail: reviews-unsubscr...@spark.apache.org
For additional commands, e-mail: reviews-h...@spark.apache.org



[GitHub] spark pull request #17783: [SPARK-20490][SPARKR][WIP] Add R wrappers for eqN...

2017-04-27 Thread zero323
GitHub user zero323 opened a pull request:

https://github.com/apache/spark/pull/17783

[SPARK-20490][SPARKR][WIP] Add R wrappers for eqNullSafe and ! / not.

## What changes were proposed in this pull request?

- Add null-safe equality operator `%<=>%` (sames as 
`o.a.s.sql.Column.eqNullSafe`, `o.a.s.sql.Column.<=>`)
- Add boolean negation operator (`!`) and function (`not `).

## How was this patch tested?

Existing unit tests, additional unit tests, `check-cran.sh`.

You can merge this pull request into a Git repository by running:

$ git pull https://github.com/zero323/spark SPARK-20490

Alternatively you can review and apply these changes as the patch at:

https://github.com/apache/spark/pull/17783.patch

To close this pull request, make a commit to your master/trunk branch
with (at least) the following in the commit message:

This closes #17783






---
If your project is set up for it, you can reply to this email and have your
reply appear on GitHub as well. If your project does not have this feature
enabled and wishes so, or if the feature is enabled but not working, please
contact infrastructure at infrastruct...@apache.org or file a JIRA ticket
with INFRA.
---

-
To unsubscribe, e-mail: reviews-unsubscr...@spark.apache.org
For additional commands, e-mail: reviews-h...@spark.apache.org