File: readAtomicVector.R

package info (click to toggle)
r-bioc-alabaster.base 1.6.1%2Bds-1
  • links: PTS, VCS
  • area: main
  • in suites: experimental
  • size: 1,652 kB
  • sloc: cpp: 11,377; sh: 29; makefile: 2
file content (92 lines) | stat: -rw-r--r-- 2,950 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
#' Read an atomic vector from disk
#'
#' Read a vector consisting of atomic elements from its on-disk representation.
#' This is usually not directly called by users, but is instead called by dispatch in \code{\link{readObject}}.
#'
#' @param path Path to a directory created with any of the vector methods for \code{\link{saveObject}}.
#' @param metadata Named list containing metadata for the object, see \code{\link{readObjectFile}} for details.
#' @param ... Further arguments, ignored.
#'
#' @return 
#' The vector described by \code{info}.
#'
#' @seealso
#' \code{"\link{saveObject,integer-method}"}, for one of the staging methods.
#'
#' @author Aaron Lun
#' 
#' @examples
#' tmp <- tempfile()
#' saveObject(setNames(runif(26), letters), tmp)
#' readObject(tmp)
#' 
#' @export
#' @aliases loadAtomicVector
readAtomicVector <- function(path, metadata, ...) {
    fpath <- file.path(path, "contents.h5")
    fhandle <- H5Fopen(fpath, flags="H5F_ACC_RDONLY")
    on.exit(H5Fclose(fhandle), add=TRUE, after=FALSE)

    host <- "atomic_vector"
    ghandle <- H5Gopen(fhandle, host)
    on.exit(H5Gclose(ghandle), add=TRUE, after=FALSE)
    expected.type <- h5_read_attribute(ghandle, "type")

    vhandle <- H5Dopen(ghandle, "values")
    on.exit(H5Dclose(vhandle), add=TRUE, after=FALSE)
    contents <- H5Dread(vhandle, drop=TRUE)
    missing.placeholder <- h5_read_attribute(vhandle, missingPlaceholderName, check=TRUE, default=NULL)

    contents <- h5_cast(contents, expected.type=expected.type, missing.placeholder=missing.placeholder)
    if (expected.type == "string") {
        if (H5Aexists(ghandle, "format")) {
            format <- h5_read_attribute(ghandle, "format")
            if (format == "date") {
                contents <- as.Date(contents)
            } else if (format == "date-time") {
                contents <- as.Rfc3339(contents)
            }
        }
    }

    if (h5_object_exists(ghandle, "names")) {
        names(contents) <- h5_read_vector(ghandle, "names")
    }

    contents
}

#######################################
########### OLD STUFF HERE ############
#######################################

#' @export
loadAtomicVector <- function(info, project, ...) {
    fpath <- acquireFile(project, info$path)
    meta <- info$atomic_vector

    df <- read.csv3(fpath, compression=meta$compression, nrows=meta$length)
    output <- df[,ncol(df)]
    type <- meta$type

    if (type == "string") {
        format <- meta$format
        if (!is.null(format)) {
            if (format == "date") {
                output <- as.Date(output)
            } else if (format == "date-time") {
                output <- .cast_datetime(output)
            } else {
                output <- as.character(output)
            }
        }
    } else {
        stopifnot(.is_atomic(type))
        output <- .cast_atomic(output, type)
    }

    if (isTRUE(meta$names)) {
        names(output) <- df[,1]
    }
    output 
}