Skip to content

Commit

Permalink
Rename characterize_particles() to def_features()
Browse files Browse the repository at this point in the history
  • Loading branch information
zsteinmetz committed Aug 9, 2023
1 parent 84e45ef commit 845ffd9
Show file tree
Hide file tree
Showing 4 changed files with 47 additions and 45 deletions.
6 changes: 3 additions & 3 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -7,14 +7,14 @@ S3method(as_OpenSpecy,data.frame)
S3method(as_OpenSpecy,default)
S3method(as_OpenSpecy,hyperSpec)
S3method(as_OpenSpecy,list)
S3method(characterize_particles,OpenSpecy)
S3method(characterize_particles,default)
S3method(collapse_spec,OpenSpecy)
S3method(collapse_spec,default)
S3method(conform_spec,OpenSpecy)
S3method(conform_spec,default)
S3method(cor_spec,OpenSpecy)
S3method(cor_spec,default)
S3method(def_features,OpenSpecy)
S3method(def_features,default)
S3method(filter_spec,OpenSpecy)
S3method(filter_spec,default)
S3method(flatten_range,OpenSpecy)
Expand Down Expand Up @@ -54,12 +54,12 @@ export(adj_neg)
export(adj_res)
export(as_OpenSpecy)
export(c_spec)
export(characterize_particles)
export(check_lib)
export(collapse_spec)
export(conform_res)
export(conform_spec)
export(cor_spec)
export(def_features)
export(filter_spec)
export(flatten_range)
export(gen_grid)
Expand Down
43 changes: 22 additions & 21 deletions R/collapse_particles.R → R/def_features.R
Original file line number Diff line number Diff line change
@@ -1,13 +1,14 @@
#' @rdname characterize_particles
#' @title Characterize Particles
#' @rdname def_features
#' @title Define features
#'
#' @description
#' Functions for analyzing particles in spectral map oriented OpenSpecy object.
#' Functions for analyzing features, like particles, fragments, or fibers, in
#' spectral map oriented OpenSpecy object.
#'
#' @details
#' `characterize_particles()` accepts an OpenSpecy object and a logical or character vector describing which pixels correspond to particles.
#' `def_features()` accepts an OpenSpecy object and a logical or character vector describing which pixels correspond to particles.
#' `collapse_spec()` takes an OpenSpecy object with particle-specific metadata
#' (from `characterize_particles()`) and collapses the spectra to median intensities for each unique particle.
#' (from `def_features()`) and collapses the spectra to median intensities for each unique particle.
#' It also updates the metadata with centroid coordinates, while preserving the particle information on area and Feret max.
#'
#' @return
Expand All @@ -17,13 +18,13 @@
#' #Logical example
#' map <- read_extdata("CA_tiny_map.zip") |> read_any()
#' map$metadata$particles <- map$metadata$x == 0
#' identified_map <- characterize_particles(map, map$metadata$particles)
#' identified_map <- def_features(map, map$metadata$particles)
#' test_collapsed <- collapse_spec(identified_map)
#'
#' #Character example
#' map <- read_extdata("CA_tiny_map.zip") |> read_any()
#' map$metadata$particles <- ifelse(map$metadata$x == 1, "particle", "not_particle")
#' identified_map <- characterize_particles(map, map$metadata$particles)
#' identified_map <- def_features(map, map$metadata$particles)
#' test_collapsed <- collapse_spec(identified_map)
#'
#' @param object An OpenSpecy object
Expand All @@ -41,14 +42,14 @@ collapse_spec <- function(object, ...) {
UseMethod("collapse_spec")
}

#' @rdname characterize_particles
#' @rdname def_features
#'
#' @export
collapse_spec.default <- function(object, ...) {
stop("'x' needs to be of class 'OpenSpecy'")
}

#' @rdname characterize_particles
#' @rdname def_features
#'
#' @export
collapse_spec.OpenSpecy <- function(object, ...) {
Expand All @@ -66,40 +67,40 @@ collapse_spec.OpenSpecy <- function(object, ...) {
return(object)
}

#' @rdname characterize_particles
#' @rdname def_features
#'
#' @export
characterize_particles <- function(object, ...) {
UseMethod("characterize_particles")
def_features <- function(object, ...) {
UseMethod("def_features")
}

#' @rdname characterize_particles
#' @rdname def_features
#'
#' @export
characterize_particles.default <- function(object, ...) {
def_features.default <- function(object, ...) {
stop("'x' needs to be of class 'OpenSpecy'")
}

#' @rdname characterize_particles
#' @rdname def_features
#'
#' @importFrom imager label as.cimg
#' @importFrom data.table as.data.table setDT rbindlist data.table
#' @export
characterize_particles.OpenSpecy <- function(object, particles, ...) {
def_features.OpenSpecy <- function(object, particles, ...) {
if(is.logical(particles)) {
if(all(particles) | all(!particles)){
stop("Features cannot be all TRUE or all FALSE values because that ",
"would indicate that there are no distinct features")
"would indicate that there are no distinct features")
}
particles_df <- .characterize_particles(object, particles)
particles_df <- .def_features(object, particles)
} else if(is.character(particles)) {
if(length(unique(particles)) == 1) {
stop("Features cannot all have a single name because that would ",
"indicate that there are no distinct features.")
"indicate that there are no distinct features.")
}
particles_df <- rbindlist(lapply(unique(particles), function(x) {
logical_particles <- particles == x
.characterize_particles(object, logical_particles)
.def_features(object, logical_particles)
}))
} else {
stop("Features needs to be a character or logical vector.", call. = F)
Expand All @@ -119,7 +120,7 @@ characterize_particles.OpenSpecy <- function(object, particles, ...) {

#' @importFrom grDevices chull
#' @importFrom stats dist
.characterize_particles <- function(x, binary, name = NULL) {
.def_features <- function(x, binary, name = NULL) {
# Label connected components in the binary image
binary_matrix <- matrix(binary, ncol = max(x$metadata$y) + 1, byrow = T)
labeled_image <- imager::label(imager::as.cimg(binary_matrix),
Expand Down
27 changes: 14 additions & 13 deletions man/characterize_particles.Rd → man/def_features.Rd

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

16 changes: 8 additions & 8 deletions tests/testthat/test-collapse_particles.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
test_that("check that particles are identified when given logical", {
map <- read_extdata("CA_tiny_map.zip") |> read_any()
map$metadata$particles <- map$metadata$x == 0
identified_map <- characterize_particles(map, map$metadata$particles)
identified_map <- def_features(map, map$metadata$particles)
expect_true(is_OpenSpecy(identified_map))
expect_true(length(unique(identified_map$metadata$particle_id)) == 2)
expect_true(max(identified_map$metadata$area, na.rm = T) == 13)
Expand All @@ -12,7 +12,7 @@ test_that("check that particles are identified when given logical", {
test_that("check that particles are identified when given character", {
map <- read_extdata("CA_tiny_map.zip") |> read_any()
map$metadata$particles <- ifelse(map$metadata$x == 1, "particle", "not_particle")
identified_map <- characterize_particles(map, map$metadata$particles)
identified_map <- def_features(map, map$metadata$particles)
expect_true(is_OpenSpecy(identified_map))
expect_true(length(unique(identified_map$metadata$particle_id)) == 3)
expect_true(max(identified_map$metadata$area, na.rm = T) == 182)
Expand All @@ -22,7 +22,7 @@ test_that("check that particles are identified when given character", {

test_that("check that an error is thrown for invalid 'particles' input", {
map <- read_extdata("CA_tiny_map.zip") |> read_any()
expect_error(characterize_particles(map, map$metadata),
expect_error(def_features(map, map$metadata),
"Particles needs to be a character or logical vector.")
})

Expand All @@ -31,33 +31,33 @@ test_that("check that particles are identified with all TRUE or FALSE logical ve

# All TRUE case
map$metadata$particles <- rep(TRUE, nrow(map$metadata))
expect_error(identified_map <- characterize_particles(map, map$metadata$particles))
expect_error(identified_map <- def_features(map, map$metadata$particles))

# All FALSE case
map$metadata$particles <- rep("test_FALSE", nrow(map$metadata))
expect_error(identified_map <- characterize_particles(map, map$metadata$particles))
expect_error(identified_map <- def_features(map, map$metadata$particles))
})

test_that("check that the original OpenSpecy object remains unmodified", {
map <- read_extdata("CA_tiny_map.zip") |> read_any()
map2 <- map

particles <- ifelse(map$metadata$x == 1, "particle", "not_particle")
identified_map <- characterize_particles(map, particles)
identified_map <- def_features(map, particles)

expect_equal(map, map2)
})

test_that("check that collapse particles returns expected values", {
map <- read_extdata("CA_tiny_map.zip") |> read_any()
particles <- ifelse(map$metadata$x == 1, "particleA", "particleB")
identified_map <- characterize_particles(map, particles)
identified_map <- def_features(map, particles)
test_collapsed <- collapse_spec(identified_map)
expect_true(is_OpenSpecy(test_collapsed))

map <- read_extdata("CA_tiny_map.zip") |> read_any()
particles <- map$metadata$x == 1
identified_map <- characterize_particles(map, particles)
identified_map <- def_features(map, particles)
test_collapsed <- collapse_spec(identified_map)
expect_true(is_OpenSpecy(test_collapsed))

Expand Down

0 comments on commit 845ffd9

Please sign in to comment.