Skip to content

Commit

Permalink
closes #22. Addressed #37
Browse files Browse the repository at this point in the history
  • Loading branch information
hejtmy committed Nov 2, 2019
1 parent 3b54ee8 commit ab7ca3f
Show file tree
Hide file tree
Showing 10 changed files with 71 additions and 26 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ Roxygen: list(markdown = TRUE)
Depends:
ggplot2
Suggests:
testthat,
testthat (>= 2.1.0),
knitr,
rmarkdown,
covr
Expand Down
2 changes: 1 addition & 1 deletion NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -31,12 +31,12 @@ export(add_speeds)
export(add_time_columns)
export(add_time_diffs)
export(add_times_since_start)
export(angle_diff)
export(angle_from_positions)
export(angle_to_180)
export(angle_to_360)
export(angle_to_radian)
export(animate_path)
export(calculate_angle_differences)
export(calculate_distances)
export(calculate_speeds)
export(euclid_distance)
Expand Down
34 changes: 23 additions & 11 deletions R/navr-angle-calculations.R
Original file line number Diff line number Diff line change
@@ -1,20 +1,32 @@
#' Adds new colum angle_diff_axis where it calculates angle difference between rows
#' Creates a series of angle_diffs conversted to degrees of angukar difference where it calculates angle difference between rows
#'
#' @param rotations vector of angles in 360
#'
#' @export
#'
#' @example
calculate_angle_differences <- function(rotations){
angle_diffs <- round(c(0, diff(rotations)), 4)
angle_diffs <- angle_to_180(angle_diffs)
return(angle_diffs)
}

# converts positive and negative angles to 0-360
# asumes it is not below -360
# 390 is converted to 30, -40 to 320 etc
#' Title
#' Calculates angular difference between passed angle matrices
#'
#' @param angle1 vector of angles (in degrees)
#' @param angle2
#'
#' @return
#' @export
#'
#' @examples
angle_diff <- function(angle1, angle2) {
if(length(angle1)!=length(angle2)){
warning("lengths of the matrices don't match")
return(NULL)
}
return(navr::angle_to_180(angle2-angle1))
}

#' converts positive and negative angles to 0-360
#' @description asumes it is not below -360
#' 390 is converted to 30, -40 to 320 etc
#'
#' @param angle
#'
Expand Down Expand Up @@ -69,8 +81,8 @@ angle_to_radian <- function(angle){

#' Calculates angle from two 2d positions
#'
#' @param pos_from
#' @param pos_to
#' @param pos_from numeric(2) vector of original position
#' @param pos_to numeric(2) vector of position towards the target
#' @param zero_vec defines which axis should correspond to 0 degrees. defaults to c(0,1) (Y axis)
#'
#' @return
Expand Down
10 changes: 2 additions & 8 deletions _pkgdown.yml
Original file line number Diff line number Diff line change
Expand Up @@ -8,13 +8,7 @@ reference:
- title: Preprocessing
desc: Function to preprocess navr object. Adding time and angle columns, smoothing speeds etc.
contents:
- '`add_angle_differences`'
- '`add_distances`'
- '`add_speeds`'
- '`add_times_since_start`'
- '`add_time_columns.navr`'
- '`add_time_columns`'
- '`add_time_diffs`'
- '`prepare_navr`'
- '`add_area_boundaries`'
- '`pick_unreal_speeds`'
- '`remove_unreal_speeds.navr`'
Expand Down Expand Up @@ -77,10 +71,10 @@ reference:
- '`vector_from_angle`'
- '`smooth_vector`'
- '`angle_from_positions`'
- '`angle_diff`'
- '`angle_to_180`'
- '`angle_to_360`'
- '`angle_to_radian`'
- '`calculate_angle_differences`'
- '`calculate_distances`'
- '`calculate_speeds`'
- '`euclid_distance`'
Expand Down
16 changes: 16 additions & 0 deletions man/angle_diff.Rd

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

4 changes: 4 additions & 0 deletions man/angle_from_positions.Rd

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

5 changes: 3 additions & 2 deletions man/angle_to_360.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/calculate_angle_differences.Rd

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

18 changes: 18 additions & 0 deletions tests/testthat/test-angle_calculations.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
test_that("angle to 180 works", {
expect_equal(angle_to_180(359), -1)
expect_equal(angle_to_180(180), -180)
expect_equal(angle_to_180(179), 179)
expect_equal(angle_to_180(90), 90)
expect_equal(angle_to_180(0), 0)
expect_equal(angle_to_180(360), 0)
expect_equal(angle_to_180(-90), -90)
expect_equal(angle_to_180(-270), 90)
})

test_that("angle diff works", {
expect_warning(angle_diff(1:5, 330:335))
expect_silent(res <- angle_diff(1:5, 330:334))
expect_true(all(res == -31))
expect_equal(angle_diff(270, 0), 90)
expect_equal(angle_diff(0, 270), -90)
})
2 changes: 1 addition & 1 deletion tests/testthat/test-getting.R
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
context("Getting and subsetting")
obj <- navr_object

test_that("Data can filtered with time", {
obj_filtered <- filter_times(obj, c(58227, 58242))
expect_equal(nrow(obj_filtered$data), 412)
Expand All @@ -12,7 +13,6 @@ test_that("Data can filtered with time", {
expect_equal(nrow(obj_filtered$data), 5091)
})


test_that("Can select time_diff", {
expect_error(get_time_diffs(obj))
obj_prepped <- add_time_columns(obj)
Expand Down

0 comments on commit ab7ca3f

Please sign in to comment.