Skip to content

Commit

Permalink
Bugfix for correct dimnames reading in dense arrays.
Browse files Browse the repository at this point in the history
Also extended tests for arrays inside DFs to the new world.
  • Loading branch information
LTLA committed Nov 28, 2023
1 parent afc5c55 commit 88f8557
Show file tree
Hide file tree
Showing 2 changed files with 17 additions and 2 deletions.
2 changes: 1 addition & 1 deletion R/readArray.R
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ readArray <- function(path, array.file.backed=TRUE, ...) {
on.exit(H5Dclose(dhandle), add=TRUE, after=FALSE)
placeholder <- h5_read_attribute(dhandle, "missing-value-placeholder", check=TRUE, default=NULL)

ndims <- length(H5Sget_simple_extent_dims(H5Dget_space(dhandle)))
ndims <- H5Sget_simple_extent_dims(H5Dget_space(dhandle))$rank
names <- load_names(ghandle, ndims)

list(type=type, names=names, transposed=(transposed != 0L), placeholder=placeholder)
Expand Down
17 changes: 16 additions & 1 deletion tests/testthat/test-stage-df.R
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,14 @@ test_that("staging of arrays within DFs works correctly", {
roundtrip$Y <- as.matrix(roundtrip$Y)
roundtrip$Z <- as.matrix(roundtrip$Z)
expect_equal(roundtrip, input)

# Works in the new world.
tmp <- tempfile()
saveObject(input, tmp)
roundtrip <- readObject(tmp)
roundtrip$Y <- as.matrix(roundtrip$Y)
roundtrip$Z <- as.matrix(roundtrip$Z)
expect_identical(roundtrip, input)
})

test_that("staging of arrays continues to work with character matrices", {
Expand All @@ -36,5 +44,12 @@ test_that("staging of arrays continues to work with character matrices", {
roundtrip$Y <- as.matrix(roundtrip$Y)
roundtrip$Z <- as.matrix(roundtrip$Z)
expect_equal(roundtrip, input)
})

# Works in the new world.
tmp <- tempfile()
saveObject(input, tmp)
roundtrip <- readObject(tmp)
roundtrip$Y <- as.matrix(roundtrip$Y)
roundtrip$Z <- as.matrix(roundtrip$Z)
expect_identical(roundtrip, input)
})

0 comments on commit 88f8557

Please sign in to comment.