Skip to content

Commit

Permalink
Move dbQuoteIdentifer implementation
Browse files Browse the repository at this point in the history
  • Loading branch information
hadley authored and aviator-bot committed Nov 8, 2023
1 parent 8335301 commit 2d42775
Show file tree
Hide file tree
Showing 5 changed files with 15 additions and 21 deletions.
7 changes: 6 additions & 1 deletion R/00-Id.R
Original file line number Diff line number Diff line change
Expand Up @@ -49,5 +49,10 @@ Id <- function(...) {

#' @export
toString.Id <- function(x, ...) {
paste0("<Id> ", paste0('"', x@name, '"', collapse = "."))
paste0("<Id> ", dbQuoteIdentifier(ANSI(), x))
}


dbQuoteIdentifier_DBIConnection_Id <- function(conn, x, ...) {
SQL(paste0(dbQuoteIdentifier(conn, x@name), collapse = "."))
}
5 changes: 1 addition & 4 deletions R/dbQuoteIdentifier_DBIConnection.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,9 +3,6 @@
dbQuoteIdentifier_DBIConnection <- function(conn, x, ...) {
# Don't support lists, auto-vectorization violates type stability
if (is(x, "SQL")) return(x)
if (is(x, "Id")) {
return(SQL(paste0(dbQuoteIdentifier(conn, x@name), collapse = ".")))
}
if (!is.character(x)) stop("x must be character or SQL", call. = FALSE)

if (any(is.na(x))) {
Expand Down Expand Up @@ -37,4 +34,4 @@ setMethod("dbQuoteIdentifier", signature("DBIConnection", "SQL"), dbQuoteIdentif

#' @rdname hidden_aliases
#' @export
setMethod("dbQuoteIdentifier", signature("DBIConnection", "Id"), dbQuoteIdentifier_DBIConnection)
setMethod("dbQuoteIdentifier", signature("DBIConnection", "Id"), dbQuoteIdentifier_DBIConnection_Id)
2 changes: 1 addition & 1 deletion tests/testthat/_snaps/00-Id.md
Original file line number Diff line number Diff line change
Expand Up @@ -11,5 +11,5 @@
Code
Id("a", "b")
Output
<Id> a.b
<Id> "a"."b"

15 changes: 0 additions & 15 deletions tests/testthat/_snaps/00-Id.new.md

This file was deleted.

7 changes: 7 additions & 0 deletions tests/testthat/test-00-Id.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,3 +5,10 @@ test_that("Id() requires a character vector", {
test_that("has a decent print method", {
expect_snapshot(Id("a", "b"))
})

test_that("each element is quoted individually", {
expect_equal(
DBI::dbQuoteIdentifier(ANSI(), Id("a", "b.c")),
SQL('"a"."b.c"')
)
})

0 comments on commit 2d42775

Please sign in to comment.