Skip to content

Commit

Permalink
<- replaced by = for default values
Browse files Browse the repository at this point in the history
  • Loading branch information
nteetor committed Aug 25, 2017
1 parent 3f894b9 commit 06de465
Show file tree
Hide file tree
Showing 7 changed files with 53 additions and 23 deletions.
2 changes: 1 addition & 1 deletion NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@
* A `%->%` operator has been added. The right operator performs the same
operation as `%<-%` with the name structure on the right-hand side and
the values to assign on the left-hand side.
* `<-` may be used to specify the default value of a variable. A default value
* `=` may be used to specify the default value of a variable. A default value
is used when there are an insufficient number of values.

# zeallot 0.0.4
Expand Down
6 changes: 3 additions & 3 deletions R/operator.R
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@
#'
#' **default values**
#'
#' Use `<-` to specify a default value for a variable, \code{c(x, y <- NULL)
#' Use `=` to specify a default value for a variable, \code{c(x, y = NULL)
#' \%<-\% tail(1, 2)}.
#'
#' @return
Expand Down Expand Up @@ -157,12 +157,12 @@
#' strsplit(x, " ")[[1]]
#' }
#'
#' c(hour, period <- NA) %<-% parse_time("10:00 AM")
#' c(hour, period = NA) %<-% parse_time("10:00 AM")
#'
#' hour # "10:00"
#' period # "AM"
#'
#' c(hour, period <- NA) %<-% parse_time("15:00")
#' c(hour, period = NA) %<-% parse_time("15:00")
#'
#' hour # "15:00"
#' period # NA
Expand Down
33 changes: 27 additions & 6 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -32,16 +32,29 @@ add_defaults <- function(names, values, env) {
append(values, evaled)
}

names2 <- function(x) {
if (is.null(names(x))) rep.int("", length(x)) else names(x)
}

tree <- function(x) {
if (length(x) == 1) {
if (length(x) == 1 && is.language(x) && !is.symbol(x)) {
return(x)
}

if (x[[1]] == "<-") {
return(as.list(x))
x <- as.list(x)

if (length(x) == 1 && length(x[[1]]) <= 1) {
if (names2(x) != "") {
return(list(as.symbol("="), as.symbol(names(x)), x[[1]]))
}

return(x[[1]])
}

append(tree(x[[1]]), lapply(x[-1], tree))
append(
tree(x[[1]]),
lapply(seq_along(x[-1]), function(i) tree(x[-1][i]))
)
}

calls <- function(x) {
Expand All @@ -51,7 +64,7 @@ calls <- function(x) {

this <- car(x)

if (this != "c" && this != "<-") {
if (this != "c" && this != "=") {
stop_invalid_lhs(unexpected_call(this))
}

Expand All @@ -60,14 +73,18 @@ calls <- function(x) {

variables <- function(x) {
if (!is_list(x)) {
if (x == "") {
stop_invalid_lhs(empty_variable(x))
}

if (!is.symbol(x)) {
stop_invalid_lhs(unexpected_variable(x))
}

return(as.character(x))
}

if (car(x) == "<-") {
if (car(x) == "=") {
var <- as.character(car(cdr(x)))
default <- car(cdr(cdr(x)))

Expand All @@ -91,6 +108,10 @@ incorrect_number_of_values <- function() {
"incorrect number of values"
}

empty_variable <- function(obj) {
paste("found empty variable, check for extraneous commas")
}

unexpected_variable <- function(obj) {
paste("expected symbol, but found", class(obj))
}
Expand Down
2 changes: 1 addition & 1 deletion cran-comments.md
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@

### Notes

* Possibly misspelled word "destructuring" in DESCRIPTION.
* Possibly misspelled word "destructuring" in DESCRIPTION is intentionally used.

## Reverse dependencies

Expand Down
6 changes: 3 additions & 3 deletions man/operator.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

17 changes: 12 additions & 5 deletions tests/testthat/test-operator.R
Original file line number Diff line number Diff line change
Expand Up @@ -102,28 +102,28 @@ test_that("%<-% skips multiple values using ...", {
})

test_that("%<-% assigns default values", {
c(a, b <- 1) %<-% c(3)
c(a, b = 1) %<-% c(3)
expect_equal(a, 3)
expect_equal(b, 1)

c(d, e <- iris, f <- 3030) %<-% 5
c(d, e = iris, f = 3030) %<-% 5
expect_equal(d, 5)
expect_equal(e, iris)
expect_equal(f, 3030)
})

test_that("%<-% assign default value of NULL", {
c(a, b <- NULL) %<-% c(3)
c(a, b = NULL) %<-% c(3)
expect_equal(a, 3)
expect_equal(b, NULL)
})

test_that("%<-% default values do not override specified values", {
c(a <- 1, b <- 4) %<-% 2
c(a = 1, b = 4) %<-% 2
expect_equal(a, 2)
expect_equal(b, 4)

c(d <- 5, e <- 6) %<-% c(8, 9)
c(d = 5, e = 6) %<-% c(8, 9)
expect_equal(d, 8)
expect_equal(e, 9)
})
Expand Down Expand Up @@ -163,6 +163,13 @@ test_that("%<-% throws error when invalid calls on LHS", {
)
})

test_that("%<-% throws error when blank variable names", {
expect_error(
c(, a) %<-% c(1, 2),
"invalid `%<-%` left-hand side, found empty variable, check for extraneous commas"
)
})

test_that('%<-% throws error when invalid "variables" on LHS', {
expect_error(
c(mean(1, 2), a) %<-% list(1, 2),
Expand Down
10 changes: 6 additions & 4 deletions vignettes/unpacking-assignment.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -329,9 +329,10 @@ It is important to note that although value(s) are skipped they are still
expected. The next section touches on how to handle missing values.

## Default values: handle missing values
You can specify a default value for a left-hand side variable using `<-`. This
comes in handy when the number of elements returned by a function cannot be
guaranteed. `tail` for example may return fewer elements than asked for.
You can specify a default value for a left-hand side variable using `=`, similar
to specifying the default value of a function argument. This comes in handy when
the number of elements returned by a function cannot be guaranteed. `tail` for
example may return fewer elements than asked for.

```{r}
nums <- 1:2
Expand All @@ -351,7 +352,7 @@ We can fix the problem and resolve the error by specifying a default value for
`z`.

```{r}
c(x, y, z <- NULL) %<-% tail(nums, 3)
c(x, y, z = NULL) %<-% tail(nums, 3)
x
y
z
Expand Down Expand Up @@ -396,6 +397,7 @@ mtcars %>%
aggregate(. ~ cyl, data = ., FUN = . %>% mean() %>% round(2)) %>%
transform(kpl = mpg %>% multiply_by(0.4251)) %->%
c(cyl, mpg, ...rest)
cyl
mpg
rest
Expand Down

0 comments on commit 06de465

Please sign in to comment.