commit 37b6187947043f8aeb710cff00b9b1cdaef05fe7
parent 984b2be3466125af005397ca086f75e9c5eb2d40
Author: eamoncaddigan <eamon.caddigan@gmail.com>
Date: Thu, 22 Sep 2016 09:17:37 -0400
Handling NA flightpath altitude values as intended
Diffstat:
2 files changed, 21 insertions(+), 18 deletions(-)
diff --git a/R/distanceFromPath.R b/R/distanceFromPath.R
@@ -34,11 +34,18 @@ distanceFromPath <- function(trajectory, path) {
trajectoryCoords[, c(1,2)],
r = 20925646)
- # If the waypoints are at the same altitude, just calculate the deviation
- # from this altitude. Easy.
- if (isTRUE(all.equal(pathCoords[legIdx, 3], pathCoords[legIdx+1, 3]))) {
+
+ if (is.na(pathCoords[legIdx, 3]) || is.na(pathCoords[legIdx+1, 3])) {
+ # When a waypoint has an altidue of NA, we don't care about its altitude.
+ # Therefore, the "vertical deviation" is meaningless. Use 0.
+ vDistanceToLeg[, legIdx] <- 0
+ } else if (pathCoords[legIdx, 3] == pathCoords[legIdx+1, 3]) {
+ # If the waypoints are at the same altitude, just calculate the deviation
+ # from this altitude. Easy.
vDistanceToLeg[, legIdx] <- trajectoryCoords[, 3] - pathCoords[legIdx, 3]
} else {
+ # When waypoints have different altitudes, a flight has "deviated" when
+ # it's above the higher altitude or below the lower altitude.
vDistanceToLeg[, legIdx] <- 0
deviationAbove <- trajectoryCoords[, 3] - max(pathCoords[c(legIdx, legIdx+1), 3])
deviationBelow <- trajectoryCoords[, 3] - min(pathCoords[c(legIdx, legIdx+1), 3])
diff --git a/tests/testthat/test_distanceFromPath.R b/tests/testthat/test_distanceFromPath.R
@@ -1,9 +1,6 @@
-# TODO: Handle NA altitudes in flightpaths.
-
library(flightpathr)
context("distanceFromPath")
-distancePrecision <- 10
numPoints <- 5
fakeTrajectory <- function(waypoints, n = numPoints) {
@@ -11,7 +8,7 @@ fakeTrajectory <- function(waypoints, n = numPoints) {
coordList[[1]] <- waypoints[1, ]
for (i in seq(2, nrow(waypoints))) {
coordList[[(i-1)*2]] <- geosphere::gcIntermediate(waypoints[i-1, ],
- waypoints[i, ], n)
+ waypoints[i, ], n)
coordList[[(i-1)*2+1]] <- waypoints[i, ]
}
coordMat <- do.call(rbind, coordList)
@@ -22,13 +19,12 @@ fakeTrajectory <- function(waypoints, n = numPoints) {
# Flying from 17N to KACY with a stop over N81. Flying VFR at 3500 msl
pathMat <- matrix(c(-75.0268, 39.7065,
- -74.7577, 39.6675,
- -74.5722, 39.4513),
- nrow = 3, byrow = TRUE,
- dimnames = list(c("17N", "N81", "KACY"),
- c("lon", "lat")))
-path <- createPath(longitude = pathMat[, "lon"], latitude = pathMat[, "lat"],
- altitude = 0)
+ -74.7577, 39.6675,
+ -74.5722, 39.4513),
+ nrow = 3, byrow = TRUE,
+ dimnames = list(c("17N", "N81", "KACY"),
+ c("lon", "lat")))
+path <- createPath(longitude = pathMat[, "lon"], latitude = pathMat[, "lat"])
trajectory <- fakeTrajectory(pathMat)
trajectoryLength <- length(trajectory$longitude)
@@ -44,12 +40,12 @@ test_that("non-deviating paths have small distances for all input types", {
# expect_true(all(distanceFromPath(as.data.frame(trajectory), as.data.frame(path)) < distancePrecision))
})
-test_that("small deviations look OK", {
+test_that("small horizontal deviations look OK", {
flownPathMat <- rbind(pathMat[1:2, ],
- KORDE = c(-74.0948, 39.0976),
- pathMat[3, , drop = FALSE])
+ KORDE = c(-74.0948, 39.0976),
+ pathMat[3, , drop = FALSE])
flownTrajectory <- fakeTrajectory(flownPathMat)
- flownPath <- createPath(flownPathMat[, 1], flownPathMat[, 2], 0)
+ flownPath <- createPath(flownPathMat[, 1], flownPathMat[, 2])
trajectoryDistance <- distanceFromPath(flownTrajectory, path)$horizontal
farthestPoint <- which.max(abs(trajectoryDistance))