jord-2.0.0.0: Geographical Position Calculations
Copyright(c) 2020 Cedric Liegeois
LicenseBSD3
MaintainerCedric Liegeois <ofmooseandmen@yahoo.fr>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Geo.Jord.GreatCircle

Description

Geographical Position calculations on great circles, i.e. using a sphere to represent the celestial body that positions refer to.

In order to use this module you should start with the following imports:

import qualified Data.Geo.Jord.Geodetic as Geodetic
import qualified Data.Geo.Jord.GreatCircle as GreatCircle

All functions are implemented using the vector-based approached described in Gade, K. (2010). A Non-singular Horizontal Position Representation

Synopsis

The GreatCircle type

data GreatCircle a Source #

A circle on the surface of a sphere which lies in a plane passing through the sphere centre. Every two distinct and non-antipodal points define a unique Great Circle.

It is internally represented as its normal vector - i.e. the normal vector to the plane containing the great circle.

Instances

Instances details
Eq a => Eq (GreatCircle a) Source # 
Instance details

Defined in Data.Geo.Jord.GreatCircle

Spherical a => Show (GreatCircle a) Source # 
Instance details

Defined in Data.Geo.Jord.GreatCircle

through :: Spherical a => HorizontalPosition a -> HorizontalPosition a -> Maybe (GreatCircle a) Source #

through p1 p2 returns the GreatCircle passing by both positions p1 and p2 (in this direction). For example:

>>> let p1 = Geodetic.s84Pos 45.0 (-143.5)
>>> let p2 = Geodetic.s84Pos 46.0 14.5
>>> GreatCircle.through p1 p2
Just Great Circle { through 45°0'0.000"N,143°30'0.000"W (S84) & 46°0'0.000"N,14°30'0.000"E (S84) }

Returns Nothing if given positions are equal or p1 is antipode of p2.

headingOn :: Spherical a => HorizontalPosition a -> Angle -> GreatCircle a Source #

headingOn p b returns the GreatCircle passing by position p and heading on bearing b. For example:

>>> let p = Geodetic.s84Pos 45.0 (-143.5)
>>> let b = Angle.decimalDegrees 33.0
>>> GreatCircle.headingOn p b
Great Circle { by 45°0'0.000"N,143°30'0.000"W (S84) & heading on 33°0'0.000" }

The MinorArc type

data MinorArc a Source #

Oriented minor arc of a great circle between two positions: shortest path between positions on a great circle.

Instances

Instances details
Model a => Eq (MinorArc a) Source # 
Instance details

Defined in Data.Geo.Jord.GreatCircle

Methods

(==) :: MinorArc a -> MinorArc a -> Bool #

(/=) :: MinorArc a -> MinorArc a -> Bool #

Spherical a => Show (MinorArc a) Source # 
Instance details

Defined in Data.Geo.Jord.GreatCircle

Methods

showsPrec :: Int -> MinorArc a -> ShowS #

show :: MinorArc a -> String #

showList :: [MinorArc a] -> ShowS #

minorArc :: Spherical a => HorizontalPosition a -> HorizontalPosition a -> Maybe (MinorArc a) Source #

minorArc p1 p2 returns the MinorArc from p1 to p2. For example:

>>> let p1 = Geodetic.s84Pos 45.0 (-143.5)
>>> let p2 = Geodetic.s84Pos 46.0 14.5
>>> GreatCircle.minorArc p1 p2
Just Minor Arc { from: 45°0'0.000"N,143°30'0.000"W (S84), to: 46°0'0.000"N,14°30'0.000"E (S84) }

Returns Nothing if given positions are equal.

minorArcStart :: Spherical a => MinorArc a -> HorizontalPosition a Source #

minorArcStart ma returns the start position of minor arc ma.

minorArcEnd :: Spherical a => MinorArc a -> HorizontalPosition a Source #

minorArcEnd ma returns the end position of minor arc ma.

Calculations

data Side Source #

Side of a position w.r.t. to a great circle.

Constructors

LeftOf

position is left of the great circle.

RightOf

position is right of the great circle.

None

position is on the great circle, or the great circle is undefined.

Instances

Instances details
Eq Side Source # 
Instance details

Defined in Data.Geo.Jord.GreatCircle

Methods

(==) :: Side -> Side -> Bool #

(/=) :: Side -> Side -> Bool #

Show Side Source # 
Instance details

Defined in Data.Geo.Jord.GreatCircle

Methods

showsPrec :: Int -> Side -> ShowS #

show :: Side -> String #

showList :: [Side] -> ShowS #

alongTrackDistance :: Spherical a => HorizontalPosition a -> MinorArc a -> Length Source #

alongTrackDistance p a computes how far position p is along a path described by the minor arc a: if a perpendicular is drawn from p to the path, the along-track distance is the signed distance from the start point to where the perpendicular crosses the path. For example:

>>> let p = Geodetic.s84Pos 53.2611 (-0.7972)
>>> let mas = Geodetic.s84Pos 53.3206 (-1.7297)
>>> let mae = Geodetic.s84Pos 53.1887 0.1334
>>> fmap (GreatCircle.alongTrackDistance p) (GreatCircle.minorArc mas mae)
Just 62.3315791km

alongTrackDistance' :: Spherical a => HorizontalPosition a -> HorizontalPosition a -> Angle -> Length Source #

alongTrackDistance' p s b computes how far Position p is along a path starting at s and heading on bearing b: if a perpendicular is drawn from p to the path, the along-track distance is the signed distance from the start point to where the perpendicular crosses the path. For example:

>>> let p = Geodetic.s84Pos 53.2611 (-0.7972)
>>> let s = Geodetic.s84Pos 53.3206 (-1.7297)
>>> let b = Angle.decimalDegrees 96.0017325
>>> GreatCircle.alongTrackDistance' p s b
62.3315791km

angularDistance :: Spherical a => HorizontalPosition a -> HorizontalPosition a -> Maybe (HorizontalPosition a) -> Angle Source #

angularDistance p1 p2 n computes the angle between the horizontal Points p1 and p2. If n is Nothing, the angle is always in [0..180], otherwise it is in [-180, +180], signed + if p1 is clockwis looking along n, - in opposite direction.

crossTrackDistance :: Spherical a => HorizontalPosition a -> GreatCircle a -> Length Source #

crossTrackDistance p gc computes the signed distance from horizontal Position p to great circle gc. Returns a negative Length if Position is left of great circle, positive Length if Position is right of great circle; the orientation of the great circle is therefore important. For example:

>>> let p = Geodetic.s84Pos 53.2611 (-0.7972)
>>> let gc1 = GreatCircle.through (Geodetic.s84Pos 51 0) (Geodetic.s84Pos 52 1)
>>> fmap (GreatCircle.crossTrackDistance p) gc1
Just -176.756870526km
>>> let gc2 = GreatCircle.through (Geodetic.s84Pos 52 1) (Geodetic.s84Pos 51 0)
>>> fmap (GreatCircle.crossTrackDistance p) gc2
Just 176.7568725km
>>> let gc3 = GreatCircle.headingOn (Geodetic.s84Pos 53.3206 (-1.7297)) (Angle.decimalDegrees 96.0)
>>> GreatCircle.crossTrackDistance p gc3
-305.665267m metres

crossTrackDistance' :: Spherical a => HorizontalPosition a -> HorizontalPosition a -> Angle -> Length Source #

crossTrackDistance' p s b computes the signed distance from horizontal Position p to the great circle passing by s and heading on bearing b.

This is equivalent to:

GreatCircle.crossTrackDistance p (GreatCircle.headingOn s b)

destination :: Spherical a => HorizontalPosition a -> Angle -> Length -> HorizontalPosition a Source #

destination p b d computes the position along the great circle, reached from position p having travelled the distance d on the initial bearing (compass angle) b. For example:

>>> let p = Geodetic.s84Pos 54 154
>>> GreatCircle.destination p (Angle.decimalDegrees 33) (Length.kilometres 1000)
61°10'44.188"N,164°10'19.254"E (S84)

Note that the bearing will normally vary before destination is reached.

distance :: Spherical a => HorizontalPosition a -> HorizontalPosition a -> Length Source #

distance p1 p2 computes the surface distance on the great circle between the positions p1 and p2. For example:

>>> GreatCircle.distance (Geodetic.northPole S84) (Geodetic.southPole S84)
20015.114352233km
>>> GreatCircle.distance (Geodetic.northPole S84) (Geodetic.northPole S84)
0.0m

enclosedBy :: Spherical a => HorizontalPosition a -> [HorizontalPosition a] -> Bool Source #

enclosedBy p ps determines whether position p is enclosed by the polygon defined by horizontal positions ps. The polygon can be opened or closed (i.e. if head ps /= last ps).

Uses the angle summation test: on a sphere, due to spherical excess, enclosed point angles will sum to less than 360°, and exterior point angles will be small but non-zero.

Always returns False if ps does not at least defines a triangle or if p is any of the ps.

Examples

Expand
>>> let malmo = Geodetic.s84Pos 55.6050 13.0038
>>> let ystad = Geodetic.s84Pos 55.4295 13.82
>>> let lund = Geodetic.s84Pos 55.7047 13.1910
>>> let helsingborg = Geodetic.s84Pos 56.0465 12.6945
>>> let kristianstad = Geodetic.s84Pos 56.0294 14.1567
>>> let polygon = [malmo, ystad, kristianstad, helsingborg, lund]
>>> let hoor = Geodetic.s84Pos 55.9295 13.5297
>>> let hassleholm = Geodetic.s84Pos 56.1589 13.7668
>>> GreatCircle.enclosedBy hoor polygon
True
>>> GreatCircle.enclosedBy hassleholm polygon
False

finalBearing :: Spherical a => HorizontalPosition a -> HorizontalPosition a -> Maybe Angle Source #

finalBearing p1 p2 computes the final bearing arriving at p2 from p1 in compass angle. Compass angles are clockwise angles from true north: 0° = north, 90° = east, 180° = south, 270° = west. The final bearing will differ from the initial bearing by varying degrees according to distance and latitude. For example:

>>> let p1 = Geodetic.s84Pos 0 1
>>> let p2 = Geodetic.s84Pos 0 0
>>> GreatCircle.finalBearing p1 p2
Just 270°0'0.000"

Returns Nothing if both positions are equals.

initialBearing :: Spherical a => HorizontalPosition a -> HorizontalPosition a -> Maybe Angle Source #

initialBearing p1 p2 computes the initial bearing from p1 to p2 in compass angle. Compass angles are clockwise angles from true north: 0° = north, 90° = east, 180° = south, 270° = west. For example:

>>> let p1 = Geodetic.s84Pos 58.643889 (-5.714722)
>>> let p2 = Geodetic.s84Pos 50.066389 (-5.714722)
>>> GreatCircle.initialBearing p1 p2
Just 180°0'0.000"

Returns Nothing if both positions are equals.

interpolated :: Spherical a => HorizontalPosition a -> HorizontalPosition a -> Double -> HorizontalPosition a Source #

interpolated p0 p1 f# computes the position at fraction f between the p0 and p1@. For example:

>>> let p1 = Geodetic.s84Pos 53.479444 (-2.245278)
>>> let p2 = Geodetic.s84Pos 55.605833 13.035833
>>> GreatCircle.interpolated p1 p2 0.5
54°47'0.805"N,5°11'41.947"E (S84)

Special conditions:

interpolated p0 p1 0.0 = p0
interpolated p0 p1 1.0 = p1
errors if f || f 1

intersection :: Spherical a => MinorArc a -> MinorArc a -> Maybe (HorizontalPosition a) Source #

Computes the intersection between the two given minor arcs of great circle. For example:

>>> let a1s = Geodetic.s84Pos 51.885 0.235
>>> let a1e = Geodetic.s84Pos 48.269 13.093
>>> let a2s = Geodetic.s84Pos 49.008 2.549
>>> let a2e = Geodetic.s84Pos 56.283 11.304
>>> GreatCircle.intersection <$> (GreatCircle.minorArc a1s a1e) <*> (GreatCircle.minorArc a2s a2e)
Just (Just 50°54'6.260"N,4°29'39.052"E (S84))

see also intersections

intersections :: Spherical a => GreatCircle a -> GreatCircle a -> Maybe (HorizontalPosition a, HorizontalPosition a) Source #

Computes the intersections between the two given GreatCircles. Two great circles intersect exactly twice unless there are equal (regardless of orientation), in which case Nothing is returned. For example:

>>> let gc1 = GreatCircle.headingOn (Geodetic.s84Pos 51.885 0.235) (Angle.decimalDegrees 108.63)
>>> let gc2 = GreatCircle.headingOn (Geodetic.s84Pos 49.008 2.549) (Angle.decimalDegrees 32.72)
>>> GreatCircle.intersections gc1 gc2
Just (50°54'6.201"N,4°29'39.401"E (S84),50°54'6.201"S,175°30'20.598"W (S84))
>>> let is = GreatCircle.intersections gc1 gc2
>>> fmap fst is == fmap (Geodetic.antipode . snd) is
True

mean :: Spherical a => [HorizontalPosition a] -> Maybe (HorizontalPosition a) Source #

mean ps computes the geographic mean horizontal position of ps, if it is defined. For example:

>>> let ps =
            [ Geodetic.s84Pos 90 0
            , Geodetic.s84Pos 60 10
            , Geodetic.s84Pos 50 (-20)
            ]
>>> GreatCircle.mean ps
Just 67°14'10.150"N,6°55'3.040"W (S84)

The geographic mean is not defined for antipodals positions (since they cancel each other).

Special conditions:

mean [] = Nothing
mean [p] = Just p
mean [p1, .., antipode p1] = Nothing

projection :: Spherical a => HorizontalPosition a -> MinorArc a -> Maybe (HorizontalPosition a) Source #

projection p ma computes the projection of the position p on the minor arc ma. Returns Nothing if the position p is the normal of the minor arc or if the projection is not within the minor arc ma (including start & end). For example:

>>> let p = Geodetic.s84Pos 53.2611 (-0.7972)
>>> let ma = fromJust (GreatCircle.minorArc (Geodetic.s84Pos 53.3206 (-1.7297)) (Geodetic.s84Pos 53.1887 0.1334))
>>> GreatCircle.projection p ma
Just Geodetic.s84Pos 53.25835330666666 (-0.7977433863888889)

side :: Spherical a => HorizontalPosition a -> HorizontalPosition a -> HorizontalPosition a -> Side Source #

side p0 p1 p2 determines whether p0 is left of, right of or on the great circle passing through p1 and p2 (in this direction). For example:

>>> GreatCircle.side (Geodetic.s84Pos 10 10) (Geodetic.s84Pos 0 0) (Geodetic.northPole S84)
RightOf
>>> GreatCircle.side (Geodetic.s84Pos 10 (-10)) (Geodetic.s84Pos 0 0) (Geodetic.northPole S84)
LeftOf
>>> GreatCircle.side (Geodetic.s84Pos 10 0) (Geodetic.s84Pos 0 0) (Geodetic.northPole S84)
None
Returns 'None' if @p1@ & @p2@ do not define a great circle (see 'through') or if any of the three position are equal.

turn :: Spherical a => HorizontalPosition a -> HorizontalPosition a -> HorizontalPosition a -> Angle Source #

turn a b c computes the angle turned from AB to BC; the angle is positive for left turn, negative for right turn and 0 if all 3 positions are aligned or if any 2 positions are equal. For example:

>>> GreatCircle.turn (Geodetic.s84Pos 0 0) (Geodetic.s84Pos 45 0) (Geodetic.s84Pos 60 (-10))
18°11'33.741"