Skip to content

Commit

Permalink
try dbList*()
Browse files Browse the repository at this point in the history
  • Loading branch information
nbenn committed Sep 30, 2023
1 parent b4571da commit 2bfa13c
Show file tree
Hide file tree
Showing 17 changed files with 303 additions and 41 deletions.
6 changes: 6 additions & 0 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -51,6 +51,8 @@ Collate:
'dbDataType_Driver.R'
'dbDataType_Driver_list.R'
'dbDisconnect_Connection.R'
'dbExistsTable_AdbiConnection_Id.R'
'dbExistsTable_AdbiConnection_SQL.R'
'dbExistsTable_Connection_character.R'
'dbFetchArrow_ResultArrow.R'
'dbFetch_Result.R'
Expand All @@ -64,15 +66,19 @@ Collate:
'dbIsValid_Connection.R'
'dbIsValid_Driver.R'
'dbIsValid_Result.R'
'dbListFields_AdbiConnection_Id.R'
'dbListFields_AdbiConnection_SQL.R'
'dbListFields_Connection_character.R'
'dbListTables_Connection.R'
'dbQuoteIdentifier_Connection_character.R'
'dbQuoteLiteral_AdbiConnection_character.R'
'dbQuoteString_Connection_character.R'
'dbRemoveTable_Connection_character.R'
'dbRollback_Connection.R'
'dbSendQueryArrow_Connection.R'
'dbSendQuery_Connection_character.R'
'dbSendStatement_Connection_character.R'
'dbUnquoteIdentifier_AdbiConnection.R'
'dbWriteTable_Connection_character_data.frame.R'
'show_Connection.R'
'show_Driver.R'
Expand Down
2 changes: 2 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -38,12 +38,14 @@ exportMethods(dbIsValid)
exportMethods(dbListFields)
exportMethods(dbListTables)
exportMethods(dbQuoteIdentifier)
exportMethods(dbQuoteLiteral)
exportMethods(dbQuoteString)
exportMethods(dbRemoveTable)
exportMethods(dbRollback)
exportMethods(dbSendQuery)
exportMethods(dbSendQueryArrow)
exportMethods(dbSendStatement)
exportMethods(dbUnquoteIdentifier)
exportMethods(dbWriteTable)
exportMethods(show)
import(DBI)
Expand Down
28 changes: 28 additions & 0 deletions R/dbExistsTable_AdbiConnection_Id.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,28 @@
#' @rdname DBI
#' @inheritParams DBI::dbExistsTable
#' @usage NULL
dbExistsTable_AdbiConnection_Id <- function(conn, name, ...) {

if (!dbIsValid(conn)) {
stop("Invalid connection.", call. = FALSE)
}

name <- as.list(name@name)

if (!all(names(name) %in% c("catalog", "schema", "table"))) {
stop("Expecting Id components \"catalog\", \"schema\", and \"table\".",
call. = FALSE)
}

res <- do.call(get_schema_objects, c(list(conn, "table"), name))

length(res[["table_name"]]) == 1L
}

#' @rdname DBI
#' @export
setMethod(
"dbExistsTable",
c("AdbiConnection", "Id"),
dbExistsTable_AdbiConnection_Id
)
14 changes: 14 additions & 0 deletions R/dbExistsTable_AdbiConnection_SQL.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
#' @rdname DBI
#' @inheritParams DBI::dbExistsTable
#' @usage NULL
dbExistsTable_AdbiConnection_SQL <- function(conn, name, ...) {
dbExistsTable(conn, dbUnquoteIdentifier(conn, name)[[1L]], ...)
}

#' @rdname DBI
#' @export
setMethod(
"dbExistsTable",
c("AdbiConnection", "SQL"),
dbExistsTable_AdbiConnection_SQL
)
2 changes: 1 addition & 1 deletion R/dbExistsTable_Connection_character.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
#' @inheritParams DBI::dbExistsTable
#' @usage NULL
dbExistsTable_AdbiConnection_character <- function(conn, name, ...) {
name %in% dbListTables(conn)
dbExistsTable(conn, Id(table = name), ...)
}

#' @rdname DBI
Expand Down
32 changes: 32 additions & 0 deletions R/dbListFields_AdbiConnection_Id.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,32 @@
#' @rdname DBI
#' @inheritParams DBI::dbListFields
#' @usage NULL
dbListFields_AdbiConnection_Id <- function(conn, name, ...) {

if (!dbIsValid(conn)) {
stop("Invalid connection.", call. = FALSE)
}

if (!dbExistsTable(conn, name)) {
stop("Table `", name, "` does not exist.", call. = FALSE)
}

name <- as.list(name@name)

if (!all(names(name) %in% c("catalog", "schema", "table"))) {
stop("Expecting Id components \"catalog\", \"schema\", and \"table\".",
call. = FALSE)
}

res <- do.call(get_schema_objects, c(list(conn, "field"), name))

res[["column_name"]]
}

#' @rdname DBI
#' @export
setMethod(
"dbListFields",
c("AdbiConnection", "Id"),
dbListFields_AdbiConnection_Id
)
14 changes: 14 additions & 0 deletions R/dbListFields_AdbiConnection_SQL.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
#' @rdname DBI
#' @inheritParams DBI::dbListFields
#' @usage NULL
dbListFields_AdbiConnection_SQL <- function(conn, name, ...) {
dbListFields(conn, dbUnquoteIdentifier(conn, name)[[1L]], ...)
}

#' @rdname DBI
#' @export
setMethod(
"dbListFields",
c("AdbiConnection", "SQL"),
dbListFields_AdbiConnection_SQL
)
9 changes: 7 additions & 2 deletions R/dbListFields_Connection_character.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,8 +2,13 @@
#' @inheritParams DBI::dbListFields
#' @usage NULL
dbListFields_AdbiConnection_character <- function(conn, name, ...) {
testthat::skip("Not yet implemented: dbListFields(Connection, character)")
dbListFields(conn, Id(table = name), ...)
}

#' @rdname DBI
#' @export
setMethod("dbListFields", c("AdbiConnection", "character"), dbListFields_AdbiConnection_character)
setMethod(
"dbListFields",
c("AdbiConnection", "character"),
dbListFields_AdbiConnection_character
)
120 changes: 98 additions & 22 deletions R/dbListTables_Connection.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,38 +3,114 @@
#' @usage NULL
dbListTables_AdbiConnection <- function(conn, ...) {

extract_tables <- function(x) {
x[, c("table_name", "table_type")]
if (!dbIsValid(conn)) {
stop("Invalid connection.", call. = FALSE)
}

extract_schemas <- function(x) {
cbind(
schema_name = x[["db_schema_name"]],
do.call(rbind, lapply(x[["db_schema_tables"]], extract_tables))
)
get_schema_objects(conn, "table")[["table_name"]]
}

#' @rdname DBI
#' @export
setMethod("dbListTables", "AdbiConnection", dbListTables_AdbiConnection)

process_fields <- function(x, dat, what) {

stopifnot(identical(what, "field"))

res <- x[, c("column_name", "xdbc_type_name")]

if (!nrow(res)) {
dat <- dat[0L, , drop = FALSE]
}

extract_catalogs <- function(x) {
cbind(
catalog_name = x[["catalog_name"]],
do.call(rbind, lapply(x[["catalog_db_schemas"]], extract_schemas))
)
cbind(dat, res, row.names = NULL)
}

process_tables <- function(x, dat, what) {

res <- x[, c("table_name", "table_type")]

if (!nrow(res)) {
dat <- dat[0L, , drop = FALSE]
}

stopifnot(dbIsValid(conn))
res <- cbind(dat, res, row.names = NULL)

res <- adbcdrivermanager::adbc_connection_get_objects(
conn@connection,
depth = 3L
if (identical(what, "table")) {
return(res)
}

res <- Map(
process_fields,
x[["table_columns"]],
split_rows(res),
MoreArgs = list(what = what)
)

tbl <- extract_catalogs(
nanoarrow::convert_array_stream(res)
do.call(rbind, res)
}

process_schemas <- function(x, dat, what) {

res <- x[, c("db_schema_name"), drop = FALSE]

if (!nrow(res)) {
dat <- dat[0L, , drop = FALSE]
}

res <- cbind(dat, res, row.names = NULL)

if (identical(what, "schema")) {
return(res)
}

res <- Map(
process_tables,
x[["db_schema_tables"]],
split_rows(res),
MoreArgs = list(what = what)
)

tbl[["table_name"]]
do.call(rbind, res)
}

#' @rdname DBI
#' @export
setMethod("dbListTables", "AdbiConnection", dbListTables_AdbiConnection)
process_catalogs <- function(x, what) {

res <- x[, c("catalog_name"), drop = FALSE]

if (identical(what, "catalog")) {
return(res)
}

res <- Map(
process_schemas,
x[["catalog_db_schemas"]],
split_rows(res),
MoreArgs = list(what = what)
)

do.call(rbind, res)
}

get_schema_objects <- function(con,
what = c("catalog", "schema", "table", "field"),
catalog = NULL,
schema = NULL,
table = NULL) {

what <- match.arg(what)

nfo <- adbcdrivermanager::adbc_connection_get_objects(
con@connection,
depth = switch(what, catalog = 1L, schema = 2L, table = 3L, field = 0L),
catalog = catalog,
db_schema = schema,
table_name = table
)

process_catalogs(
nanoarrow::convert_array_stream(nfo),
what
)
}
10 changes: 7 additions & 3 deletions R/dbQuoteIdentifier_Connection_character.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,13 @@
#' @inheritParams DBI::dbQuoteIdentifier
#' @usage NULL
dbQuoteIdentifier_AdbiConnection_character <- function(conn, x, ...) {
# Optional
getMethod("dbQuoteIdentifier", c("DBIConnection", "character"), asNamespace("DBI"))(conn, x, ...)
dbQuoteIdentifier(ANSI(), x, ...)
}

#' @rdname DBI
#' @export
setMethod("dbQuoteIdentifier", c("AdbiConnection", "character"), dbQuoteIdentifier_AdbiConnection_character)
setMethod(
"dbQuoteIdentifier",
c("AdbiConnection", "character"),
dbQuoteIdentifier_AdbiConnection_character
)
14 changes: 14 additions & 0 deletions R/dbQuoteLiteral_AdbiConnection_character.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
#' @rdname DBI
#' @inheritParams DBI::dbQuoteLiteral
#' @usage NULL
dbQuoteLiteral_AdbiConnection_character <- function(conn, x, ...) {
dbQuoteLiteral(ANSI(), x, ...)
}

#' @rdname DBI
#' @export
setMethod(
"dbQuoteLiteral",
c("AdbiConnection", "character"),
dbQuoteLiteral_AdbiConnection_character
)
10 changes: 7 additions & 3 deletions R/dbQuoteString_Connection_character.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,13 @@
#' @inheritParams DBI::dbQuoteString
#' @usage NULL
dbQuoteString_AdbiConnection_character <- function(conn, x, ...) {
# Optional
getMethod("dbQuoteString", c("DBIConnection", "character"), asNamespace("DBI"))(conn, x, ...)
dbQuoteString(ANSI(), x, ...)
}

#' @rdname DBI
#' @export
setMethod("dbQuoteString", c("AdbiConnection", "character"), dbQuoteString_AdbiConnection_character)
setMethod(
"dbQuoteString",
c("AdbiConnection", "character"),
dbQuoteString_AdbiConnection_character
)
14 changes: 14 additions & 0 deletions R/dbUnquoteIdentifier_AdbiConnection.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
#' @rdname DBI
#' @inheritParams DBI::dbUnquoteIdentifier
#' @usage NULL
dbUnquoteIdentifier_AdbiConnection <- function(conn, x, ...) {
dbUnquoteIdentifier(ANSI(), x, ...)
}

#' @rdname DBI
#' @export
setMethod(
"dbUnquoteIdentifier",
"AdbiConnection",
dbUnquoteIdentifier_AdbiConnection
)
19 changes: 18 additions & 1 deletion R/dbWriteTable_Connection_character_data.frame.R
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,9 @@
dbWriteTable_AdbiConnection_character_data.frame <- function(conn, name, value, overwrite = FALSE, append = FALSE, ..., field.types = NULL, row.names = NULL,
temporary = FALSE) {

stopifnot(dbIsValid(conn))
if (!dbIsValid(conn)) {
stop("Invalid connection.", call. = FALSE)
}

if (is.null(row.names)) {
row.names <- FALSE
Expand Down Expand Up @@ -70,6 +72,21 @@ dbWriteTable_AdbiConnection_character_data.frame <- function(conn, name, value,
mode <- "create"
}

if (is(name, "SQL")) {
name <- dbUnquoteIdentifier(conn, name)[[1L]]
}

if (is(name, "Id")) {

name <- name@name

if (!identical(names(name), "table")) {
stop("Currently passing catalog and schema information is not supported.")
}

name <- unname(name["table"])
}

stmt <- adbcdrivermanager::adbc_statement_init(
conn@connection,
adbc.ingest.target_table = name,
Expand Down
Loading

0 comments on commit 2bfa13c

Please sign in to comment.