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.ENU

Description

East-North-Up coordinates.

Synopsis

Documentation

data ENU a Source #

R3 vector with the origin located at some arbitrary ECEF position vector, first basis pointing east at the origin, second basis vector pointing north at the origin, and third basis vector normal to the plane tangent to the ellipsoid at the origin.

Each value records both the ENU vector and the ENU origin. Most functions of multiple ENU values will require the points to occupy coordinal frames. Binary operations on ENU values should preserve the coordinate frame of the left value.

The Eq and Ord instances for this type implement structural equality, i.e. ENU points with different enuOrigin values will never be equal. Floating point errors limit the usefulness of exact-equality-as-coincidence.

Operations on ENU points use the uncorrected WGS84 geoid model.

Constructors

ENU 

Fields

Instances

Instances details
R1 ENU Source # 
Instance details

Defined in Linear.Geo.ENU

Methods

_x :: Lens' (ENU a) a #

R2 ENU Source # 
Instance details

Defined in Linear.Geo.ENU

Methods

_y :: Lens' (ENU a) a #

_xy :: Lens' (ENU a) (V2 a) #

R3 ENU Source # 
Instance details

Defined in Linear.Geo.ENU

Methods

_z :: Lens' (ENU a) a #

_xyz :: Lens' (ENU a) (V3 a) #

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

Defined in Linear.Geo.ENU

Methods

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

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

toConstr :: ENU a -> Constr #

dataTypeOf :: ENU a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Linear.Geo.ENU

Methods

minBound :: ENU a #

maxBound :: ENU a #

Generic (ENU a) Source # 
Instance details

Defined in Linear.Geo.ENU

Associated Types

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

Methods

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

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

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

Defined in Linear.Geo.ENU

Methods

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

show :: ENU a -> String #

showList :: [ENU a] -> ShowS #

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

Defined in Linear.Geo.ENU

Methods

rnf :: ENU a -> () #

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

Defined in Linear.Geo.ENU

Methods

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

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

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

Defined in Linear.Geo.ENU

Methods

compare :: ENU a -> ENU a -> Ordering #

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

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

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

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

max :: ENU a -> ENU a -> ENU a #

min :: ENU a -> ENU a -> ENU a #

type Rep (ENU a) Source # 
Instance details

Defined in Linear.Geo.ENU

type Rep (ENU a) = D1 ('MetaData "ENU" "Linear.Geo.ENU" "linear-geo-0.1.0.0-LxCVplq22GGCkRzZB0XgZk" 'False) (C1 ('MetaCons "ENU" 'PrefixI 'True) (S1 ('MetaSel ('Just "enuOrigin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ECEF a)) :*: S1 ('MetaSel ('Just "enuPoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (V3 a))))

alignOrigin :: RealFloat a => ENU a -> ENU a -> ENU a Source #

Align the second argument with the coordinate system of the first.

liftAO2 :: RealFloat a => (V3 a -> V3 a -> b) -> ENU a -> ENU a -> b Source #

Lift a function on vectors to a function on origin-aligned ENU points.

liftAO2V :: RealFloat a => (V3 a -> V3 a -> V3 a) -> ENU a -> ENU a -> ENU a Source #

Lift a binary operation on vectors to a binary operation on origin-aligned ENU points.

rotNormToECEF Source #

Arguments

:: Floating a 
=> Radians a

lat

-> Radians a

lon

-> M33 a 

Rotation matrix that rotates the ENU coordinate frame at the provided latitude and longitude to the ECEF coordinate frame.

rotNormToECEFFromENU :: RealFloat a => ENU a -> M33 a Source #

Do rotNormToECEF, but get the lat and lon from some ENUs origin.

enuToECEF :: RealFloat a => ENU a -> ECEF a Source #

Convert an ENU to an ECEF by adding the rotated position vector to the origin.

rotECEFToNorm Source #

Arguments

:: Floating a 
=> Radians a

lat

-> Radians a

lon

-> M33 a 

Rotation matrix that rotates the ECEF coordinate frame to the ENU coordinate frame at the provided latitude and longitude.

rotECEFToNormFromENU :: RealFloat a => ENU a -> M33 a Source #

Do rotECEFToNorm, but get the lat and lon from some ENUs origin.

ecefToENU Source #

Arguments

:: RealFloat a 
=> ECEF a

Origin

-> ECEF a

Point

-> ENU a 

Pack an ECEF origin and point into an ENU.

disp :: Num a => ENU a -> V3 a -> ENU a Source #

Affine addition. Apply a displacement vector.

diff :: RealFloat a => ENU a -> ENU a -> V3 a Source #

Affine subtraction. Get the vector from the first to the second ENU point.

lerp :: RealFloat a => a -> ENU a -> ENU a -> ENU a Source #

Linearly interpolate between two points.

dot :: RealFloat a => ENU a -> ENU a -> a Source #

Lifted dot.

quadrance :: Num a => ENU a -> a Source #

Lifted quadrance.

norm :: Floating a => ENU a -> a Source #

Lifted norm.

distance :: RealFloat a => ENU a -> ENU a -> a Source #

Lifted distance.

normalize :: (Floating a, Epsilon a) => ENU a -> ENU a Source #

Lifted normalize.

project :: RealFloat a => ENU a -> ENU a -> ENU a Source #

Lifted project.