geodetic-0.1.4: Geodetic calculations

Safe HaskellNone
LanguageHaskell2010

Data.Geo.Geodetic.Vincenty

Description

An implementation of Thaddeus Vincenty's direct and inverse geodetic algorithms. http://www.ngs.noaa.gov/PUBS_LIB/inverse.pdf

Synopsis

Documentation

>>> import Control.Monad(Monad(return))
>>> import Data.Functor(Functor(fmap))
>>> import Data.Geo.Geodetic.Bearing(modBearing)
>>> import Data.Geo.Geodetic.Ellipsoid(ans)
>>> import Data.Geo.Coordinate((<°>))

convergence :: Convergence Source

A typically acceptable convergence value.

direct Source

Arguments

:: (AsCoordinate (->) (Const Coordinate) c, AsBearing (->) (Const Bearing) b, AsEllipsoid (->) (Const Ellipsoid) e) 
=> e

reference ellipsoid

-> Convergence

convergence point to stop calculating

-> c

begin coordinate

-> b

bearing

-> Double

distance

-> VincentyDirectResult 

Vincenty direct algorithm.

>>> fmap (\c' -> direct wgs84 convergence c' (modBearing 165.34) 4235) (27.812 <°> 154.295)
Just (VincentyDirectResult (Coordinate (Latitude (DegreesLatitude 27) (Minutes 46) (Seconds 30.0981)) (Longitude (DegreesLongitude 154) (Minutes 18) (Seconds 21.1466))) (Bearing 165.3451))
>>> fmap (\c' -> direct wgs84 convergence c' (modBearing 165.34) 4235) ((-66.093) <°> 12.84)
Just (VincentyDirectResult (Coordinate (Latitude (DegreesLatitude (-66)) (Minutes 7) (Seconds 47.0667)) (Longitude (DegreesLongitude 12) (Minutes 51) (Seconds 49.4142))) (Bearing 165.3183))
>>> fmap (\c' -> direct ans convergence c' (modBearing 165.34) 4235) (27.812 <°> 154.295)
Just (VincentyDirectResult (Coordinate (Latitude (DegreesLatitude 27) (Minutes 46) (Seconds 30.0986)) (Longitude (DegreesLongitude 154) (Minutes 18) (Seconds 21.1464))) (Bearing 165.3451))
>>> fmap (\c' -> direct ans convergence c' (modBearing 165.34) 4235) ((-66.093) <°> 12.84)
Just (VincentyDirectResult (Coordinate (Latitude (DegreesLatitude (-66)) (Minutes 7) (Seconds 47.0662)) (Longitude (DegreesLongitude 12) (Minutes 51) (Seconds 49.4139))) (Bearing 165.3183))

directD Source

Arguments

:: (AsCoordinate (->) (Const Coordinate) c, AsBearing (->) (Const Bearing) b) 
=> c

begin coordinate

-> b

bearing

-> Double

distance

-> VincentyDirectResult 

Vincenty direct algorithm with a default ellipsoid of WGS84 and standard convergence.

>>> fmap (\c' -> directD c' (modBearing 165.34) 4235) (27.812 <°> 154.295)
Just (VincentyDirectResult (Coordinate (Latitude (DegreesLatitude 27) (Minutes 46) (Seconds 30.0981)) (Longitude (DegreesLongitude 154) (Minutes 18) (Seconds 21.1466))) (Bearing 165.3451))
>>> fmap (\c' -> directD c' (modBearing 165.34) 4235) ((-66.093) <°> 12.84)
Just (VincentyDirectResult (Coordinate (Latitude (DegreesLatitude (-66)) (Minutes 7) (Seconds 47.0667)) (Longitude (DegreesLongitude 12) (Minutes 51) (Seconds 49.4142))) (Bearing 165.3183))

direct' :: Optional2 Ellipsoid Convergence (Coordinate -> Bearing -> Double -> VincentyDirectResult) x => x Source

Vincenty direct algorithm with an optionally applied default ellipsoid of WGS84 and standard convergence.

>>> fmap (\c' -> direct' c' (modBearing 165.34) (4235 :: Double) :: VincentyDirectResult) (27.812 <°> 154.295)
Just (VincentyDirectResult (Coordinate (Latitude (DegreesLatitude 27) (Minutes 46) (Seconds 30.0981)) (Longitude (DegreesLongitude 154) (Minutes 18) (Seconds 21.1466))) (Bearing 165.3451))
>>> fmap (\c' -> direct' c' (modBearing 165.34) (4235 :: Double) :: VincentyDirectResult) ((-66.093) <°> 12.84)
Just (VincentyDirectResult (Coordinate (Latitude (DegreesLatitude (-66)) (Minutes 7) (Seconds 47.0667)) (Longitude (DegreesLongitude 12) (Minutes 51) (Seconds 49.4142))) (Bearing 165.3183))

inverse Source

Arguments

:: (AsCoordinate (->) (Const Coordinate) start, AsCoordinate (->) (Const Coordinate) end, AsEllipsoid (->) (Const Ellipsoid) e) 
=> e

reference ellipsoid

-> Convergence

convergence point to stop calculating

-> start

start coordinate

-> end

end coordinate

-> Curve 

Vincenty inverse algorithm.

>>> do fr <- 27.812 <°> 154.295; to <- (-66.093) <°> 12.84; return (inverse wgs84 convergence fr to)
Just (GeodeticCurve 14998576.9860 Azimuth 180.0000 Azimuth 0.0000)
>>> do fr <- 27.812 <°> 154.295; to <- 87.7769 <°> 19.944; return (inverse wgs84 convergence fr to)
Just (GeodeticCurve 7099204.2589 Azimuth 0.0000 Azimuth 180.0000)
>>> do fr <- 27.812 <°> 154.295; to <- (-66.093) <°> 12.84; return (inverse ans convergence fr to)
Just (GeodeticCurve 14998630.4056 Azimuth 180.0000 Azimuth 0.0000)
>>> do fr <- 27.812 <°> 154.295; to <- 87.7769 <°> 19.944; return (inverse ans convergence fr to)
Just (GeodeticCurve 7099229.9126 Azimuth 0.0000 Azimuth 180.0000)

inverseD Source

Arguments

:: (AsCoordinate (->) (Const Coordinate) start, AsCoordinate (->) (Const Coordinate) end) 
=> start

start coordinate

-> end

end coordinate

-> Curve 

Vincenty inverse algorithm with a default ellipsoid of WGS84 and standard convergence.

>>> do fr <- 27.812 <°> 154.295; to <- (-66.093) <°> 12.84; return (inverseD fr to)
Just (GeodeticCurve 14998576.9860 Azimuth 180.0000 Azimuth 0.0000)
>>> do fr <- 27.812 <°> 154.295; to <- 87.7769 <°> 19.944; return (inverseD fr to)
Just (GeodeticCurve 7099204.2589 Azimuth 0.0000 Azimuth 180.0000)

inverse' :: Optional2 Ellipsoid Convergence (Coordinate -> Coordinate -> Curve) x => x Source

Vincenty inverse algorithm with an optionally applied default ellipsoid of WGS84 and standard convergence.

>>> do fr <- 27.812 <°> 154.295; to <- (-66.093) <°> 12.84; return (inverse' fr to :: Curve)
Just (GeodeticCurve 14998576.9860 Azimuth 180.0000 Azimuth 0.0000)
>>> do fr <- 27.812 <°> 154.295; to <- 87.7769 <°> 19.944; return (inverse' fr to :: Curve)
Just (GeodeticCurve 7099204.2589 Azimuth 0.0000 Azimuth 180.0000)

data P Source

Constructors

P 

Instances

vmap2 :: (a -> b) -> (a, a) -> (b, b) Source

square :: Num a => a -> a Source

doWhile :: (a -> a) -> (a -> Bool) -> a -> a Source

whileDo :: (a -> a) -> (a -> Bool) -> a -> a Source

data Q Source

Constructors

Q