Skip to content

Commit

Permalink
Fix warnings when calculating circular stats on NA sets
Browse files Browse the repository at this point in the history
  • Loading branch information
QSparks committed Oct 11, 2024
1 parent 294925d commit 96860b0
Show file tree
Hide file tree
Showing 3 changed files with 20 additions and 14 deletions.
22 changes: 16 additions & 6 deletions R/generic_stats.R
Original file line number Diff line number Diff line change
Expand Up @@ -305,15 +305,18 @@ compute_circular_mean <- function(direction_degrees, date.factors, format) {
direction_degrees <- direction_degrees[valid_idx]
date.factors <- date.factors[valid_idx]

if (length(direction_degrees) == 0) {
return(NA) # If all are NA, return NA
}

# Convert directions to 'circular' objects
directions_circular <- circular::circular(direction_degrees, units = "degrees", modulo = "2pi")

# Compute circular mean
circular_mean <- tapply(directions_circular, date.factors, circular::mean.circular, na.rm = TRUE)
circular_mean <- tapply(directions_circular, date.factors, function(x) {
if (all(is.na(x))) {
return(NA) # Return NA if the entire group is NA
} else {
return(circular::mean.circular(x, na.rm = TRUE))
}
})


# Convert back to degrees
circular_mean_degrees <- as.numeric(circular_mean)
Expand Down Expand Up @@ -354,7 +357,14 @@ compute_circular_sd <- function(direction_degrees, date.factors) {
directions_circular <- circular::circular(direction_degrees, units = "degrees", modulo = "2pi")

# Compute circular standard deviation
circular_sd <- tapply(directions_circular, date.factors, circular::sd.circular, na.rm = TRUE)
circular_sd <- tapply(directions_circular, date.factors, function(x) {
if (all(is.na(x))) {
return(NA) # Return NA if the entire group is NA
} else {
return(circular::sd.circular(x, na.rm = TRUE))
}
})

circular_sd_degrees <- as.numeric(circular_sd) * (180 / pi) # Convert from radians to degrees
circular_sd_degrees[is.nan(circular_sd_degrees)] <- NA
return(circular_sd_degrees)
Expand Down
9 changes: 3 additions & 6 deletions tests/test_generic_scalar_stats.R
Original file line number Diff line number Diff line change
Expand Up @@ -62,15 +62,13 @@ climdex.pcic.test.scalar.exact.dates <- function() {
northern.hemisphere = TRUE,
calendar = "gregorian"
)
# Monthly max
result <- compute.stat.scalar(scalar_obj, stat = "max", freq = "monthly", include.exact.dates = TRUE)

# Annual max
result <- compute.stat.scalar(scalar_obj, stat = "max", freq = "annual", include.exact.dates = TRUE)
expected_max <- max(data)
max_index <- which.max(data)
expected_max_date <- dates[max_index]

computed_exact_date <- as.PCICt(result$ymd[1], cal = "gregorian")

checkEqualsNumeric(as.numeric(result$val[1]), expected_max,
msg = paste("Computed max statistic:", result$val[1],
"Expected max statistic:", expected_max))
Expand Down Expand Up @@ -117,7 +115,6 @@ climdex.pcic.test.compute.stat.scalar.sd <- function() {
# Monthly SD
result <- compute.stat.scalar(scalar_obj, stat = "sd", freq = "monthly", include.exact.dates = FALSE)
expected_sd <- sd(data)

checkEqualsNumeric(as.numeric(result[1]), expected_sd, tolerance = 1e-6,
msg = paste("Computed SD:", result[1], "Expected SD:", expected_sd))
}
Expand Down
3 changes: 1 addition & 2 deletions tests/test_generic_vector_stats.R
Original file line number Diff line number Diff line change
Expand Up @@ -304,7 +304,6 @@ climdex.pcic.test.compute.stat.vector.filtered.direction.crossing.360 <- functio
include.exact.dates = FALSE,
direction.range = c(350, 10)
)
result
filtered_speeds <- speed[direction >= 350 | direction <= 10]
expected_max_magnitude <- max(filtered_speeds)
checkEqualsNumeric(as.numeric(result$magnitude[1]), expected_max_magnitude)
Expand Down Expand Up @@ -334,7 +333,7 @@ climdex.pcic.test.compute.stat.vector.no.data.in.direction.range <- function() {
include.exact.dates = FALSE,
direction.range = c(270, 360)
)
result

result$magnitude[1]
checkTrue(is.na(result$magnitude[1]), "Expected NA result when no data is in the specified direction range.")
}
Expand Down

0 comments on commit 96860b0

Please sign in to comment.