gps-0.9: For manipulating GPS coordinates and trails.

Data.GPS

Contents

Description

A basic GPS library with calculations for distance and speed along with helper functions for filtering/smoothing trails. All distances are in meters and time is in seconds. Speed is thus meters/second

Synopsis

Types

type Distance = DoubleSource

Distances are expressed in meters

type Heading = DoubleSource

Angles are expressed in radians from North. 0 == North pi/2 == West pi == South (32)pi == East == - (pi 2)

type Speed = DoubleSource

Speed is hard coded as meters per second

type Trail a = [a]Source

type Circle a = (a, Distance)Source

Genearlly a circle indicates a known area in which we are searching (so a center point and maximum possible distance from that point)

type Arc a = (Circle a, Heading, Heading)Source

An arc is represented as a circle, starting heading and ending heading

Constants

north :: HeadingSource

North is 0 radians

south :: HeadingSource

South, being 180 degrees from North, is pi.

east :: HeadingSource

East is 270 degrees (3 pi / 2)

west :: HeadingSource

West is 90 degrees (pi/2)

radiusOfEarth :: DoubleSource

radius of the earth in meters

circumferenceOfEarth :: DoubleSource

Circumference of earth (meters)

Coordinate Functions

heading :: (LatL a, LonL a, LatL b, LonL b) => a -> b -> HeadingSource

Direction two points aim toward (0 = North, pi2 = West, pi = South, 3pi2 = East)

distance :: (LatL a, LonL a, LatL b, LonL b) => a -> b -> DistanceSource

speed :: (LatL loc, LonL loc, TimeL loc, LatL b, LonL b, TimeL b) => loc -> b -> Maybe SpeedSource

Speed in meters per second, only if a Time was recorded for each waypoint.

getVector :: (LatL a, LonL a, LatL b, LonL b) => a -> b -> VectorSource

addVector :: (LatL c, LonL c) => Vector -> c -> cSource

Given a vector and coordinate, computes a new coordinate. Within some epsilon it should hold that if

dest = addVector (dist,heading) start

then

heading == heading start dest
dist    == distance start dest

getRadianPair :: (LatL p, LonL p) => p -> (Latitude, Longitude)Source

Provides a lat/lon pair of doubles in radians

divideArea :: (LatL c, LonL c) => Distance -> Distance -> c -> c -> [[c]]Source

divideArea vDist hDist nw se divides an area into a grid of equally spaced coordinates within the box drawn by the northwest point (nw) and southeast point (se). Because this uses floating point there might be a different number of points in some rows (the last might be too far east based on a heading from the se point).

interpolate :: (LatL a, LonL a) => a -> a -> Double -> aSource

interpolate c1 c2 w where 0 <= w <= 1 Gives a point on the line between c1 and c2 equal to c1 when w == 0 (weighted linearly toward c2).

circleIntersectionPoints :: (LatL a, LonL a) => (a, Distance) -> (a, Distance) -> Maybe (a, a)Source

Compute the points at which two circles intersect (assumes a flat plain). If the circles do not intersect or are identical then the result is Nothing.

intersectionArcsOf :: (LatL a, LonL a) => [Circle a] -> [Arc a]Source

Find the area in which all given circles intersect. The resulting area is described in terms of the bounding arcs. All cirlces must intersect at two points.

IO helpers

readGPX :: FilePath -> IO (Trail Wpt)Source

Reads a GPX file (using the GPX library) by simply concatenating all the tracks, segments, and points (trkpts, trksegs, trks) into a single Trail.

Utility

Types

data AvgMethod c Source

Constructors

AvgMean

Obtain the mean of the considered points

AvgHarmonicMean

Obtain the harmonicMean

AvgGeometricMean

Obtain the geometricMean

AvgMedian

Obtain the median of the considered points

AvgEndPoints

Compute the speed considering only the given endpoints

AvgMinOf [AvgMethod c]

Take the minimum of the speeds from the given methods

AvgWith ([c] -> Speed) 

data Selected a Source

When grouping points, lists of points are either marked as Select or NotSelect.

Constructors

Select 

Fields

unSelect :: a
 
NotSelect 

Fields

unSelect :: a
 

Instances

Functor Selected 
Eq a => Eq (Selected a) 
Ord a => Ord (Selected a) 
Show a => Show (Selected a) 

type PointGrouping c = Trail c -> [Selected (Trail c)]Source

A PointGrouping is a function that selects segments of a trail.

Grouping point _does not_ result in deleted points. It is always true that:

forall g :: PointGrouping c --> concatMap unSelect (g ts) == ts

The purpose of grouping is usually for later processing. Any desire to drop points that didn't meet a particular grouping criteria can be filled with a composition with filter (or directly via filterPoints).

type TransformGrouping c = [Selected (Trail c)] -> [Selected (Trail c)]Source

Given a selection of coordinates, transform the selected coordinates in some way (while leaving the non-selected coordinates unaffected).

Utility Functions

onSelected :: (a -> b) -> (a -> b) -> Selected a -> bSource

Trail Functions

Queries

totalDistance :: (LatL a, LonL a) => [a] -> DistanceSource

Find the total distance traveled

avgSpeeds :: (LatL a, LonL a, TimeL a) => NominalDiffTime -> Trail a -> [(UTCTime, Speed)]Source

avgSpeeds n points Average speed using a window of up to n seconds and averaging by taking the Median (AvgMedian).

slidingAverageSpeed :: (LatL a, LonL a, TimeL a) => AvgMethod a -> NominalDiffTime -> Trail a -> [(UTCTime, Speed)]Source

slidingAverageSpeed m n Average speed using a moving window of up to n seconds and an AvgMethod of m.

closestDistance :: (LatL a, LonL a) => Trail a -> Trail a -> Maybe DistanceSource

Returns the closest distance between two trails (or Nothing if a trail is empty). Inefficient implementation: O( (n * m) * log (n * m) )

convexHull :: (Eq c, LatL c, LonL c) => [c] -> [c]Source

Uses Grahams scan to compute the convex hull of the given points. This operation requires sorting of the points, so don't try it unless you have notably more memory than the list of points will consume.

Transformations

bezierCurveAt :: (LatL a, LonL a, TimeL a) => [UTCTime] -> Trail a -> Trail aSource

Construct a bezier curve using the provided trail. Construct a new trail by sampling the given bezier curve at the given times. The current implementation assumes the times of the input coordinates are available and all equal (Ex: all points are 5 seconds apart), the results will be poor if this is not the case!

bezierCurve :: (LatL a, LonL a, TimeL a) => [Selected (Trail a)] -> Trail aSource

Interpolate selected points onto a bezier curve. Note this gets exponentially more expensive with the length of the segement being transformed - it is not advisable to perform this operation on trail segements with more than ten points!

linearTime :: (LonL a, LatL a, TimeL a) => [a] -> [a]Source

Filters out any points that go backward in time (thus must not be valid if this is a trail)

filterPoints :: PointGrouping a -> Trail a -> Trail aSource

Remove all points that remain NotSelected by the given grouping algorithm.

Grouping Methods

betweenSpeeds :: (LatL a, LonL a, TimeL a) => Double -> Double -> PointGrouping aSource

Groups trail segments into contiguous points within the speed and all others outside of the speed. The speed from point p(i) to p(i+1) is associated with p(i) (execpt for the first speed value, which is associated with both the first and second point)

restLocations :: (LatL a, LonL a, TimeL a) => Distance -> NominalDiffTime -> PointGrouping aSource

A rest point means the coordinates remain within a given distance for at least a particular amount of time.

spansTime :: (LatL a, LonL a, TimeL a) => NominalDiffTime -> PointGrouping aSource

chunking points into groups spanning at most the given time interval.

everyNPoints :: Int -> PointGrouping aSource

chunk the trail into groups of N points

Group Transformations

intersectionOf :: (LatL a, LonL a, TimeL a) => [PointGrouping a] -> PointGrouping aSource

intersects the given groupings

invertSelection :: TransformGrouping aSource

Inverts the selected/nonselected segments

firstGrouping :: TransformGrouping aSource

firstGrouping f ps only the first segment remains Selected, and only if it was already selected by f.

lastGrouping :: TransformGrouping aSource

Only the last segment, if any, is selected (note: the current implementation is inefficient, using reverse)

unionOf :: (LatL a, LonL a, TimeL a) => [PointGrouping a] -> PointGrouping aSource

Union all the groupings

refineGrouping :: PointGrouping a -> TransformGrouping aSource

For every selected group, refine the selection using the second grouping method. This differs from IntersectionOf by restarting the second grouping algorithm at the beginning each group selected by the first algorithm.

(/\) :: [Selected (Trail a)] -> TransformGrouping aSource

Intersection binary operator

(\/) :: [Selected (Trail a)] -> TransformGrouping aSource

Union binary operator

Composite Operations (Higher Level)

smoothRests :: (LatL a, LonL a, TimeL a) => Trail a -> Trail aSource

smoothSome :: (LatL a, LonL a, TimeL a) => Trail a -> Trail aSource

smoothMore :: (LatL a, LonL a, TimeL a) => Trail a -> Trail aSource

Misc

bezierPoint :: (LatL a, LonL a) => [a] -> Double -> aSource