gps-1.2: For manipulating GPS coordinates and trails.

Safe HaskellNone
LanguageHaskell98

Geo.Computations

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 = Double Source

Distances are expressed in meters

type Heading = Double Source

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

type Speed = Double Source

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

data Point Source

Track point is a full-fledged representation of all the data available in most GPS loggers. It is possible you don't want all this data and can just made do with coordinates (via Pnt) or a custom derivative.

Constructors

Point 

Constants

north :: Heading Source

North is 0 radians

south :: Heading Source

South, being 180 degrees from North, is pi.

east :: Heading Source

East is 270 degrees (3 pi / 2)

west :: Heading Source

West is 90 degrees (pi/2)

radiusOfEarth :: Double Source

radius of the earth in meters

circumferenceOfEarth :: Double Source

Circumference of earth (meters)

Coordinate Functions

heading :: Point -> Point -> Heading Source

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

speed :: Point -> Point -> Maybe Speed Source

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

addVector :: Vector -> Point -> Point Source

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

interpolate :: Point -> Point -> Double -> Point Source

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 :: (Point, Distance) -> (Point, Distance) -> Maybe (Point, Point) 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 :: [Circle Point] -> [Arc Point] 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.

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 -> b Source

Trail Functions

Queries

totalDistance :: [Point] -> Distance Source

Find the total distance traveled

avgSpeeds :: NominalDiffTime -> Trail Point -> [(UTCTime, Speed)] Source

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

slidingAverageSpeed :: AvgMethod Point -> NominalDiffTime -> Trail Point -> [(UTCTime, Speed)] Source

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

closestDistance :: Trail Point -> Trail Point -> Maybe Distance Source

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

convexHull :: [Point] -> [Point] 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 :: [UTCTime] -> Trail Point -> Trail Point Source

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 :: [Selected (Trail Point)] -> Trail Point Source

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 :: [Point] -> [Point] 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 a Source

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

Grouping Methods

betweenSpeeds :: Double -> Double -> PointGrouping Point Source

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 :: Distance -> NominalDiffTime -> PointGrouping Point Source

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

spansTime :: NominalDiffTime -> PointGrouping Point Source

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

everyNPoints :: Int -> PointGrouping a Source

chunk the trail into groups of N points

Group Transformations

intersectionOf :: [PointGrouping Point] -> PointGrouping Point Source

intersects the given groupings

invertSelection :: TransformGrouping a Source

Inverts the selected/nonselected segments

firstGrouping :: TransformGrouping a Source

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

lastGrouping :: TransformGrouping a Source

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

unionOf :: [PointGrouping Point] -> PointGrouping Point Source

Union all the groupings

refineGrouping :: PointGrouping a -> TransformGrouping a Source

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 a Source

Intersection binary operator

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

Union binary operator

Composite Operations (Higher Level)

smoothRests :: Trail Point -> Trail Point Source

Smooth points with rest areas using a bezierCurve.

Parameters: rest for 1 minute within 30 meters get smoothed in a bezier curve over every 8 points.

smoothTrail :: Trail Point -> Trail Point Source

Smooth every 7 points using a bezier curve

Misc

module Geo.Types