Copyright | Travis Whitaker 2023 |
---|---|
License | MIT |
Maintainer | pi.boy.travis@gmail.com |
Stability | Provisional |
Portability | Portable (Windows, POSIX) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Geodetic coordinates. The ellipsoid is not indexed explicitly, but conversion functions for WGS84 are provided.
Synopsis
- data Geo a = Geo {}
- normalizeGeo :: (Floating a, Real a) => Geo a -> Geo a
- fromLatLonAlt :: (PlaneAngle lat, PlaneAngle lon, Floating a, Real a) => lat a -> lon a -> a -> Geo a
- toLatLonAlt :: (PlaneAngle lat, PlaneAngle lon, Floating a, Real a) => Geo a -> (lat a, lon a, a)
- simpleEllipsoid :: Floating a => a -> a -> Geo a -> ECEF a
- earthEllipsoid :: RealFloat a => Geo a -> ECEF a
- ecefToGeoFerrariEllipsoid :: RealFloat a => a -> a -> ECEF a -> Geo a
- ecefToGeoFerrariEarth :: RealFloat a => ECEF a -> Geo a
- geoToECEF :: RealFloat a => Geo a -> ECEF a
- ecefToGeo :: RealFloat a => ECEF a -> Geo a
Documentation
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.
Instances
MonadFix Geo Source # | |
Defined in Linear.Geo.Geodetic | |
MonadZip Geo Source # | |
Foldable Geo Source # | |
Defined in Linear.Geo.Geodetic 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 # elem :: Eq a => a -> Geo a -> Bool # maximum :: Ord a => Geo a -> a # | |
Traversable Geo Source # | |
Applicative Geo Source # | |
Functor Geo Source # | |
Monad Geo Source # | |
Data a => Data (Geo a) Source # | |
Defined in Linear.Geo.Geodetic 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) # 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 # | |
Generic (Geo a) Source # | |
Show a => Show (Geo a) Source # | |
NFData a => NFData (Geo a) Source # | |
Defined in Linear.Geo.Geodetic | |
Eq a => Eq (Geo a) Source # | |
Ord a => Ord (Geo a) Source # | |
type Rep (Geo a) Source # | |
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
.
:: (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.
Convert from geodetic coordinates to ECEF by assuming the earth is an ellipsoid.
ecefToGeoFerrariEllipsoid Source #
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/