Skip to content

Commit

Permalink
Merge pull request #34 from ccb-hms/variable-qc
Browse files Browse the repository at this point in the history
DB insert bugfixes
  • Loading branch information
deepayan authored Mar 10, 2024
2 parents cb89c1e + 26d1989 commit 96f1a6d
Showing 1 changed file with 9 additions and 5 deletions.
14 changes: 9 additions & 5 deletions R/db-insert.R
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ addPrimaryKey <- function(con, table, columns)
{
qcol <- DBI::dbQuoteIdentifier(con, columns)
sql <- sprintf("ALTER TABLE %s ADD PRIMARY KEY (%s);",
x,
table,
paste0(qcol, collapse = ", "))
query <- DBI::SQL(sql)
dbExecute(con, query)
Expand All @@ -44,7 +44,10 @@ addPrimaryKey <- function(con, table, columns)
## isWholeNumber <- function(x, tol = .Machine$double.eps^0.5) all(abs(x - round(x)) < tol)

## But this one is faster and should be OK for NHANES data
isWholeNumber <- function(x) all(x == as.integer(x))
isWholeNumber <- function(x) {
keep <- !is.na(x)
isTRUE(all(x[keep] == as.integer(x[keep])))
}



Expand Down Expand Up @@ -78,9 +81,9 @@ insertTableDB <-
qtable <- DBI::dbQuoteIdentifier(con, table)
dtype <- DBI::dbDataType(con, data)
if (!is.null(non_null)) {
if (!all(non_null %in% dcol)) {
if (!all(non_null %in% dcols)) {
stop("Columns specified as non-null do not exists in data:",
non_null[!(non_null %in% dcol)] |> paste(collapse = ", "))
non_null[!(non_null %in% dcols)] |> paste(collapse = ", "))
}
dtype[non_null] <- paste0(dtype[non_null], " NOT NULL")
}
Expand Down Expand Up @@ -173,6 +176,7 @@ dbTableNameFromNHANES <- function(x, type = c("raw", "translated"))
##' missing values. TODO more details.
##' @author Deepayan Sarkar
##' @export

dbInsertNhanesTable <-
function(con, x, data = nhanes(x, translated = FALSE),
type = c("raw", "translated", "both"),
Expand All @@ -182,7 +186,7 @@ dbInsertNhanesTable <-
cleanse_numeric = TRUE)
{
type <- match.arg(type)
pk <- if (isTRUE(primary_key))
pk <- if (isTRUE(make_primary_key))
primary_keys(x, require_unique = FALSE)
else NULL
if (type %in% c("raw", "both")) {
Expand Down

0 comments on commit 96f1a6d

Please sign in to comment.