Copyright | (c) 2020 Cedric Liegeois |
---|---|
License | BSD3 |
Maintainer | Cedric Liegeois <ofmooseandmen@yahoo.fr> |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
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 Data.Geo.Jord.GreatCircle import Data.Geo.Jord.Position
If you wish to use both this module and the Data.Geo.Jord.Geodesic module you must qualify both imports.
All functions are implemented using the vector-based approached described in Gade, K. (2010). A Non-singular Horizontal Position Representation
Synopsis
- data GreatCircle a
- greatCircleThrough :: Spherical a => Position a -> Position a -> Maybe (GreatCircle a)
- greatCircleHeadingOn :: Spherical a => Position a -> Angle -> GreatCircle a
- data MinorArc a
- minorArc :: Spherical a => Position a -> Position a -> Maybe (MinorArc a)
- alongTrackDistance :: Spherical a => Position a -> MinorArc a -> Length
- alongTrackDistance' :: Spherical a => Position a -> Position a -> Angle -> Length
- angularDistance :: Spherical a => Position a -> Position a -> Maybe (Position a) -> Angle
- crossTrackDistance :: Spherical a => Position a -> GreatCircle a -> Length
- crossTrackDistance' :: Spherical a => Position a -> Position a -> Angle -> Length
- destination :: Spherical a => Position a -> Angle -> Length -> Position a
- finalBearing :: Spherical a => Position a -> Position a -> Maybe Angle
- initialBearing :: Spherical a => Position a -> Position a -> Maybe Angle
- interpolate :: Spherical a => Position a -> Position a -> Double -> Position a
- intersection :: Spherical a => MinorArc a -> MinorArc a -> Maybe (Position a)
- intersections :: Spherical a => GreatCircle a -> GreatCircle a -> Maybe (Position a, Position a)
- isBetween :: Spherical a => Position a -> MinorArc a -> Bool
- isInsideSurface :: Spherical a => Position a -> [Position a] -> Bool
- mean :: Spherical a => [Position a] -> Maybe (Position a)
- surfaceDistance :: Spherical a => Position a -> Position a -> Length
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
Eq a => Eq (GreatCircle a) Source # | |
Defined in Data.Geo.Jord.GreatCircle (==) :: GreatCircle a -> GreatCircle a -> Bool # (/=) :: GreatCircle a -> GreatCircle a -> Bool # | |
Model a => Show (GreatCircle a) Source # | |
Defined in Data.Geo.Jord.GreatCircle showsPrec :: Int -> GreatCircle a -> ShowS # show :: GreatCircle a -> String # showList :: [GreatCircle a] -> ShowS # |
greatCircleThrough :: Spherical a => Position a -> Position a -> Maybe (GreatCircle a) Source #
greatCircleThrough p1 p2
returns the GreatCircle
passing by both positions p1
and p2
.
If positions are antipodal, any great circle passing through those positions will be returned.
Returns Nothing
if given positions are equal.
Examples
>>>
import Data.Geo.Jord.GreatCircle
>>>
import Data.Geo.Jord.Position
>>>
>>>
let p1 = latLongHeightPos 45.0 (-143.5) (metres 1500) S84
>>>
let p2 = latLongHeightPos 46.0 14.5 (metres 3000) S84
>>>
greatCircleThrough p1 p2 -- heights are ignored, great circle is always at surface.
Just Great Circle { through 45°0'0.000"N,143°30'0.000"W 1500.0m (S84) & 46°0'0.000"N,14°30'0.000"E 3000.0m (S84) }
greatCircleHeadingOn :: Spherical a => Position a -> Angle -> GreatCircle a Source #
greatCircleHeadingOn p b
returns the GreatCircle
passing by position p
and
heading on bearing b
.
Examples
>>>
import Data.Geo.Jord.GreatCircle
>>>
import Data.Geo.Jord.Position
>>>
>>>
let p = latLongPos 45.0 (-143.5) S84
>>>
let b = decimalDegrees 33.0
>>>
greatCircleHeadingOn p b
Great Circle { by 45°0'0.000"N,143°30'0.000"W 0.0m (S84) & heading on 33°0'0.000" }
The MinorArc
type
Oriented minor arc of a great circle between two positions: shortest path between positions on a great circle.
minorArc :: Spherical a => Position a -> Position a -> Maybe (MinorArc a) Source #
minorArc p1 p2
returns the MinorArc
from p1
to p2
.
Returns Nothing
if given positions are equal.
Examples
>>>
import Data.Geo.Jord.GreatCircle
>>>
import Data.Geo.Jord.Position
>>>
>>>
let p1 = latLongHeightPos 45.0 (-143.5) (metres 1500) S84
>>>
let p2 = latLongHeightPos 46.0 14.5 (metres 3000) S84
Just Minor Arc { from: 45°0'0.000"N,143°30'0.000"W 1500.0m (S84), to: 46°0'0.000"N,14°30'0.000"E 3000.0m (S84) }
Calculations
alongTrackDistance :: Spherical a => Position 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.
Examples
>>>
import Data.Geo.Jord.GreatCircle
>>>
import Data.Geo.Jord.Position
>>>
>>>
let p = s84Pos 53.2611 (-0.7972) zero
>>>
let g = minorArcBetween (s84Pos 53.3206 (-1.7297) zero) (s84Pos 53.1887 0.1334 zero)
>>>
fmap (alongTrackDistance p) a
Right 62.3315757km
alongTrackDistance' :: Spherical a => Position a -> Position 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.
Examples
>>>
import Data.Geo.Jord.GreatCircle
>>>
import Data.Geo.Jord.Position
>>>
>>>
let p = s84Pos 53.2611 (-0.7972) zero
>>>
let s = s84Pos 53.3206 (-1.7297) zero
>>>
let b = decimalDegrees 96.0017325
>>>
alongTrackDistance' p s b
62.3315757km
angularDistance :: Spherical a => Position a -> Position a -> Maybe (Position 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 clockwise looking along n
, - in opposite direction.
crossTrackDistance :: Spherical a => Position 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 if left of great circle,
positive Length
if Position if right of great circle; the orientation of the
great circle is therefore important:
Examples
>>>
import Data.Geo.Jord.GreatCircle
>>>
import Data.Geo.Jord.Position
>>>
>>>
let gc1 = greatCircleThrough (s84Pos 51 0 zero) (s84Pos 52 1 zero)
>>>
fmap (crossTrackDistance p) gc1
Right -176.7568725km>>>
>>>
let gc2 = greatCircleThrough (s84Pos 52 1 zero) (s84Pos 51 0 zero)
>>>
fmap (crossTrackDistance p) gc2
Right 176.7568725km>>>
>>>
let p = s84Pos 53.2611 (-0.7972) zero
>>>
let gc = greatCircleHeadingOn (s84Pos 53.3206 (-1.7297) zero) (decimalDegrees 96.0)
>>>
crossTrackDistance p gc
-305.6629 metres
crossTrackDistance' :: Spherical a => Position a -> Position 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:
crossTrackDistance
p (greatCircleHeadingOn
s b)
destination :: Spherical a => Position a -> Angle -> Length -> Position a Source #
destination p b d
computes the position along the great circle, reached from
position p
having travelled the surface distance d
on the initial bearing (compass angle) b
at constant height.
Note that the bearing will normally vary before destination is reached.
Examples
>>>
import Data.Geo.Jord.GreatCircle
>>>
import Data.Geo.Jord.Position
>>>
>>>
destination (s84Pos 54 154 (metres 15000)) (decimalDegrees 33) (kilometres 1000)
61°10'44.188"N,164°10'19.254"E 15.0km (S84)
finalBearing :: Spherical a => Position a -> Position 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.
Returns Nothing
if both positions are equals.
Examples
>>>
import Data.Geo.Jord.GreatCircle
>>>
import Data.Geo.Jord.Position
>>>
>>>
let p1 = s84Pos 0 1 (metres 12000)
>>>
let p2 = s84Pos 0 0 (metres 5000)
>>>
finalBearing p1 p2
Just 270°0'0.000">>>
>>>
finalBearing p1 p1
Nothing
initialBearing :: Spherical a => Position a -> Position 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.
Returns Nothing
if both positions are equals.
Examples
>>>
import Data.Geo.Jord.GreatCircle
>>>
import Data.Geo.Jord.Position
>>>
>>>
let p1 = s84Pos 58.643889 (-5.714722) (metres 12000)
>>>
let p2 = s84Pos 50.066389 (-5.714722) (metres 12000)
>>>
initialBearing p1 p2
Just 180°0'0.000">>>
>>>
initialBearing p1 p1
Nothing
interpolate :: Spherical a => Position a -> Position a -> Double -> Position a Source #
interpolate p0 p1 f# computes the position at fraction
f between the
p0 and
p1@.
Special conditions:
interpolate p0 p1 0.0 = p0 interpolate p0 p1 1.0 = p1
Examples
>>>
import Data.Geo.Jord.GreatCircle
>>>
import Data.Geo.Jord.Position
>>>
>>>
let p1 = s84Pos 53.479444 (-2.245278) (metres 10000)
>>>
let p2 = s84Pos 55.605833 13.035833 (metres 20000)
>>>
interpolate p1 p2 0.5
54°47'0.805"N,5°11'41.947"E 15.0km (S84)
intersection :: Spherical a => MinorArc a -> MinorArc a -> Maybe (Position a) Source #
Computes the intersection between the two given minor arcs of great circle.
see also intersections
Examples
>>>
import Data.Geo.Jord.GreatCircle
>>>
import Data.Geo.Jord.Position
>>>
>>>
let a1 = minorArcBetween (s84Pos 51.885 0.235 zero) (s84Pos 48.269 13.093 zero)
>>>
let a2 = minorArcBetween (s84Pos 49.008 2.549 zero) (s84Pos 56.283 11.304 zero)
>>>
join (intersection <$> a1 <*> a2)
Just 50°54'6.260"N,4°29'39.052"E 0.0m (S84)
intersections :: Spherical a => GreatCircle a -> GreatCircle a -> Maybe (Position a, Position a) Source #
Computes the intersections between the two given GreatCircle
s.
Two great circles intersect exactly twice unless there are equal (regardless of orientation),
in which case Nothing
is returned.
Examples
>>>
import Data.Geo.Jord.GreatCircle
>>>
import Data.Geo.Jord.Position
>>>
>>>
let gc1 = greatCircleHeadingOn (s84Pos 51.885 0.235 zero) (decimalDegrees 108.63)
>>>
let gc2 = greatCircleHeadingOn (s84Pos 49.008 2.549 zero) (decimalDegrees 32.72)
>>>
intersections gc1 gc2
Just (50°54'6.201"N,4°29'39.402"E 0.0m (S84),50°54'6.201"S,175°30'20.598"W 0.0m (S84))>>>
let i = intersections gc1 gc2
fmap fst i == fmap (antipode . snd) i>>>
True
isBetween :: Spherical a => Position a -> MinorArc a -> Bool Source #
isBetween p a
determines whether position p
is within the minor arc
of great circle a
.
If p
is not on the arc, returns whether p
is within the area bound
by perpendiculars to the arc at each point (in the same hemisphere).
isInsideSurface :: Spherical a => Position a -> [Position a] -> Bool Source #
isInsideSurface p ps
determines whether position p
is inside the surface polygon defined by
positions ps
(i.e. ignoring the height of the positions).
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.
Examples
>>>
import Data.Geo.Jord.GreatCircle
>>>
import Data.Geo.Jord.Position
>>>
>>>
let malmo = s84Pos 55.6050 13.0038 zero
>>>
let ystad = s84Pos 55.4295 13.82 zero
>>>
let lund = s84Pos 55.7047 13.1910 zero
>>>
let helsingborg = s84Pos 56.0465 12.6945 zero
>>>
let kristianstad = s84Pos 56.0294 14.1567 zero
>>>
let polygon = [malmo, ystad, kristianstad, helsingborg, lund]
>>>
let hoor = s84Pos 55.9295 13.5297 zero
>>>
let hassleholm = s84Pos 56.1589 13.7668 zero
>>>
isInsideSurface hoor polygon
True>>>
isInsideSurface hassleholm polygon
False
mean :: Spherical a => [Position a] -> Maybe (Position a) Source #
mean ps
computes the geographic mean surface position of ps
, if it is defined.
The geographic mean is not defined for antipodals positions (since they cancel each other).
Special conditions:
mean [] = Nothing mean [p] = Just p mean [p1, p2, p3] = Just circumcentre mean [p1, .., antipode p1] = Nothing
surfaceDistance :: Spherical a => Position a -> Position a -> Length Source #
surfaceDistance p1 p2
computes the surface distance on the great circle between the
positions p1
and p2
.
Examples
>>>
import Data.Geo.Jord.GreatCircle
>>>
import Data.Geo.Jord.Position
>>>
>>>
surfaceDistance (northPole S84) (southPole S84)
20015.114352233km>>>
>>>
surfaceDistance (northPole S84) (northPole S84)
0.0m