Skip to content

Commit

Permalink
Merge remote-tracking branch 'origin/master'
Browse files Browse the repository at this point in the history
  • Loading branch information
LudvigOlsen committed Oct 25, 2020
2 parents 5064353 + 10c8793 commit 98b6234
Show file tree
Hide file tree
Showing 79 changed files with 66 additions and 244 deletions.
3 changes: 0 additions & 3 deletions R/angle.R
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@



# __________________ #< 1bae15c31fc98d40b9bd4b7b5434d7b3 ># __________________
# Angle ####

Expand Down Expand Up @@ -36,7 +35,6 @@
#' @inheritParams multi_mutator_
#' @family measuring functions
#' @examples
#' \donttest{
#' # Attach packages
#' library(rearrr)
#' library(dplyr)
Expand Down Expand Up @@ -78,7 +76,6 @@
#' y_col = "y",
#' origin_fn = centroid
#' )
#' }
angle <- function(data,
x_col = NULL,
y_col = NULL,
Expand Down
15 changes: 6 additions & 9 deletions R/apply_transformation_matrix.R
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,6 @@
#' @family mutate functions
#' @inheritParams multi_mutator_
#' @examples
#' \donttest{
#' # Attach packages
#' library(rearrr)
#' library(dplyr)
Expand All @@ -73,7 +72,7 @@
#' )
#'
#' # Apply identity matrix
#' mat <- matrix(c(1,0,0,0,1,0,0,0,1), nrow=3)
#' mat <- matrix(c(1, 0, 0, 0, 1, 0, 0, 0, 1), nrow = 3)
#' apply_transformation_matrix(
#' data = df,
#' mat = mat,
Expand All @@ -84,7 +83,7 @@
#' # Apply rotation matrix
#' # 90 degrees around z-axis
#' # Origin is the most centered point
#' mat <- matrix(c(0,1,0,-1,0,0,0,0,1), nrow=3)
#' mat <- matrix(c(0, 1, 0, -1, 0, 0, 0, 0, 1), nrow = 3)
#' res <- apply_transformation_matrix(
#' data = df,
#' mat = mat,
Expand All @@ -95,9 +94,9 @@
#' # Plot the rotation
#' # z wasn't changed so we plot x and y
#' res %>%
#' ggplot(aes(x=x, y=y)) +
#' ggplot(aes(x = x, y = y)) +
#' geom_point() +
#' geom_point(aes(x=x_transformed, y=y_transformed)) +
#' geom_point(aes(x = x_transformed, y = y_transformed)) +
#' theme_minimal()
#'
#' # Apply rotation matrix to grouped data frame
Expand All @@ -112,12 +111,10 @@
#'
#' # Plot the rotation
#' res %>%
#' ggplot(aes(x=x, y=y, color=g)) +
#' ggplot(aes(x = x, y = y, color = g)) +
#' geom_point() +
#' geom_point(aes(x=x_transformed, y=y_transformed)) +
#' geom_point(aes(x = x_transformed, y = y_transformed)) +
#' theme_minimal()
#'
#' }
apply_transformation_matrix <- function(data,
mat,
cols,
Expand Down
8 changes: 4 additions & 4 deletions R/by_distance.R
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,6 @@
#' @return
#' The sorted \code{data.frame} (\code{tibble}) / \code{vector}.
#' @examples
#' \donttest{
#' # Attach packages
#' library(rearrr)
#' library(dplyr)
Expand Down Expand Up @@ -98,7 +97,8 @@
#' cols = "B",
#' origin_fn = create_origin_fn(median)
#' )$B,
#' xlab = "Position", ylab = "B"
#' xlab = "Position",
#' ylab = "B"
#' )
#' plot(
#' x = 1:10,
Expand All @@ -107,13 +107,13 @@
#' origin_fn = create_origin_fn(median),
#' shuffle_ties = TRUE
#' )$A,
#' xlab = "Position", ylab = "A"
#' xlab = "Position",
#' ylab = "A"
#' )
#'
#' # In multiple dimensions
#' df %>%
#' closest_to(cols = c("A", "B"), origin_fn = most_centered)
#' }
closest_to <- function(data,
cols = NULL,
origin = NULL,
Expand Down
4 changes: 0 additions & 4 deletions R/centering.R
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,6 @@
#' @return
#' The sorted \code{data.frame} (\code{tibble}) / \code{vector}.
#' @examples
#' \donttest{
#' # Attach packages
#' library(rearrr)
#' library(dplyr)
Expand Down Expand Up @@ -72,7 +71,6 @@
#' # Plot the centered values
#' plot(x = 1:10, y = center_max(df, col = "B")$B)
#' plot(x = 1:10, y = center_max(df, col = "B", shuffle_sides = TRUE)$B)
#' }
center_max <- function(data,
col = NULL,
shuffle_sides = FALSE) {
Expand Down Expand Up @@ -112,7 +110,6 @@ center_max <- function(data,
#' @return
#' The sorted \code{data.frame} (\code{tibble}) / \code{vector}.
#' @examples
#' \donttest{
#' # Attach packages
#' library(rearrr)
#' library(dplyr)
Expand Down Expand Up @@ -153,7 +150,6 @@ center_max <- function(data,
#' # Plot the centered values
#' plot(x = 1:10, y = center_min(df, col = "B")$B)
#' plot(x = 1:10, y = center_min(df, col = "B", shuffle_sides = TRUE)$B)
#' }
center_min <- function(data,
col = NULL,
shuffle_sides = FALSE) {
Expand Down
2 changes: 0 additions & 2 deletions R/centroid.R
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,6 @@
#' @export
#' @return Means of the supplied \code{vectors}/\code{columns}. Either as a \code{vector} or a \code{data.frame}.
#' @examples
#' \donttest{
#' # Attach packages
#' library(rearrr)
#' library(dplyr)
Expand Down Expand Up @@ -53,7 +52,6 @@
#' df %>%
#' dplyr::group_by(g) %>%
#' centroid(cols = c("x", "y", "z"))
#' }
centroid <- function(..., cols = NULL, na.rm = FALSE) {
# Apply centroid function
apply_coord_fn_(
Expand Down
2 changes: 0 additions & 2 deletions R/circularize.R
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,6 @@
#' @family forming functions
#' @inheritParams multi_mutator_
#' @examples
#' \donttest{
#' # Attach packages
#' library(rearrr)
#' library(dplyr)
Expand Down Expand Up @@ -122,7 +121,6 @@
#' )) +
#' geom_point() +
#' theme_minimal()
#' }
circularize <- function(data,
y_col = NULL,
.min = NULL,
Expand Down
2 changes: 0 additions & 2 deletions R/cluster_groups.R
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,6 @@
#' @family mutate functions
#' @family clustering functions
#' @examples
#' \donttest{
#' # Attach packages
#' library(rearrr)
#' library(dplyr)
Expand Down Expand Up @@ -131,7 +130,6 @@
#' group_col = "g"
#' )
#'
#' }
#' \dontrun{
#' # Plot 3d with plotly
#' plotly::plot_ly(
Expand Down
2 changes: 0 additions & 2 deletions R/conversion.R
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,6 @@
#'
#' Missing values (\code{NA}s) are returned as they are.
#' @examples
#' \donttest{
#' # Attach packages
#' library(rearrr)
#' library(dplyr)
Expand All @@ -26,7 +25,6 @@
#'
#' # Get back the original degrees
#' radians_to_degrees(degrees_to_radians(c(90, 180, 270)))
#' }
degrees_to_radians <- function(degrees) {
checkmate::assert_numeric(degrees)
degrees * (pi / 180)
Expand Down
2 changes: 0 additions & 2 deletions R/create_dimming_fn.R
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,6 @@
#'
#' \code{\}}
#' @examples
#' \donttest{
#' # Attach packages
#' library(rearrr)
#' library(ggplot2)
Expand Down Expand Up @@ -73,7 +72,6 @@
#' geom_point() +
#' geom_line() +
#' theme_minimal()
#' }
create_dimming_fn <- function(numerator = 1, exponent = 2, add_to_distance = 1) {

# Check arguments ####
Expand Down
2 changes: 0 additions & 2 deletions R/create_n_fn.R
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,6 @@
#' Note: The dots argument in the generated function should not to be confused with the dots
#' argument in \code{create_n_fn()}).
#' @examples
#' \donttest{
#' # Attach packages
#' library(rearrr)
#'
Expand Down Expand Up @@ -83,7 +82,6 @@
#' mean(y, na.rm = TRUE),
#' mean(z, na.rm = TRUE)
#' ))
#' }
create_n_fn <- function(fn,
use_index = FALSE,
negate = FALSE,
Expand Down
2 changes: 0 additions & 2 deletions R/create_origin_fn.R
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,6 @@
#' @return Function with the dots (\code{...}) argument that applies the \code{`fn`} function to
#' each element in \code{...} (usually one vector per dimension).
#' @examples
#' \donttest{
#' # Attach packages
#' library(rearrr)
#'
Expand Down Expand Up @@ -53,7 +52,6 @@
#' mean(y, na.rm = TRUE),
#' mean(z, na.rm = TRUE)
#' )
#' }
create_origin_fn <- function(fn, ...) {
args <- list(...)
function(...) {
Expand Down
2 changes: 0 additions & 2 deletions R/dim_values.R
Original file line number Diff line number Diff line change
Expand Up @@ -74,7 +74,6 @@
#' @family distance functions
#' @inheritParams multi_mutator_
#' @examples
#' \donttest{
#' # Attach packages
#' library(rearrr)
#' library(dplyr)
Expand Down Expand Up @@ -145,7 +144,6 @@
#' geom_point() +
#' theme_minimal() +
#' labs(x = "x", y = "y", color = "Cluster", alpha = "o_dimmed")
#' }
dim_values <- function(data,
cols,
dimming_fn = create_dimming_fn(
Expand Down
2 changes: 0 additions & 2 deletions R/distance.R
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,6 @@
#' @family measuring functions
#' @family distance functions
#' @examples
#' \donttest{
#' # Attach packages
#' library(rearrr)
#' library(dplyr)
Expand Down Expand Up @@ -60,7 +59,6 @@
#' cols = c("x", "y"),
#' origin_fn = centroid
#' )
#' }
distance <- function(data,
cols = NULL,
origin = NULL,
Expand Down
2 changes: 0 additions & 2 deletions R/expand_distances.R
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,6 @@
#' @family distance functions
#' @inheritParams multi_mutator_
#' @examples
#' \donttest{
#' # Attach packages
#' library(rearrr)
#' library(dplyr)
Expand Down Expand Up @@ -220,7 +219,6 @@
#' geom_point() +
#' theme_minimal() +
#' labs(x = "x", y = "y", color = "g")
#' }
expand_distances <- function(data,
cols = NULL,
multiplier = NULL,
Expand Down
2 changes: 0 additions & 2 deletions R/expand_distances_each.R
Original file line number Diff line number Diff line change
Expand Up @@ -90,7 +90,6 @@
#' @family distance functions
#' @inheritParams multi_mutator_
#' @examples
#' \donttest{
#' # Attach packages
#' library(rearrr)
#' library(dplyr)
Expand Down Expand Up @@ -251,7 +250,6 @@
#' geom_point() +
#' theme_minimal() +
#' labs(x = "x", y = "y", color = "g")
#' }
expand_distances_each <- function(data,
cols = NULL,
multipliers = NULL,
Expand Down
2 changes: 0 additions & 2 deletions R/flip_values.R
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,6 @@
#' @family mutate functions
#' @inheritParams multi_mutator_
#' @examples
#' \donttest{
#' # Attach packages
#' library(rearrr)
#' library(dplyr)
Expand Down Expand Up @@ -106,7 +105,6 @@
#' geom_line(aes(y = A_flip_3, color = "Flipped A (3)")) +
#' geom_hline(aes(color = "3", yintercept = 3)) +
#' theme_minimal()
#' }
flip_values <- function(data,
cols = NULL,
origin = NULL,
Expand Down
2 changes: 0 additions & 2 deletions R/generate_clusters.R
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,6 @@
#' }
#' @family clustering functions
#' @examples
#' \donttest{
#' # Attach packages
#' library(rearrr)
#' library(dplyr)
Expand Down Expand Up @@ -73,7 +72,6 @@
#' num_clusters = 5, compactness = 1.6
#' )
#'
#' }
#' \dontrun{
#' # Plot 3d with plotly
#' plotly::plot_ly(
Expand Down
Loading

0 comments on commit 98b6234

Please sign in to comment.