Skip to content

Commit

Permalink
typos
Browse files Browse the repository at this point in the history
  • Loading branch information
tobiste committed Jun 21, 2024
1 parent df8d315 commit e29ee18
Show file tree
Hide file tree
Showing 5 changed files with 62 additions and 35 deletions.
31 changes: 22 additions & 9 deletions R/plotting.R
Original file line number Diff line number Diff line change
Expand Up @@ -414,9 +414,13 @@ rose <- function(x, weights = NULL, binwidth = NULL, bins = NULL, axial = TRUE,
at = seq(0, 360 - 45, 45), cborder = TRUE, labels = TRUE,
col = "grey", dots = FALSE, dot_pch = 1, dot_cex = 1,
dot_col = "slategrey", stack = FALSE, add = FALSE, ...) {
if (missing(main) || is.null(main)) {
main <- spatstat.utils::short.deparse(substitute(x))
if (!add){
if (missing(main) || is.null(main)) {
main <- spatstat.utils::short.deparse(substitute(x))
}
circular_plot(main = main, labels = labels, at = at, cborder = cborder)
}

if (axial) {
x <- x %% 180
x[x >= 180] <- 180 - 2 * .Machine$double.eps
Expand All @@ -432,8 +436,6 @@ rose <- function(x, weights = NULL, binwidth = NULL, bins = NULL, axial = TRUE,
axial = axial
)

if (!add) circular_plot(main = main, labels = labels, at = at, cborder = cborder)

rose_histogram(freqs, ...,
col = col, axial = axial,
main = main, labels = TRUE, at = at, cborder = TRUE, add = TRUE
Expand Down Expand Up @@ -468,11 +470,11 @@ rose <- function(x, weights = NULL, binwidth = NULL, bins = NULL, axial = TRUE,
#' @importFrom graphics segments polygon
#' @name rose_geom
#' @examples
#' a <- c(0, 10, 45)
#' angles <- c(0, 10, 45)
#' radius <- c(.7, 1, .2)
#' lwd <- c(2, 1, .75)
#' col <- c(1, 2, 3)
#' rose_line(c(0, 10, 45), radius = radius, axial = FALSE, add = FALSE, lwd = lwd, col = col)
#' rose_line(angles, radius = radius, axial = FALSE, add = FALSE, lwd = lwd, col = col)
NULL

#' @rdname rose_geom
Expand Down Expand Up @@ -616,7 +618,12 @@ rose_stats <- function(x, weights = NULL, axial = TRUE, avg = c("mean", "median"
plot_points <- function(x, axial = TRUE, stack = FALSE, cex = 1, sep = 0.025, ..., scale = 1.1, add = TRUE,
main = NULL, labels = TRUE,
at = seq(0, 360 - 45, 45), cborder = TRUE) {
if (!add) circular_plot(main = main, labels = labels, at = at, cborder = cborder)
if (!add){
if (missing(main) || is.null(main)) {
main <- spatstat.utils::short.deparse(substitute(x))
}
circular_plot(main = main, labels = labels, at = at, cborder = cborder)
}

f <- ifelse(axial, 2, 1)

Expand Down Expand Up @@ -764,11 +771,17 @@ circular_lines <- function(x, y, join = FALSE, nosort = FALSE, offset = 1.1, shr
#' @examples
#' rose(san_andreas$azi, dots = TRUE, stack = TRUE, dot_cex = 0.5, dot_pch = 21)
#' plot_density(san_andreas$azi, kappa = 10, col = "seagreen", shrink = 1.5)
#' plot_density(san_andreas$azi, kappa = 10, col = "seagreen", add = FALSE, scale = .6)
plot_density <- function(x, kappa, axial = TRUE, n = 512, norm_density = TRUE, ...,
scale = 1.1, shrink,
scale = 1.1, shrink = 1,
add = TRUE, main = NULL, labels = TRUE,
at = seq(0, 360 - 45, 45), cborder = TRUE) {
if (!add) circular_plot(main = main, labels = labels, at = at, cborder = cborder)
if (!add){
if (missing(main) || is.null(main)) {
main <- spatstat.utils::short.deparse(substitute(x))
}
circular_plot(main = main, labels = labels, at = at, cborder = cborder)
}


f <- ifelse(axial, 2, 1)
Expand Down
45 changes: 27 additions & 18 deletions R/various.R
Original file line number Diff line number Diff line change
Expand Up @@ -181,19 +181,19 @@ quantise_wsm_quality <- function(x) {
#' Returns the converted azimuths, distances to the plate boundary,
#' statistics of the model, and some plots.
#'
#' @param x \code{data.frame} or `sf` object containing the coordinates of the point(s)
#' (\code{lat}, \code{lon}), the direction of
#' \eqn{\sigma_{Hmax}}{SHmax} \code{azi} and its standard deviation
#' @param x `data.frame` or `sf` object containing the coordinates of the point(s)
#' (`lat`, `lon`), the direction of
#' \eqn{\sigma_{Hmax}}{SHmax} `azi` and its standard deviation
#' \code{unc} (optional)
#' @param PoR Pole of Rotation. \code{data.frame} or object of class \code{"euler.pole"}
#' @param PoR Pole of Rotation. `data.frame` or object of class `"euler.pole"`
#' containing the geographical coordinates of the Euler pole
#' @param type Character. Type of plate boundary (optional). Can be
#' \code{"out"}, \code{"in"}, \code{"right"}, or
#' \code{"left"} for outward, inward, right-lateral, or left-lateral
#' moving plate boundaries, respectively. If \code{"none"} (the default), only
#' `"out"`, `"in"`, `"right"`, or
#' `"left"` for outward, inward, right-lateral, or left-lateral
#' moving plate boundaries, respectively. If `"none"` (the default), only
#' the PoR-equivalent azimuth is returned.
#' @param pb (optional) `sf` object of the plate boundary geometries in the geographical
#' coordinate system
#' @param pb (optional) `sf` object of the plate boundary geometries in the
#' geographical coordinate system
#' @param plot (logical). Whether to produce a plot additional to output.
#' @param ... optional arguments to [distance_from_pb()]
#'
Expand All @@ -204,13 +204,17 @@ quantise_wsm_quality <- function(x) {
#' deviation angle from predicted (`dev`), circular distance (`cdist`),
#' misfit to predicted stress direction (`nchisq`) and, if given, distance to tested
#' plate boundary (`distance`)}
#' \item{`stats`}{array with circular (weighted) mean, circular standard deviation, circular variance, circular dispersion, the 95% confidence angle, and the normalized Chi-squared test statistic}
#' \item{`test`}{list containting the test results of the (weighted) Rayleigh test against the uniform distribution about the predicted orientation.}
#' \item{`stats`}{array with circular (weighted) mean, circular standard
#' deviation, circular variance, circular median, skewness, kurtosis, the 95%
#' confidence angle, circular dispersion, and the normalized Chi-squared test
#' statistic}
#' \item{`test`}{list containing the test results of the (weighted) Rayleigh
#' test against the uniform distribution about the predicted orientation.}
#' }
#'
#' @export
#'
#' @seealso [PoR_shmax()], [distance_from_pb()], [norm_chisq()], [quick_plot()]
#' @seealso [PoR_shmax()], [distance_from_pb()], [norm_chisq()], [quick_plot()], [circular_summary()]
#'
#' @examples
#' \donttest{
Expand All @@ -234,11 +238,13 @@ stress_analysis <- function(x, PoR, type = c("none", "in", "out", "right", "left
}
prd <- res$prd

mean <- circular_mean(res$azi.PoR, 1 / x$unc)
sd <- circular_sd(res$azi.PoR, 1 / x$unc)
var <- circular_var(res$azi.PoR, 1 / x$unc)
stats <- circular_summary(res$azi.PoR, 1 / x$unc)

# mean <- circular_mean(res$azi.PoR, 1 / x$unc)
# sd <- circular_sd(res$azi.PoR, 1 / x$unc)
# var <- circular_var(res$azi.PoR, 1 / x$unc)
disp <- circular_dispersion(res$azi.PoR, prd, 1 / x$unc)
conf <- confidence_angle(res$azi.PoR, w = 1 / x$unc)
# conf <- confidence_angle(res$azi.PoR, w = 1 / x$unc)
nchisq <- norm_chisq(res$azi.PoR, prd, unc = x$unc)
rayleigh <- weighted_rayleigh(res$azi.PoR, prd, w = 1 / x$unc)

Expand All @@ -251,8 +257,11 @@ stress_analysis <- function(x, PoR, type = c("none", "in", "out", "right", "left
list(
result = res,
stats =
rbind(mean = mean, sd = sd, var = var, dispersion = disp, conf95 = conf, norm_chisq = nchisq),
test = rayleigh
rbind(mean = stats['mean'], sd = stats['sd'], var = stats['var'],
median = stats['median'], skewness = stats['skewness'], kurtosis = stats['kurtosis'],
conf95 = stats['95%CI'],
dispersion = disp, norm_chisq = nchisq),
rayleigh.test = rayleigh
)
}

Expand Down
3 changes: 2 additions & 1 deletion man/plot_density.Rd

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

4 changes: 2 additions & 2 deletions man/rose_geom.Rd

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

14 changes: 9 additions & 5 deletions man/stress_analysis.Rd

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

0 comments on commit e29ee18

Please sign in to comment.