estimator-1.2.0.0: State-space estimation algorithms such as Kalman Filters

Safe HaskellNone
LanguageHaskell2010

Numeric.Estimator.Model.Coordinate

Contents

Description

The Linear module provides basic fixed-dimensional vector types such as V3, for three-element vectors. However, it does not help with identifying which coordinate system a vector was measured in.

The types in this module are trivial newtype wrappers around V3 to tag vectors with an appropriate coordinate system. The systems used here follow a common convention used in navigation problems.

Synopsis

Navigation frame

newtype NED a Source #

Navigation occurs in a right-hand coordinate system with respect to a "local tangent plane". The origin of this plane is chosen to be some convenient point on the Earth's surface--perhaps the location where navigation began. The plane is oriented such that it is tangent to the Earth's surface at that origin point. The basis vectors point northward, eastward, and downward from the origin. Notice that the further you travel from the origin, the further the tangent plane separates from the surface of the Earth, so this approach is of limited use over long distances.

Constructors

NED 

Fields

Instances

Functor NED Source # 

Methods

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

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

Applicative NED Source # 

Methods

pure :: a -> NED a #

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

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

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

Foldable NED Source # 

Methods

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

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

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

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

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

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

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

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

toList :: NED a -> [a] #

null :: NED a -> Bool #

length :: NED a -> Int #

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

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

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

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

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

Traversable NED Source # 

Methods

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

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

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

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

Distributive NED Source # 

Methods

distribute :: Functor f => f (NED a) -> NED (f a) #

collect :: Functor f => (a -> NED b) -> f a -> NED (f b) #

distributeM :: Monad m => m (NED a) -> NED (m a) #

collectM :: Monad m => (a -> NED b) -> m a -> NED (m b) #

Metric NED Source # 

Methods

dot :: Num a => NED a -> NED a -> a #

quadrance :: Num a => NED a -> a #

qd :: Num a => NED a -> NED a -> a #

distance :: Floating a => NED a -> NED a -> a #

norm :: Floating a => NED a -> a #

signorm :: Floating a => NED a -> NED a #

Additive NED Source # 

Methods

zero :: Num a => NED a #

(^+^) :: Num a => NED a -> NED a -> NED a #

(^-^) :: Num a => NED a -> NED a -> NED a #

lerp :: Num a => a -> NED a -> NED a -> NED a #

liftU2 :: (a -> a -> a) -> NED a -> NED a -> NED a #

liftI2 :: (a -> b -> c) -> NED a -> NED b -> NED c #

Num a => Num (NED a) Source # 

Methods

(+) :: NED a -> NED a -> NED a #

(-) :: NED a -> NED a -> NED a #

(*) :: NED a -> NED a -> NED a #

negate :: NED a -> NED a #

abs :: NED a -> NED a #

signum :: NED a -> NED a #

fromInteger :: Integer -> NED a #

Show a => Show (NED a) Source # 

Methods

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

show :: NED a -> String #

showList :: [NED a] -> ShowS #

ned :: a -> a -> a -> NED a Source #

Construct a navigation frame coordinate from (north, east, down).

Body frame

newtype XYZ a Source #

Most sensor measurements are taken with respect to the sensor platform in the vehicle. We assume the sensors are perfectly orthogonally arranged in a right-hand Cartesian coordinate system, which is usually close enough to the truth, although more sophisticated approaches exist to calibrate out non-orthogonal alignment and other errors. This coordinate system is only meaningful with respect to the current position and orientation of the sensor platform, as of the instant that the measurement was taken.

Constructors

XYZ 

Fields

Instances

Functor XYZ Source # 

Methods

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

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

Applicative XYZ Source # 

Methods

pure :: a -> XYZ a #

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

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

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

Foldable XYZ Source # 

Methods

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

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

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

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

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

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

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

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

toList :: XYZ a -> [a] #

null :: XYZ a -> Bool #

length :: XYZ a -> Int #

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

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

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

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

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

Traversable XYZ Source # 

Methods

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

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

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

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

Distributive XYZ Source # 

Methods

distribute :: Functor f => f (XYZ a) -> XYZ (f a) #

collect :: Functor f => (a -> XYZ b) -> f a -> XYZ (f b) #

distributeM :: Monad m => m (XYZ a) -> XYZ (m a) #

collectM :: Monad m => (a -> XYZ b) -> m a -> XYZ (m b) #

Metric XYZ Source # 

Methods

dot :: Num a => XYZ a -> XYZ a -> a #

quadrance :: Num a => XYZ a -> a #

qd :: Num a => XYZ a -> XYZ a -> a #

distance :: Floating a => XYZ a -> XYZ a -> a #

norm :: Floating a => XYZ a -> a #

signorm :: Floating a => XYZ a -> XYZ a #

Additive XYZ Source # 

Methods

zero :: Num a => XYZ a #

(^+^) :: Num a => XYZ a -> XYZ a -> XYZ a #

(^-^) :: Num a => XYZ a -> XYZ a -> XYZ a #

lerp :: Num a => a -> XYZ a -> XYZ a -> XYZ a #

liftU2 :: (a -> a -> a) -> XYZ a -> XYZ a -> XYZ a #

liftI2 :: (a -> b -> c) -> XYZ a -> XYZ b -> XYZ c #

Num a => Num (XYZ a) Source # 

Methods

(+) :: XYZ a -> XYZ a -> XYZ a #

(-) :: XYZ a -> XYZ a -> XYZ a #

(*) :: XYZ a -> XYZ a -> XYZ a #

negate :: XYZ a -> XYZ a #

abs :: XYZ a -> XYZ a #

signum :: XYZ a -> XYZ a #

fromInteger :: Integer -> XYZ a #

Show a => Show (XYZ a) Source # 

Methods

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

show :: XYZ a -> String #

showList :: [XYZ a] -> ShowS #

xyz :: a -> a -> a -> XYZ a Source #

Construct a body frame coordinate from (x, y, z).

Coordinate frame conversion

convertFrames :: Num a => Quaternion a -> (XYZ a -> NED a, NED a -> XYZ a) Source #

Most practical problems involving inertial sensors (such as accelerometers and gyroscopes) require keeping track of the relationship between these two coordinate systems.

If you maintain a quaternion representing the rotation from navigation frame to body frame, then you can use this function to get functions that will convert coordinates between frames in either direction.