linear-geo-0.1.0.0: Geographic coordinates, built on the linear package.
CopyrightTravis Whitaker 2023
LicenseMIT
Maintainerpi.boy.travis@gmail.com
StabilityProvisional
PortabilityPortable (Windows, POSIX)
Safe HaskellSafe-Inferred
LanguageHaskell2010

Linear.Geo.Geodetic

Description

Geodetic coordinates. The ellipsoid is not indexed explicitly, but conversion functions for WGS84 are provided.

Synopsis

Documentation

data Geo a Source #

A point in some geodetic coordinate system, where geoLat is the angle between the normal at the specified point on the ellipsoid and the equatorial plane (north positive, south negative), geoLon is the angle formed by the intersection of the parallel and the prime meridian and the specified point on the parallel, and geoAlt is the magnitude of the position vector minus the magnitude of the unique vector colinear and coordinal with the position vector impingent on the ellipsoid's surface (i.e. height above ellipsoid). Angles are in radians.

Constructors

Geo 

Fields

Instances

Instances details
MonadFix Geo Source # 
Instance details

Defined in Linear.Geo.Geodetic

Methods

mfix :: (a -> Geo a) -> Geo a #

MonadZip Geo Source # 
Instance details

Defined in Linear.Geo.Geodetic

Methods

mzip :: Geo a -> Geo b -> Geo (a, b) #

mzipWith :: (a -> b -> c) -> Geo a -> Geo b -> Geo c #

munzip :: Geo (a, b) -> (Geo a, Geo b) #

Foldable Geo Source # 
Instance details

Defined in Linear.Geo.Geodetic

Methods

fold :: Monoid m => Geo m -> m #

foldMap :: Monoid m => (a -> m) -> Geo a -> m #

foldMap' :: Monoid m => (a -> m) -> Geo a -> m #

foldr :: (a -> b -> b) -> b -> Geo a -> b #

foldr' :: (a -> b -> b) -> b -> Geo a -> b #

foldl :: (b -> a -> b) -> b -> Geo a -> b #

foldl' :: (b -> a -> b) -> b -> Geo a -> b #

foldr1 :: (a -> a -> a) -> Geo a -> a #

foldl1 :: (a -> a -> a) -> Geo a -> a #

toList :: Geo a -> [a] #

null :: Geo a -> Bool #

length :: Geo a -> Int #

elem :: Eq a => a -> Geo a -> Bool #

maximum :: Ord a => Geo a -> a #

minimum :: Ord a => Geo a -> a #

sum :: Num a => Geo a -> a #

product :: Num a => Geo a -> a #

Traversable Geo Source # 
Instance details

Defined in Linear.Geo.Geodetic

Methods

traverse :: Applicative f => (a -> f b) -> Geo a -> f (Geo b) #

sequenceA :: Applicative f => Geo (f a) -> f (Geo a) #

mapM :: Monad m => (a -> m b) -> Geo a -> m (Geo b) #

sequence :: Monad m => Geo (m a) -> m (Geo a) #

Applicative Geo Source # 
Instance details

Defined in Linear.Geo.Geodetic

Methods

pure :: a -> Geo a #

(<*>) :: Geo (a -> b) -> Geo a -> Geo b #

liftA2 :: (a -> b -> c) -> Geo a -> Geo b -> Geo c #

(*>) :: Geo a -> Geo b -> Geo b #

(<*) :: Geo a -> Geo b -> Geo a #

Functor Geo Source # 
Instance details

Defined in Linear.Geo.Geodetic

Methods

fmap :: (a -> b) -> Geo a -> Geo b #

(<$) :: a -> Geo b -> Geo a #

Monad Geo Source # 
Instance details

Defined in Linear.Geo.Geodetic

Methods

(>>=) :: Geo a -> (a -> Geo b) -> Geo b #

(>>) :: Geo a -> Geo b -> Geo b #

return :: a -> Geo a #

Data a => Data (Geo a) Source # 
Instance details

Defined in Linear.Geo.Geodetic

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Geo a -> c (Geo a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Geo a) #

toConstr :: Geo a -> Constr #

dataTypeOf :: Geo a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Geo a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Geo a)) #

gmapT :: (forall b. Data b => b -> b) -> Geo a -> Geo a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Geo a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Geo a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Geo a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Geo a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Geo a -> m (Geo a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Geo a -> m (Geo a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Geo a -> m (Geo a) #

Bounded a => Bounded (Geo a) Source # 
Instance details

Defined in Linear.Geo.Geodetic

Methods

minBound :: Geo a #

maxBound :: Geo a #

Generic (Geo a) Source # 
Instance details

Defined in Linear.Geo.Geodetic

Associated Types

type Rep (Geo a) :: Type -> Type #

Methods

from :: Geo a -> Rep (Geo a) x #

to :: Rep (Geo a) x -> Geo a #

Show a => Show (Geo a) Source # 
Instance details

Defined in Linear.Geo.Geodetic

Methods

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

show :: Geo a -> String #

showList :: [Geo a] -> ShowS #

NFData a => NFData (Geo a) Source # 
Instance details

Defined in Linear.Geo.Geodetic

Methods

rnf :: Geo a -> () #

Eq a => Eq (Geo a) Source # 
Instance details

Defined in Linear.Geo.Geodetic

Methods

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

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

Ord a => Ord (Geo a) Source # 
Instance details

Defined in Linear.Geo.Geodetic

Methods

compare :: Geo a -> Geo a -> Ordering #

(<) :: Geo a -> Geo a -> Bool #

(<=) :: Geo a -> Geo a -> Bool #

(>) :: Geo a -> Geo a -> Bool #

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

max :: Geo a -> Geo a -> Geo a #

min :: Geo a -> Geo a -> Geo a #

type Rep (Geo a) Source # 
Instance details

Defined in Linear.Geo.Geodetic

type Rep (Geo a) = D1 ('MetaData "Geo" "Linear.Geo.Geodetic" "linear-geo-0.1.0.0-LxCVplq22GGCkRzZB0XgZk" 'False) (C1 ('MetaCons "Geo" 'PrefixI 'True) (S1 ('MetaSel ('Just "geoLat") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Radians a)) :*: (S1 ('MetaSel ('Just "geoLon") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Radians a)) :*: S1 ('MetaSel ('Just "geoAlt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a))))

normalizeGeo :: (Floating a, Real a) => Geo a -> Geo a Source #

Normalize the two angle components of a Geo.

fromLatLonAlt Source #

Arguments

:: (PlaneAngle lat, PlaneAngle lon, Floating a, Real a) 
=> lat a

Latitude

-> lon a

Longitude

-> a

Altitude

-> Geo a 

Convert a pair of angles and a height above the ellipsoid into a Geo.

toLatLonAlt :: (PlaneAngle lat, PlaneAngle lon, Floating a, Real a) => Geo a -> (lat a, lon a, a) Source #

Unpack a Geo into latitude, longitude, and height above the ellipsoid.

simpleEllipsoid Source #

Arguments

:: Floating a 
=> a

Semi-major axis.

-> a

Semi-minor axis.

-> Geo a 
-> ECEF a 

Convert from geodetic coordinates to ECEF by assuming the earth is an ellipsoid.

earthEllipsoid :: RealFloat a => Geo a -> ECEF a Source #

Standard WGS84 ellipsoid.

ecefToGeoFerrariEllipsoid Source #

Arguments

:: RealFloat a 
=> a

Semi-major axis.

-> a

Semi-minor axis.

-> ECEF a 
-> Geo a 

Conversion from ECEF to geodetic coordinates via a numerically stable formulation of Ferrari's closed-form solution to the quartic polynomial. See https://ieeexplore.ieee.org/document/303772/

ecefToGeoFerrariEarth :: RealFloat a => ECEF a -> Geo a Source #

Standard WGS84 ellipsoid.

geoToECEF :: RealFloat a => Geo a -> ECEF a Source #

Synonym for earthEllipsoid.