Skip to content

Commit

Permalink
OmeTiffWrapper update
Browse files Browse the repository at this point in the history
  • Loading branch information
keller-mark committed Sep 24, 2023
1 parent 116c5c9 commit 2144ac4
Show file tree
Hide file tree
Showing 4 changed files with 75 additions and 31 deletions.
3 changes: 2 additions & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,8 @@ Imports:
stats,
methods,
S4Vectors,
grDevices
grDevices,
uuid
Suggests:
testthat,
knitr,
Expand Down
2 changes: 1 addition & 1 deletion R/wrappers.R
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@


make_unique_filename <- function(file_ext) {
return(paste0("some_uuid", file_ext))
return(paste0(uuid::UUIDgenerate(output = "string"), file_ext))
}


Expand Down
76 changes: 47 additions & 29 deletions R/wrappers_images.R
Original file line number Diff line number Diff line change
Expand Up @@ -118,6 +118,9 @@ OmeTiffWrapper <- R6::R6Class("OmeTiffWrapper",
#' @field is_remote Whether or not this image is remote.
#' @keywords internal
is_remote = NULL,
#' @field local_img_uid
#' @keywords internal
local_img_uid = NULL,
#' @description
#' Create a wrapper around multiple image objects.
#' @param img_path A local filepath to an OME-TIFF file.
Expand All @@ -137,6 +140,8 @@ OmeTiffWrapper <- R6::R6Class("OmeTiffWrapper",
self$transformation_matrix <- transformation_matrix
self$is_bitmask <- is_bitmask

self$local_img_uid <- make_unique_filename(".ome.tif")

if(!is.na(img_url) && !is.na(img_path)) {
warning("Expected either img_path or img_url to be provided, but not both.")
}
Expand All @@ -147,9 +152,9 @@ OmeTiffWrapper <- R6::R6Class("OmeTiffWrapper",
#' Create the web server routes and file definition creators.
#' @param dataset_uid The ID for this dataset.
#' @param obj_i The index of this data object within the dataset.
convert_and_save = function(dataset_uid, obj_i) {
convert_and_save = function(dataset_uid, obj_i, base_dir = NA) {
if(!self$is_remote) {
super$convert_and_save(dataset_uid, obj_i)
super$convert_and_save(dataset_uid, obj_i, base_dir = base_dir)
}

# Get the file definition creator functions.
Expand All @@ -169,11 +174,18 @@ OmeTiffWrapper <- R6::R6Class("OmeTiffWrapper",
if(self$is_remote) {
return(list())
} else {
route <- VitessceConfigServerRangeRoute$new(
self$get_route_str(dataset_uid, obj_i, basename(self$img_path)),
self$img_path
)
return(list(route))
if(is.na(self$base_dir)) {
local_img_path <- self$img_path
local_img_route_path <- self$get_route_str(dataset_uid, obj_i, self$local_img_uid)
} else {
local_img_path <- file.path(self$base_dir, self$img_path)
local_img_route_path <- file_path_to_url_path(self$img_path)
}
route <- VitessceConfigServerRangeRoute$new(
local_img_route_path,
local_img_path
)
return(list(route))
}
},
#' @description
Expand All @@ -184,27 +196,8 @@ OmeTiffWrapper <- R6::R6Class("OmeTiffWrapper",
#' @return A list that can be converted to JSON.
#' @keywords internal
make_image_def = function(dataset_uid, obj_i, base_url) {
img_url <- NA
if(self$is_remote) {
img_url <- self$img_url
} else {
img_url <- self$get_url(base_url, dataset_uid, obj_i, basename(self$img_path))
}

img_def <- list(
name = self$name,
type = "ome-tiff",
url = img_url
)
metadata <- obj_list()
if(!is.na(self$transformation_matrix)) {
metadata[['transform']] = list(
matrix = self$transformation_matrix
)
}
metadata[['isBitmask']] = self$is_bitmask
img_def[['metadata']] = metadata
img_def
img_url <- self$get_img_url(base_url, dataset_uid, obj_i)
return(self$create_image_json(img_url))
},
#' @description
#' Make the file definition creator function for the raster data type.
Expand All @@ -220,13 +213,38 @@ OmeTiffWrapper <- R6::R6Class("OmeTiffWrapper",
)
)
file_def <- list(
type = DataType$RASTER,
fileType = FileType$RASTER_JSON,
options = options_def
)
return(file_def)
}
return(get_raster)
},
create_image_json = function(img_url, offsets_url = NA) {
metadata <- obj_list()
img_def <- list(
name = self$name,
type = "ome-tiff",
url = img_url
)
# TODO: offsets_url
if(!is.na(self$transformation_matrix)) {
metadata[['transform']] = list(
matrix = self$transformation_matrix
)
}
metadata[['isBitmask']] = self$is_bitmask
img_def[['metadata']] = metadata
img_def
},
get_img_url = function(base_url = "", dataset_uid = "", obj_i = "") {
if(self$is_remote) {
return(self$img_url)
}
if(!is.na(self$base_dir)) {
return(self$get_url_simple(base_url, file_path_to_url_path(self$img_path, prepend_slash = FALSE)))
}
return(self$get_url(base_url, dataset_uid, obj_i, self$local_img_uid))
}
),
)
25 changes: 25 additions & 0 deletions tests/testthat/test-wrappers.R
Original file line number Diff line number Diff line change
Expand Up @@ -46,3 +46,28 @@ test_that("file_path_to_url_path", {
# posix_with_dot_without_slash <- file_path_to_url_path("./tests/data/test.snap.mtx", prepend_slash = FALSE)
# expect_equal(posix_with_dot_without_slash, "tests/data/test.snap.mtx")
})

test_that("OmeTiffWrapper", {
w <- OmeTiffWrapper$new(img_path = "tests/data/test.ome.tiff", name = "Test")
w$local_img_uid <- "test.ome.tiff"

file_def_creator <- w$make_raster_file_def_creator("A", "0")
file_def <- file_def_creator("http://localhost:8000")

expect_equal(file_def, list(
fileType = "raster.json",
options = list(
schemaVersion = "0.0.2",
images = list(
obj_list(
name = "Test",
type = "ome-tiff",
url = "http://localhost:8000/A/0/test.ome.tiff",
metadata = list(
isBitmask = FALSE
)
)
)
)
))
})

0 comments on commit 2144ac4

Please sign in to comment.