Skip to content

Commit

Permalink
zarr_open
Browse files Browse the repository at this point in the history
  • Loading branch information
keller-mark committed May 7, 2024
1 parent fb8d744 commit aadfe01
Show file tree
Hide file tree
Showing 5 changed files with 88 additions and 1 deletion.
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,7 @@ export(zarr_create_array)
export(zarr_create_empty)
export(zarr_create_group)
export(zarr_create_zeros)
export(zarr_open)
export(zarr_open_array)
export(zarr_open_group)
export(zarr_save_array)
Expand Down
48 changes: 47 additions & 1 deletion R/creation.R
Original file line number Diff line number Diff line change
Expand Up @@ -790,4 +790,50 @@ zarr_save_array <- function(store, arr, ...) {
# Reference: https://github.com/zarr-developers/zarr-python/blob/5dd4a0e6cdc04c6413e14f57f61d389972ea937c/zarr/convenience.py#L112
store <- normalize_store_arg(store)
zarr_create_array(data=arr$get_item("..."), shape=arr$get_shape(), store=store, ...)
}
}

#' Convenience function to open a group or array using file-mode-like semantics.
#' @param store : MutableMapping or string, optional
#' Store or path to directory in file system or name of zip file.
#' @param mode : {'r', 'r+', 'a', 'w', 'w-'}, optional
#' Persistence mode: 'r' means read only (must exist); 'r+' means
#' read/write (must exist); 'a' means read/write (create if doesn't
#' exist); 'w' means create (overwrite if exists); 'w-' means create
#' (fail if exists).
#' @param path : str or NA, optional
#' The path within the store to open.
#' @param ... Additional arguments to pass to zarr_open_array or zarr_open_group.
#' @returns ZarrArray or ZarrGroup
#' @export
zarr_open <- function(store = NA, mode = NA, path = NA, ...) {
kwargs <- list(...)

if(is_na(mode)) {
mode <- "a"
}

store <- normalize_store_arg(store)
path <- normalize_storage_path(path)

if(mode %in% c("w", "w-", "x")) {
if("shape" %in% names(kwargs)) {
return(zarr_open_array(store=store, mode=mode, path=path, ...))
} else {
return(zarr_open_group(store=store, mode=mode, path=path, ...))
}
} else if(mode == "a") {
if("shape" %in% names(kwargs) || contains_array(store, path)) {
return(zarr_open_array(store=store, mode=mode, path=path, ...))
} else {
return(zarr_open_group(store=store, mode=mode, path=path, ...))
}
} else {
if(contains_array(store, path)) {
return(zarr_open_array(store=store, mode=mode, path=path, ...))
} else if(contains_group(store, path)) {
return(zarr_open_group(store=store, mode=mode, path=path, ...))
} else {
stop("PathNotFoundError(path)")
}
}
}
29 changes: 29 additions & 0 deletions man/zarr_open.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 1 addition & 0 deletions pkgdown/_pkgdown.yml
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,7 @@ reference:
- zarr_create_zeros
- zarr_create_array
- zarr_create_group
- zarr_open
- zarr_open_group
- zarr_open_array
- zarr_save_array
Expand Down
10 changes: 10 additions & 0 deletions tests/testthat/test-compat.R
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,16 @@ test_that("Can open Zarr group using convenience function", {
expect_equal(a$get_shape(), c(4))
})

test_that("Can open Zarr group or array using convenience function", {

root <- system.file("extdata", "fixtures", "v2", "data.zarr", package="pizzarr")
g <- zarr_open(root)
a <- zarr_open(root, path="1d.contiguous.lz4.i2")

expect_equal(class(g)[1], "ZarrGroup")
expect_equal(class(a)[1], "ZarrArray")
})

test_that("Can open Zarr group and read a 1D 2-byte integer array with LZ4 compression", {

root <- system.file("extdata", "fixtures", "v2", "data.zarr", package="pizzarr")
Expand Down

0 comments on commit aadfe01

Please sign in to comment.