Safe Haskell | Safe-Infered |
---|
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
- type Distance = Double
- type Heading = Double
- type Speed = Double
- type Vector = (Distance, Heading)
- type Trail a = [a]
- type Circle a = (a, Distance)
- type Arc a = (Circle a, Heading, Heading)
- class (LatL a, LonL a) => Coordinate a where
- north :: Heading
- south :: Heading
- east :: Heading
- west :: Heading
- radiusOfEarth :: Double
- circumferenceOfEarth :: Double
- heading :: (Coordinate a, Coordinate b) => a -> b -> Heading
- distance :: (Coordinate a, Coordinate b) => a -> b -> Distance
- speed :: (Coordinate loc, TimeL loc, Coordinate b, TimeL b) => loc -> b -> Maybe Speed
- getVector :: (Coordinate a, Coordinate b) => a -> b -> Vector
- addVector :: Coordinate c => Vector -> c -> c
- getRadianPair :: Coordinate p => p -> (Latitude, Longitude)
- getDMSPair :: Coordinate c => c -> (Latitude, Longitude)
- divideArea :: Coordinate c => Distance -> Distance -> c -> c -> [[c]]
- interpolate :: Coordinate a => a -> a -> Double -> a
- circleIntersectionPoints :: Coordinate a => (a, Distance) -> (a, Distance) -> Maybe (a, a)
- intersectionArcsOf :: Coordinate a => [Circle a] -> [Arc a]
- maximumDistanceOfArc :: Coordinate a => a -> Arc a -> Distance
- writeGPX :: FilePath -> Trail Wpt -> IO ()
- readGPX :: FilePath -> IO (Trail Wpt)
- readGPXSegments :: FilePath -> IO [Trail Wpt]
- getUTCTime :: TimeL a => a -> Maybe UTCTime
- module Data.Geo.GPX
- data AvgMethod c
- = AvgMean
- | AvgHarmonicMean
- | AvgGeometricMean
- | AvgMedian
- | AvgEndPoints
- | AvgMinOf [AvgMethod c]
- | AvgWith ([c] -> Speed)
- data Selected a
- type PointGrouping c = Trail c -> [Selected (Trail c)]
- type TransformGrouping c = [Selected (Trail c)] -> [Selected (Trail c)]
- isSelected :: Selected a -> Bool
- isNotSelected :: Selected a -> Bool
- onSelected :: (a -> b) -> (a -> b) -> Selected a -> b
- selLength :: Selected [a] -> Int
- totalDistance :: Coordinate a => [a] -> Distance
- totalTime :: TimeL a => Trail a -> NominalDiffTime
- avgSpeeds :: (Coordinate a, TimeL a) => NominalDiffTime -> Trail a -> [(UTCTime, Speed)]
- slidingAverageSpeed :: (Coordinate a, TimeL a) => AvgMethod a -> NominalDiffTime -> Trail a -> [(UTCTime, Speed)]
- closestDistance :: Coordinate a => Trail a -> Trail a -> Maybe Distance
- convexHull :: (Eq c, Coordinate c) => [c] -> [c]
- bezierCurveAt :: (Coordinate a, TimeL a) => [UTCTime] -> Trail a -> Trail a
- bezierCurve :: (Coordinate a, TimeL a) => [Selected (Trail a)] -> Trail a
- linearTime :: (Coordinate a, TimeL a) => [a] -> [a]
- filterPoints :: PointGrouping a -> Trail a -> Trail a
- betweenSpeeds :: (Coordinate a, TimeL a) => Double -> Double -> PointGrouping a
- restLocations :: (Coordinate a, TimeL a) => Distance -> NominalDiffTime -> PointGrouping a
- spansTime :: (Coordinate a, TimeL a) => NominalDiffTime -> PointGrouping a
- everyNPoints :: Int -> PointGrouping a
- intersectionOf :: (Coordinate a, TimeL a) => [PointGrouping a] -> PointGrouping a
- invertSelection :: TransformGrouping a
- firstGrouping :: TransformGrouping a
- lastGrouping :: TransformGrouping a
- unionOf :: (Coordinate a, TimeL a) => [PointGrouping a] -> PointGrouping a
- refineGrouping :: PointGrouping a -> TransformGrouping a
- (/\) :: [Selected (Trail a)] -> TransformGrouping a
- (\/) :: [Selected (Trail a)] -> TransformGrouping a
- smoothRests :: (Coordinate a, TimeL a) => Trail a -> Trail a
- smoothSome :: (Coordinate a, TimeL a) => Trail a -> Trail a
- smoothMore :: (Coordinate a, TimeL a) => Trail a -> Trail a
- bezierPoint :: Coordinate a => [a] -> Double -> a
Types
Angles are expressed in radians from North. 0 == North pi/2 == West pi == South (32)pi == East == - (pi 2)
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
class (LatL a, LonL a) => Coordinate a whereSource
Constants
radius of the earth in meters
circumferenceOfEarth :: DoubleSource
Circumference of earth (meters)
Coordinate Functions
heading :: (Coordinate a, Coordinate b) => a -> b -> HeadingSource
Direction two points aim toward (0 = North, pi2 = West, pi = South, 3pi2 = East)
distance :: (Coordinate a, Coordinate b) => a -> b -> DistanceSource
speed :: (Coordinate loc, TimeL loc, Coordinate b, TimeL b) => loc -> b -> Maybe SpeedSource
Speed in meters per second, only if a Time
was recorded for each waypoint.
getVector :: (Coordinate a, Coordinate b) => a -> b -> VectorSource
addVector :: Coordinate 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 :: Coordinate p => p -> (Latitude, Longitude)Source
Provides a lat/lon pair of doubles in radians
getDMSPair :: Coordinate c => c -> (Latitude, Longitude)Source
divideArea :: Coordinate 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 :: Coordinate 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 :: Coordinate 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 :: Coordinate 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.
maximumDistanceOfArc :: Coordinate a => a -> Arc a -> DistanceSource
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
getUTCTime :: TimeL a => a -> Maybe UTCTimeSource
module Data.Geo.GPX
Types
AvgMean | Obtain the |
AvgHarmonicMean | Obtain the |
AvgGeometricMean | Obtain the |
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) |
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
isSelected :: Selected a -> BoolSource
isNotSelected :: Selected a -> BoolSource
onSelected :: (a -> b) -> (a -> b) -> Selected a -> bSource
Trail Functions
Queries
totalDistance :: Coordinate a => [a] -> DistanceSource
Find the total distance traveled
totalTime :: TimeL a => Trail a -> NominalDiffTimeSource
avgSpeeds :: (Coordinate 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 :: (Coordinate 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 :: Coordinate 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, Coordinate 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 :: (Coordinate 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 :: (Coordinate 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 :: (Coordinate 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 NotSelect
ed by the given grouping algorithm.
Grouping Methods
betweenSpeeds :: (Coordinate 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 :: (Coordinate 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 :: (Coordinate 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 :: (Coordinate 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 Select
ed, 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 :: (Coordinate 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 :: (Coordinate a, TimeL a) => Trail a -> Trail aSource
smoothSome :: (Coordinate a, TimeL a) => Trail a -> Trail aSource
smoothMore :: (Coordinate a, TimeL a) => Trail a -> Trail aSource
Misc
bezierPoint :: Coordinate a => [a] -> Double -> aSource