diff --git a/NAMESPACE b/NAMESPACE index 807cae1..cd494b3 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -19,6 +19,7 @@ export(.stageObject) export(.writeMetadata) export(acquireFile) export(acquireMetadata) +export(addMissingPlaceholderAttribute) export(addMissingStringPlaceholderAttribute) export(altLoadObject) export(altLoadObjectFunction) diff --git a/R/loadDataFrame.R b/R/loadDataFrame.R index b416cb4..9e3fe64 100644 --- a/R/loadDataFrame.R +++ b/R/loadDataFrame.R @@ -56,14 +56,15 @@ loadDataFrame <- function(info, project, include.nested=TRUE, parallel=TRUE) { df <- make_zero_col_DFrame(nrow=nrows) } else { raw <- h5read(path, prefix("data")) + version_above_1 <- isTRUE(info$data_frame$version > 1) - # Replacing NAs for strings. + # Replacing placeholders with NAs. for (i in names(raw)) { current <- raw[[i]] - if (is.character(current)) { + if (version_above_1 || is.character(current)) { attr <- h5readAttributes(path, prefix(paste0("data/", i))) replace.na <- attr[["missing-value-placeholder"]] - if (!is.null(replace.na)) { + if (!is.null(replace.na) && !is.na(replace.na)) { raw[[i]][current == replace.na] <- NA } } diff --git a/R/stageDataFrame.R b/R/stageDataFrame.R index 02937ec..e7da2e1 100644 --- a/R/stageDataFrame.R +++ b/R/stageDataFrame.R @@ -64,8 +64,9 @@ #' #' @export #' @aliases -#' addMissingStringPlaceholderAttribute +#' addMissingPlaceholderAttribute #' chooseMissingStringPlaceholder +#' addMissingStringPlaceholderAttribute #' .addMissingStringPlaceholderAttribute #' .chooseMissingStringPlaceholder #' @@ -180,7 +181,7 @@ setMethod("stageObject", "DataFrame", function(x, dir, path, child=FALSE, df.nam opath <- paste0(opath, ".h5") ofile <- file.path(dir, opath) skippable <- vapply(meta, function(x) x$type == "other", TRUE) - .write_hdf5_data_frame(x, skippable, "contents", ofile) + .write_hdf5_data_frame(x, skippable, "contents", ofile, .version=.version) schema <- "hdf5_data_frame/v1.json" extra[[1]]$group <- "contents" @@ -229,7 +230,7 @@ setMethod("stageObject", "DataFrame", function(x, dir, path, child=FALSE, df.nam }) #' @importFrom rhdf5 h5write h5createGroup h5createFile -.write_hdf5_data_frame <- function(x, skippable, host, ofile) { +.write_hdf5_data_frame <- function(x, skippable, host, ofile, .version) { h5createFile(ofile) prefix <- function(x) paste0(host, "/", x) h5createGroup(ofile, host) @@ -248,16 +249,20 @@ setMethod("stageObject", "DataFrame", function(x, dir, path, child=FALSE, df.nam } missing.placeholder <- NULL - if (is.character(current) && anyNA(current)) { - missing.placeholder <- chooseMissingStringPlaceholder(current) - current[is.na(current)] <- missing.placeholder + if (anyNA(current)) { + if (is.character(current) && anyNA(current)) { + missing.placeholder <- chooseMissingStringPlaceholder(current) + current[is.na(current)] <- missing.placeholder + } else if (.version > 1) { + missing.placeholder <- as(NA, storage.mode(current)) + } } data.name <- as.character(i - 1L) h5write(current, ofile, prefix(paste0("data/", data.name))) if (!is.null(missing.placeholder)) { - addMissingStringPlaceholderAttribute(ofile, prefix(paste0("data/", data.name)), missing.placeholder) + addMissingPlaceholderAttribute(ofile, prefix(paste0("data/", data.name)), missing.placeholder) } } @@ -282,7 +287,7 @@ chooseMissingStringPlaceholder <- function(x) { #' @export #' @importFrom rhdf5 H5Fopen H5Fclose H5Dopen H5Dclose h5writeAttribute -addMissingStringPlaceholderAttribute <- function(file, path, placeholder) { +addMissingPlaceholderAttribute <- function(file, path, placeholder) { fhandle <- H5Fopen(file) on.exit(H5Fclose(fhandle), add=TRUE) dhandle <- H5Dopen(fhandle, path) @@ -295,5 +300,8 @@ addMissingStringPlaceholderAttribute <- function(file, path, placeholder) { #' @export .chooseMissingStringPlaceholder <- function(...) chooseMissingStringPlaceholder(...) +#' @export +addMissingStringPlaceholderAttribute <- function(...) addMissingPlaceholderAttribute(...) + #' @export .addMissingStringPlaceholderAttribute <- function(...) addMissingStringPlaceholderAttribute(...) diff --git a/man/stageDataFrame.Rd b/man/stageDataFrame.Rd index 447968e..80454f6 100644 --- a/man/stageDataFrame.Rd +++ b/man/stageDataFrame.Rd @@ -2,8 +2,9 @@ % Please edit documentation in R/stageDataFrame.R \name{stageObject,DataFrame-method} \alias{stageObject,DataFrame-method} -\alias{addMissingStringPlaceholderAttribute} +\alias{addMissingPlaceholderAttribute} \alias{chooseMissingStringPlaceholder} +\alias{addMissingStringPlaceholderAttribute} \alias{.addMissingStringPlaceholderAttribute} \alias{.chooseMissingStringPlaceholder} \title{Stage a DataFrame} @@ -15,7 +16,8 @@ child = FALSE, df.name = "simple", mcols.name = "mcols", - meta.name = "other" + meta.name = "other", + .version = 2 ) } \arguments{ @@ -35,6 +37,8 @@ If \code{NULL}, per-element metadata is not saved.} \item{meta.name}{String specifying the name of the directory inside \code{path} to save \code{\link{metadata}(x)}. If \code{NULL}, object metadata is not saved.} + +\item{.version}{Internal use only.} } \value{ A named list containing the metadata for \code{x}.