Skip to content

Commit

Permalink
Merge pull request #1287 from M3nin0/dc-methods-doc
Browse files Browse the repository at this point in the history
fix docs and raster api call
  • Loading branch information
gilbertocamara authored Feb 12, 2025
2 parents 641bd65 + 7563c8b commit a5295f2
Show file tree
Hide file tree
Showing 2 changed files with 30 additions and 9 deletions.
37 changes: 29 additions & 8 deletions R/api_detect_change.R
Original file line number Diff line number Diff line change
Expand Up @@ -235,14 +235,15 @@
.detect_change_tile_prep <- function(dc_method, tile, ...) {
UseMethod(".detect_change_tile_prep", dc_method)
}
#' @rdname .detect_change_tile_prep
#' @noRd
#' @export
.detect_change_tile_prep.default <- function(dc_method, tile, ...) {
return(NULL)
}
#' @rdname .detect_change_tile_prep
#' @noRd
#' @export
.detect_change_tile_prep.bayts_model <- function(dc_method, tile, ..., impute_fn) {
.detect_change_tile_prep.bayts_model <-
function(dc_method, tile, ..., impute_fn) {
deseasonlize <- environment(dc_method)[["deseasonlize"]]

if (!.has(deseasonlize)) {
Expand Down Expand Up @@ -273,6 +274,14 @@
})
do.call(cbind, quantile_values)
}
#' @title Pre-process tile to run detect_change method (bayts)
#' @name .detect_change_create_timeline
#' @keywords internal
#' @noRd
#' @param dc_method Detect change method
#' @param tile Single tile of a data cube.
#' @param ... Additional parameters
#' @param impute_fn Imputation function
.detect_change_create_timeline <- function(tile) {
# Get the number of dates in the timeline
tile_tl <- .as_chr(.tile_timeline(tile))
Expand All @@ -282,7 +291,8 @@
)
tile_tl
}

#' @name .detect_change_as_polygon
#' @noRd
.detect_change_as_polygon <- function(values, block, bbox) {
# Create a template raster
template_raster <- .raster_new_rast(
Expand All @@ -306,7 +316,13 @@
# Return the segment object
return(values)
}

#' @rdname .dc_samples
#' @title Retrieve samples available in a given detect change method.
#' @name .dc_samples
#' @keywords internal
#' @noRd
#' @param dc_method Detect change method
#' @return Samples available in the dc method.
.dc_samples <- function(dc_method) {
environment(dc_method)[["samples"]]
}
Expand All @@ -319,12 +335,12 @@
.dc_bands <- function(dc_method) {
UseMethod(".dc_bands", dc_method)
}
#' @rdname .dc_bands
#' @noRd
#' @export
.dc_bands.sits_model <- function(dc_method) {
.samples_bands(.dc_samples(dc_method))
}
#' @rdname .dc_bands
#' @noRd
#' @export
.dc_bands.bayts_model <- function(dc_method) {
if (.has(.dc_samples(dc_method))) {
Expand All @@ -334,7 +350,12 @@
stats <- unlist(lapply(stats, colnames))
return(unique(stats))
}

#' @title Retrieve bands associated to detect_change method
#' @name .dc_class
#' @keywords internal
#' @noRd
#' @param dc_method Detect change method
#' @return Class of the model.
.dc_class <- function(dc_method) {
class(dc_method)[[1]]
}
2 changes: 1 addition & 1 deletion R/api_raster.R
Original file line number Diff line number Diff line change
Expand Up @@ -429,7 +429,7 @@
.raster_check_block(block = block)
}
# create raster objects
r_obj <- .raster_open_rast.terra(file = path.expand(files), ...)
r_obj <- .raster_open_rast(file = path.expand(files), ...)

# start read
if (.has_not(block)) {
Expand Down

0 comments on commit a5295f2

Please sign in to comment.