Skip to content

Commit

Permalink
Adding return_para and some cosmetic changes
Browse files Browse the repository at this point in the history
  • Loading branch information
mhesselbarth committed Jan 14, 2024
1 parent 7f1510a commit dbf412e
Show file tree
Hide file tree
Showing 17 changed files with 95 additions and 82 deletions.
4 changes: 2 additions & 2 deletions DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Type: Package
Package: shar
Title: Species-Habitat Associations
Version: 2.2.1
Version: 2.3
Authors@R: c(person("Maximilian H.K.", "Hesselbarth", email = "[email protected]",
role = c("aut", "cre"), comment = c(ORCID = "0000-0003-1125-9918")),
person("Marco", "Sciaini", email = "[email protected]",
Expand Down Expand Up @@ -45,7 +45,7 @@ Suggests:
rmarkdown,
spatstat (>= 2.0-0),
testthat (>= 3.0.0)
RoxygenNote: 7.2.3
RoxygenNote: 7.3.0
VignetteBuilder: knitr
Encoding: UTF-8
LazyData: true
Expand Down
7 changes: 7 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,10 @@
# shar 2.3
* Improvements
* Option to return fitted parameters during `fit_point_process`
* Using `NA` instead of "NA"
* Various
* Iterations and stopping criterion are vectors instead of list during `reconstruct_algorithm`

# shar 2.2.1
* Improvements
* Simplify roxygen2 docs
Expand Down
47 changes: 36 additions & 11 deletions R/fit_point_process.R
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
#' @param n_random Integer with number of randomizations.
#' @param process Character specifying which point process model to use.
#' Either \code{"poisson"} or \code{"cluster"}.
#' @param return_para Logical if fitted parameters should be returned.
#' @param return_input Logical if the original input data is returned.
#' @param simplify Logical if only pattern will be returned if \code{n_random = 1}
#' and \code{return_input = FALSE}.
Expand All @@ -32,11 +33,8 @@
#' ecology. Chapman and Hall/CRC Press, Boca Raton. ISBN 978-1-4200-8254-8
#'
#' @export
fit_point_process <- function(pattern,
n_random = 1, process = "poisson",
return_input = TRUE,
simplify = FALSE,
verbose = TRUE){
fit_point_process <- function(pattern, n_random = 1, process = "poisson", return_para = FALSE,
return_input = TRUE, simplify = FALSE, verbose = TRUE){

# check if n_random is >= 1
if (!n_random >= 1) {
Expand All @@ -45,8 +43,6 @@ fit_point_process <- function(pattern,

}

iterations_list <- as.list(rep(NA, times = n_random))

# unmark pattern
if (spatstat.geom::is.marked(pattern)) {

Expand All @@ -72,6 +68,16 @@ fit_point_process <- function(pattern,

})

# calc parameters
if (return_para) {

number_points <- pattern$n
lambda <- spatstat.geom::intensity(pattern)

param_vec <- c(number_points = number_points,lambda = lambda)

}

} else if (process == "cluster") {

# fit cluster process
Expand All @@ -81,6 +87,18 @@ fit_point_process <- function(pattern,
correction = "best"),
method = "mincon", improve.type = "none")

# calc parameters
if (return_para) {

number_parents <- fitted_process$clustpar[["kappa"]] * spatstat.geom::area(pattern$window)
number_points <- fitted_process$mu
cluster_area <- fitted_process$clustpar[["scale"]] ^ 2 * pi

param_vec <- c(number_parents = number_parents, number_points = number_points,
cluster_area = cluster_area)

}

result <- lapply(seq_len(n_random), function(x) {

# simulate clustered pattern
Expand Down Expand Up @@ -130,13 +148,20 @@ fit_point_process <- function(pattern,

}

# set param to NA
if (!return_para) param_vec <- NA

# set names
names(result) <- paste0("randomized_", seq_len(n_random))

# combine to one list
result <- list(randomized = result, observed = pattern,
method = "fit_point_process()", energy_df = "NA",
stop_criterion = "NA", iterations = iterations_list)
result <- list(randomized = result, observed = pattern, method = "fit_point_process()",
energy_df = NA, stop_criterion = NA, iterations = NA, param = param_vec)

# add param
if (return_para) {
result$param <- param_vec
}

# set class of result
class(result) <- "rd_pat"
Expand All @@ -145,7 +170,7 @@ fit_point_process <- function(pattern,
if (!return_input) {

# set observed to NA
result$observed <- "NA"
result$observed <- NA

# check if output should be simplified
if (simplify) {
Expand Down
9 changes: 2 additions & 7 deletions R/list_to_randomized.R
Original file line number Diff line number Diff line change
Expand Up @@ -64,20 +64,15 @@ list_to_randomized <- function(list, observed = NULL) {
# return observed if present or NA if not
if (is.null(observed)) {

observed <- "NA"
observed <- NA

}

# set names
names(list) <- paste0("randomized_", seq_along(list))

# create empty iterations list
iterations_list <- as.list(rep(NA, times = length(list)))

# combine to one list
result <- list(randomized = list, observed = observed,
method = "list_to_randomized()", energy_df = "NA",
stop_criterion = "NA", iterations = iterations_list)
result <- list(randomized = list, observed = observed, method = "list_to_randomized()")

class(result) <- result_class

Expand Down
2 changes: 1 addition & 1 deletion R/plot_energy.R
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ plot_energy <- function(pattern,

}

if (all(pattern$energy_df == "NA")) {
if (!is.list(pattern$energy_df)) {

stop("There is no 'energy_df' slot. Please use pattern reconstruction for valid input data.",
call. = FALSE)
Expand Down
6 changes: 3 additions & 3 deletions R/print.rd_mar.R
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ print.rd_mar <- function(x, digits = 4, ...) {

number_patterns_obs <- 0

includes_observed <- "NA"
includes_observed <- NA

# observed pattern is present
} else {
Expand All @@ -53,7 +53,7 @@ print.rd_mar <- function(x, digits = 4, ...) {
number_patterns <- length(x$randomized) + number_patterns_obs

# calculate mean iterations
mean_iterations <- round(mean(unlist(x$iterations)), digits = digits)
mean_iterations <- round(mean(x$iterations), digits = digits)

# count stop criterions
stop_criterion <- tryCatch(expr = table(do.call(c, x$stop_criterion), useNA = "ifany"),
Expand All @@ -75,7 +75,7 @@ print.rd_mar <- function(x, digits = 4, ...) {

} else {

mean_energy <- "NA"
mean_energy <- NA

}

Expand Down
6 changes: 3 additions & 3 deletions R/print.rd_pat.R
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ print.rd_pat <- function(x,

number_patterns_obs <- 0

includes_observed <- "NA"
includes_observed <- NA

# observed pattern is present
} else {
Expand All @@ -55,7 +55,7 @@ print.rd_pat <- function(x,
number_patterns <- length(x$randomized) + number_patterns_obs

# calculate mean iterations
mean_iterations <- round(mean(unlist(x$iterations)), digits = digits)
mean_iterations <- round(mean(x$iterations), digits = digits)

# count stop criterions
stop_criterion <- tryCatch(expr = table(do.call(c, x$stop_criterion), useNA = "ifany"),
Expand All @@ -77,7 +77,7 @@ print.rd_pat <- function(x,

} else {

mean_energy <- "NA"
mean_energy <- NA

}

Expand Down
2 changes: 1 addition & 1 deletion R/print.rd_ras.R
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ print.rd_ras <- function(x, ...) {

number_raster_obs <- 0

includes_observed <- "NA"
includes_observed <- NA

# observed pattern is present
} else {
Expand Down
2 changes: 1 addition & 1 deletion R/randomize_raster.R
Original file line number Diff line number Diff line change
Expand Up @@ -193,7 +193,7 @@ randomize_raster <- function(raster,
if (!return_input) {

# set observed to NA
randomization$observed <- "NA"
randomization$observed <- NA

# check if output should be simplified
if (simplify) {
Expand Down
36 changes: 13 additions & 23 deletions R/reconstruct_algorithm.R
Original file line number Diff line number Diff line change
Expand Up @@ -24,19 +24,9 @@
#' @return list
#'
#' @keywords internal
reconstruct_algorithm <- function(pattern,
method,
n_random,
e_threshold,
max_runs,
no_change,
annealing,
weights,
r_length,
r_max,
stoyan,
verbose,
plot){
reconstruct_algorithm <- function(pattern, method, n_random, e_threshold, max_runs,
no_change, annealing, weights, r_length, r_max,
stoyan, verbose, plot){

# check if n_random is >= 1
if (n_random < 1) {
Expand Down Expand Up @@ -90,14 +80,14 @@ reconstruct_algorithm <- function(pattern,

# create empty lists for results
energy_list <- vector("list", length = n_random)
iterations_list <- vector("list", length = n_random)
stop_criterion_list <- as.list(rep("max_runs", times = n_random))
iterations_vec <- vector(mode = "numeric", length = n_random)
stop_criterion_vec <- rep("max_runs", times = n_random)
result_list <- vector("list", length = n_random)

# set names
names(energy_list) <- names_randomization
names(iterations_list) <- names_randomization
names(stop_criterion_list) <- names_randomization
names(iterations_vec) <- names_randomization
names(stop_criterion_vec) <- names_randomization
names(result_list) <- names_randomization

# calculate summary functions
Expand Down Expand Up @@ -286,8 +276,8 @@ reconstruct_algorithm <- function(pattern,
if (energy <= e_threshold || energy_counter > no_change) {

# set stop criterion due to energy
stop_criterion_list[[i]] <- ifelse(test = energy <= e_threshold,
yes = "e_threshold", no = "no_change")
stop_criterion_vec[i] <- ifelse(test = energy <= e_threshold,
yes = "e_threshold", no = "no_change")

break

Expand All @@ -302,15 +292,15 @@ reconstruct_algorithm <- function(pattern,
}

# remove NAs if stopped due to energy
if (stop_criterion_list[[i]] %in% c("e_threshold", "no_change")) {
if (stop_criterion_vec[i] %in% c("e_threshold", "no_change")) {

energy_df <- energy_df[1:j, ]

}

# save results in lists
energy_list[[i]] <- energy_df
iterations_list[[i]] <- j
iterations_vec[i] <- j
result_list[[i]] <- simulated

}
Expand All @@ -321,8 +311,8 @@ reconstruct_algorithm <- function(pattern,
# combine to one list
reconstruction <- list(randomized = result_list, observed = pattern,
method = method, energy_df = energy_list,
stop_criterion = stop_criterion_list,
iterations = iterations_list)
stop_criterion = stop_criterion_vec,
iterations = iterations_vec, param = NA)

return(reconstruction)
}
21 changes: 6 additions & 15 deletions R/reconstruct_pattern.R
Original file line number Diff line number Diff line change
Expand Up @@ -81,20 +81,11 @@
#' ecology. Chapman and Hall/CRC Press, Boca Raton. ISBN 978-1-4200-8254-8
#'
#' @export
reconstruct_pattern <- function(pattern, method = "homo",
n_random = 1,
e_threshold = 0.01,
max_runs,
no_change = Inf,
annealing = 0.01,
weights = c(1, 1),
r_length = 255,
r_max = NULL,
stoyan = 0.15,
return_input = TRUE,
simplify = FALSE,
verbose = TRUE,
plot = FALSE) {
reconstruct_pattern <- function(pattern, method = "homo", n_random = 1, e_threshold = 0.01,
max_runs = 10000, no_change = Inf, annealing = 0.01,
weights = c(1, 1), r_length = 255, r_max = NULL,
stoyan = 0.15, return_input = TRUE, simplify = FALSE,
verbose = TRUE, plot = FALSE) {

# check if correct method is selected
if (!method %in% c("homo", "hetero", "cluster")) stop("Method must be one of the following: 'homo', 'hetero', or 'cluster'.",
Expand All @@ -113,7 +104,7 @@ reconstruct_pattern <- function(pattern, method = "homo",
if (!return_input) {

# set observed to NA
reconstruction$observed <- "NA"
reconstruction$observed <- NA

# check if output should be simplified
if (simplify) {
Expand Down
Loading

0 comments on commit dbf412e

Please sign in to comment.