Skip to content

Commit

Permalink
update
Browse files Browse the repository at this point in the history
  • Loading branch information
matcasti committed Jun 30, 2024
1 parent 965e6c3 commit 078e439
Show file tree
Hide file tree
Showing 12 changed files with 264 additions and 60 deletions.
1 change: 0 additions & 1 deletion NAMESPACE
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
# Generated by roxygen2: do not edit by hand

export(calculate_angle)
export(calculate_angles_for_track)
export(plot_degrees)
export(plot_motion)
Expand Down
59 changes: 31 additions & 28 deletions R/angles.R
Original file line number Diff line number Diff line change
@@ -1,22 +1,3 @@
#' @title Calculate Angle Between Two Vectors
#' @name calculate_angle
#'
#' @param u Numeric vector representing the first vector.
#' @param v Numeric vector representing the second vector.
#'
#' @return Numeric value representing the angle in degrees.
#'
#' @export

calculate_angle <- function(u, v) {
dot_product <- sum(u * v)
magnitude_u <- sqrt(sum(u^2))
magnitude_v <- sqrt(sum(v^2))
cos_theta <- dot_product / (magnitude_u * magnitude_v)
angle <- acos(cos_theta) * 180 / pi
return(angle)
}

#' @title Calculate Angles for a Track
#' @name calculate_angles_for_track
#'
Expand All @@ -29,17 +10,39 @@ calculate_angle <- function(u, v) {
#' @export

calculate_angles_for_track <- function(track_data, x, y) {
# Check for valid input data
if (!is.data.frame(track_data)) stop("track_data must be a data frame")
if (!(x %in% names(track_data) && y %in% names(track_data))) stop("x and y must be valid column names in track_data")
if (nrow(track_data) < 3) return(rep(NA, nrow(track_data))) # Not enough points to calculate angles

n <- nrow(track_data)
angles <- numeric(n)
for (i in 2:(n - 1)) {
p1 <- track_data[i - 1, c(x, y)]
p2 <- track_data[i, c(x, y)]
p3 <- track_data[i + 1, c(x, y)]
angles <- rep(NA, n) # Pre-allocate the angles vector

# Extract coordinates
x_coords <- track_data[[x]]
y_coords <- track_data[[y]]

# Calculate differences between consecutive points
dx <- diff(x_coords)
dy <- diff(y_coords)

# Calculate vectors for points 1:(n-2), 2:(n-1), and 3:n
u_x <- dx[1:(n-2)]
u_y <- dy[1:(n-2)]
v_x <- dx[2:(n-1)]
v_y <- dy[2:(n-1)]

u <- as.numeric(p2 - p1)
v <- as.numeric(p3 - p2)
# Calculate dot products and magnitudes
dot_products <- u_x * v_x + u_y * v_y
magnitudes_u <- sqrt(u_x^2 + u_y^2)
magnitudes_v <- sqrt(v_x^2 + v_y^2)

# Calculate cosine of angles, handle numerical issues
cos_theta <- pmin(1, pmax(-1, dot_products / (magnitudes_u * magnitudes_v)))

# Calculate angles in degrees
angles[2:(n - 1)] <- acos(cos_theta) * 180 / pi

angles[i] <- calculate_angle(u, v)
}
return(angles)
}

16 changes: 11 additions & 5 deletions R/plot-motion.R
Original file line number Diff line number Diff line change
Expand Up @@ -36,22 +36,28 @@ plot_motion <- function(data, x, y, frames) {

plot_degrees <- function(data, x, y, joint_ids, frames, plot = TRUE) {

angle <- NULL

data$angle <- NA
x_var <- deparse(substitute(x))
y_var <- deparse(substitute(y))
joint_var <- deparse(substitute(joint_ids))
frame_var <- deparse(substitute(frames))

unique_tids <- unique(data[[frame_var]])
unique_frames <- unique(data[[frame_var]])

for (tid in unique_tids) {
data[data[[frame_var]] == tid, "angle"] <- calculate_angles_for_track(data[data[[frame_var]] == tid,], x_var, y_var)
for (one_frame in unique_frames) {
ind <- data[[frame_var]] == one_frame
data[ind, "angle"] <- calculate_angles_for_track(data[ind,], x_var, y_var)
}

if(!plot) return(data)
if(!plot) {
out_data <- data[,c(joint_var, frame_var, x_var, y_var, "angle")]
return(out_data)
}

# Plot the data using ggplot2
ggplot2::ggplot(data = data[data$angle != 0,],
ggplot2::ggplot(data = data[!is.na(data$angle),],
mapping = ggplot2::aes(x = .data[[frame_var]]/max(.data[[frame_var]]), y = angle, col = .data[[frame_var]])) +
ggplot2::facet_grid(ggplot2::vars(.data[[joint_var]]), scales = "free_y") +
ggplot2::geom_point(na.rm = T) +
Expand Down
57 changes: 55 additions & 2 deletions README.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,59 @@ devtools::install_github("matcasti/kinemov")

You can try using the example dataset `gait` this way:

```r
plot_motion(gait, x_coord, y_coord, frame)
```{r}
library(kinemov)
plot_motion(gait, x_coord, y_coord, frame)
```

You can also plot the degrees between joints in this way:

```{r}
fig <- plot_degrees(gait, x_coord, y_coord, joint, frame)
fig
```

As it is a ggplot object, you can further customize the output object:

```{r}
library(ggplot2)
library(scales)
fig +
labs(title = "Gait Arthrokinematics",
subtitle = "Assessed through manual motion capture with ImageJ",
caption = "Source: Own elaboration") +
scale_color_viridis_c(option = "C") +
scale_x_continuous(labels = label_percent()) +
theme(plot.background = element_rect(fill = "black"),
panel.background = element_rect(fill = "black"),
strip.background = element_rect(fill = "black"),
legend.background = element_rect(fill = "black"),
panel.grid = element_blank(),
text = element_text(colour = "white"),
axis.text = element_text(colour = "white"))
```

And from the `plot_degrees()` function, you can also only extract the degrees by specifying `plot = FALSE`:

```{r}
out <- plot_degrees(gait, x_coord, y_coord, joint, frame, plot = FALSE)
subset(out, !is.na(angle)) |> head()
```

One can further process the output data.frame to better describe the angles for each joint and for each frame:

```{r}
library(data.table)
out <- as.data.table(out)
out[i = !is.na(angle),
j = list(min = min(angle),
mean = mean(angle),
median = median(angle),
max = max(angle)) |>
lapply(round),
by = joint]
```
76 changes: 75 additions & 1 deletion README.md
Original file line number Diff line number Diff line change
Expand Up @@ -31,5 +31,79 @@ devtools::install_github("matcasti/kinemov")
You can try using the example dataset `gait` this way:

``` r
plot_motion(gait, x_coord, y_coord, frame)
library(kinemov)

plot_motion(gait, x_coord, y_coord, frame)
```

<img src="man/figures/README-unnamed-chunk-2-1.png" width="100%" />

You can also plot the degrees between joints in this way:

``` r
fig <- plot_degrees(gait, x_coord, y_coord, joint, frame)
fig
```

<img src="man/figures/README-unnamed-chunk-3-1.png" width="100%" />

As it is a ggplot object, you can further customize the output object:

``` r
library(ggplot2)
library(scales)

fig +
labs(title = "Gait Arthrokinematics",
subtitle = "Assessed through manual motion capture with ImageJ",
caption = "Source: Own elaboration") +
scale_color_viridis_c(option = "C") +
scale_x_continuous(labels = label_percent()) +
theme(plot.background = element_rect(fill = "black"),
panel.background = element_rect(fill = "black"),
strip.background = element_rect(fill = "black"),
legend.background = element_rect(fill = "black"),
panel.grid = element_blank(),
text = element_text(colour = "white"),
axis.text = element_text(colour = "white"))
```

<img src="man/figures/README-unnamed-chunk-4-1.png" width="100%" />

And from the `plot_degrees()` function, you can also only extract the
degrees by specifying `plot = FALSE`:

``` r
out <- plot_degrees(gait, x_coord, y_coord, joint, frame, plot = FALSE)

subset(out, !is.na(angle)) |> head()
#> joint frame x_coord y_coord angle
#> 29 2 1 123.0 340.0 125.0958
#> 30 2 2 123.0 339.0 133.8656
#> 31 2 3 122.5 338.0 136.2633
#> 32 2 4 123.5 337.0 126.2360
#> 33 2 5 123.5 337.5 121.2637
#> 34 2 6 124.0 336.0 119.3529
```

One can further process the output data.frame to better describe the
angles for each joint and for each frame:

``` r
library(data.table)

out <- as.data.table(out)
out[i = !is.na(angle),
j = list(min = min(angle),
mean = mean(angle),
median = median(angle),
max = max(angle)) |>
lapply(round),
by = joint]
#> joint min mean median max
#> <int> <num> <num> <num> <num>
#> 1: 2 119 130 129 144
#> 2: 3 15 39 38 56
#> 3: 4 6 28 19 74
#> 4: 5 1 18 17 40
```
19 changes: 0 additions & 19 deletions man/calculate_angle.Rd

This file was deleted.

Binary file added man/figures/README-unnamed-chunk-2-1.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Binary file added man/figures/README-unnamed-chunk-3-1.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Binary file added man/figures/README-unnamed-chunk-4-1.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
8 changes: 4 additions & 4 deletions tests/testthat.R
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@
# * https://r-pkgs.org/testing-design.html#sec-tests-files-overview
# * https://testthat.r-lib.org/articles/special-files.html

# library(testthat)
# library(kinemov)
#
# test_check("kinemov")
library(testthat)
library(kinemov)

test_check("kinemov")
30 changes: 30 additions & 0 deletions tests/testthat/test-angles.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,30 @@
test_that("calculate_angles_for_track works correctly", {
# Create sample data
track_data <- data.frame(
x = c(1, 2, 3, 4, 5),
y = c(1, 2, 1, 2, 1)
)

# Calculate angles
angles <- calculate_angles_for_track(track_data, "x", "y")

# Expected results
expected_angles <- c(NA, 90, 90, 90, NA)

# Check if the angles are as expected (within a tolerance)
expect_equal(angles, expected_angles, tolerance = 1e-6)

# Test with insufficient points
track_data_insufficient <- data.frame(
x = c(1, 2),
y = c(1, 2)
)
angles_insufficient <- calculate_angles_for_track(track_data_insufficient, "x", "y")
expect_equal(angles_insufficient, c(NA, NA))

# Test with missing column names
expect_error(calculate_angles_for_track(track_data, "a", "b"), "x and y must be valid column names in track_data")

# Test with incorrect data type
expect_error(calculate_angles_for_track(list(a = 1, b = 2), "x", "y"), "track_data must be a data frame")
})
58 changes: 58 additions & 0 deletions tests/testthat/test-plot_motion.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,58 @@
test_that("plot_motion generates a ggplot object", {
# Create sample data
sample_data <- data.frame(
x = c(1, 2, 3, 4, 5, 1+1, 2+2, 3+3, 4+4, 5+5),
y = c(1, 1, 1, 1, 1, 2, 2, 2, 2, 2),
frames = rep(1:5, 2)
)

# Generate the plot
plot <- plot_motion(sample_data, x, y, frames)

# Check if the output is a ggplot object
expect_s3_class(plot, "ggplot")
})

test_that("plot_degrees generates a ggplot object and calculates angles correctly", {
# Create sample data
sample_data <- data.frame(
x = c(1, 2, 3, 4, 5, 1+1, 2+2, 3+3, 4+4, 5+5, 1, 2, 3, 4, 5),
y = c(1, 1, 1, 1, 1, 2, 2, 2, 2, 2, 3, 3, 3, 3, 3),
joint_ids = rep(1:3, each = 5),
frames = rep(1:5, 3)
)

# Generate the plot
plot <- plot_degrees(sample_data, x, y, joint_ids, frames)

# Check if the output is a ggplot object
expect_s3_class(plot, "ggplot")

# Check if the angles are calculated correctly
angle_data <- plot_degrees(sample_data, x, y, joint_ids, frames, plot = FALSE)
expect_true("angle" %in% names(angle_data))

# Check the angle values
expected_angles <- c(NA, NA, NA, NA, NA, 90, 126.8, 143.1,
151.9, 157.3, NA, NA, NA, NA, NA)
expect_equal(angle_data$angle, expected_angles, tolerance = 1e-3)
})

test_that("plot_degrees returns data with angle measurements when plot is FALSE", {
# Create sample data
sample_data <- data.frame(
x = c(1, 2, 3, 4, 5, 1+1, 2+2, 3+3, 4+4, 5+5, 1, 2, 3, 4, 5),
y = c(1, 1, 1, 1, 1, 2, 2, 2, 2, 2, 3, 3, 3, 3, 3),
joint_ids = rep(1:3, each = 5),
frames = rep(1:5, 3)
)

# Get the angle data
angle_data <- plot_degrees(sample_data, x, y, joint_ids, frames, plot = FALSE)

# Check if the output is a data frame
expect_s3_class(angle_data, "data.frame")

# Check if the angle column exists
expect_true("angle" %in% names(angle_data))
})

0 comments on commit 078e439

Please sign in to comment.