Skip to content

Commit 6a7fccd

Browse files
committed
Revert "Don't allow casting to non-bare data frames"
This reverts commit b4f1c40.
1 parent 3509722 commit 6a7fccd

File tree

5 files changed

+28
-32
lines changed

5 files changed

+28
-32
lines changed

R/cast.R

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -209,13 +209,12 @@ vec_default_cast <- function(x,
209209
return(out)
210210
}
211211

212-
if (is_bare_df(to)) {
213-
# Bare-class fallback for data frames
214-
if (inherits(to, "tbl_df")) {
215-
out <- df_as_tibble(out)
216-
}
217-
return(out)
212+
# Bare-class fallback for data frames.
213+
# FIXME: Should we only allow it when target is a bare df?
214+
if (inherits(to, "tbl_df")) {
215+
out <- df_as_tibble(out)
218216
}
217+
return(out)
219218
}
220219

221220
if (is_same_type(x, to)) {

tests/testthat/_snaps/cast.md

Lines changed: 0 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -62,15 +62,6 @@
6262
Error:
6363
! Can't combine `..1$a$b` <factor<c1562>> and `..2$a$b` <double>.
6464

65-
# vec_cast() only falls back when casting to base type
66-
67-
Code
68-
(expect_error(vec_cast(mtcars, foobar(mtcars))))
69-
Output
70-
<error/vctrs_error_cast>
71-
Error:
72-
! Can't convert `mtcars` <data.frame> to <vctrs_foobar>.
73-
7465
# vec_cast() only attempts to fall back if `to` is a data frame (#1568)
7566

7667
Code

tests/testthat/_snaps/type-misc.md

Lines changed: 0 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,3 @@
1-
# data.table and tibble do not have a common type
2-
3-
Code
4-
(expect_error(vec_cast(tibble(y = 2), data.table(x = TRUE, y = 1L))))
5-
Output
6-
<error/vctrs_error_cast>
7-
Error:
8-
! Can't convert `tibble(y = 2)` <tibble> to <data.table>.
9-
101
# data table has formatting methods
112

123
Code

tests/testthat/test-cast.R

Lines changed: 19 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -92,11 +92,9 @@ test_that("unspecified can be cast to shaped vectors", {
9292
expect_identical(out, exp)
9393
})
9494

95-
test_that("vec_cast() only falls back when casting to base type", {
95+
test_that("vec_cast() falls back to base class even when casting to non-base type", {
9696
expect_equal(vec_cast(foobar(mtcars), mtcars), mtcars)
97-
expect_snapshot({
98-
(expect_error(vec_cast(mtcars, foobar(mtcars))))
99-
})
97+
expect_equal(vec_cast(mtcars, foobar(mtcars)), mtcars)
10098
})
10199

102100
test_that("vec_cast() only attempts to fall back if `to` is a data frame (#1568)", {
@@ -284,3 +282,20 @@ test_that("df-fallback for cast is not sensitive to attributes order", {
284282

285283
expect_identical(vec_cast(x, ptype), x)
286284
})
285+
286+
test_that("bare-type fallback for df-cast works", {
287+
# NOTE: Not sure why this was necessary. The cubble and yamlet
288+
# packages fail without this.
289+
local_methods(
290+
c.vctrs_foobaz = function(...) quux(NextMethod())
291+
)
292+
293+
df <- data_frame(x = 1, y = foobaz("foo"))
294+
gdf <- dplyr::new_grouped_df(
295+
df,
296+
data_frame(x = 1, .rows = list(1L)),
297+
class = "vctrs_foobar"
298+
)
299+
300+
expect_error(vec_rbind(gdf, gdf), NA)
301+
})

tests/testthat/test-type-misc.R

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -77,10 +77,10 @@ test_that("data.table and tibble do not have a common type", {
7777
vec_cast(data.table(y = 2), tibble(x = TRUE, y = 1L)),
7878
tibble(x = lgl(NA), y = 2L)
7979
)
80-
81-
expect_snapshot({
82-
(expect_error(vec_cast(tibble(y = 2), data.table(x = TRUE, y = 1L))))
83-
})
80+
expect_identical(
81+
vec_cast(tibble(y = 2), data.table(x = TRUE, y = 1L)),
82+
data_frame(x = lgl(NA), y = 2L)
83+
)
8484
})
8585

8686
test_that("data table has formatting methods", {

0 commit comments

Comments
 (0)