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

Safe HaskellNone
LanguageHaskell2010

Numeric.Estimator.Class

Description

These type classes abstract many details of estimation algorithms, making it easier to try different algorithms while changing the model as little as possible.

This interface does make the simplifying assumption that process uncertainty and measurement noise are each always specified as a covariance matrix describing a zero-mean multi-variate normal distribution. While some estimation algorithms (such as the Bayesian Particle Filter) can accomodate more sophisticated distributions, it's unusual to encounter problems that require that degree of flexibility.

Synopsis

Documentation

class Estimator t Source #

An estimator is a model of a system, describing how to update a prior estimated state with new information. Two kinds of estimators are the Process model, and the Measure (or observation) model.

Associated Types

type Filter t :: (* -> *) -> * -> * Source #

The type of data that this estimator maintains across updates.

Instances

Estimator (EKFMeasurement state var) Source # 

Associated Types

type Filter (EKFMeasurement state var) :: (* -> *) -> * -> * Source #

Estimator (EKFProcess state var) Source # 

Associated Types

type Filter (EKFProcess state var) :: (* -> *) -> * -> * Source #

type family State t :: * -> * Source #

The type of state vector used in an estimator.

Instances

type State (EKFMeasurement state var) Source # 
type State (EKFMeasurement state var) = state
type State (EKFProcess state var) Source # 
type State (EKFProcess state var) = state
type State (KalmanFilter state var) Source # 
type State (KalmanFilter state var) = state

type family Var t Source #

The type of individual state variables used in an estimator.

Instances

type Var (EKFMeasurement state var) Source # 
type Var (EKFMeasurement state var) = var
type Var (EKFProcess state var) Source # 
type Var (EKFProcess state var) = var
type Var (KalmanFilter state var) Source # 
type Var (KalmanFilter state var) = var

class Estimator t => Process t where Source #

A process model updates the estimated state by predicting how the system should have changed since the last prediction.

In a kinematic model, for instance, the process model might be a dead-reckoning physics simulation which updates position using a trivial numeric integration of velocity.

Parameter estimation problems, where the parameters are expected to remain constant between observations, needn't have a process model.

Minimal complete definition

process

Methods

process :: t -> State t (State t (Var t)) -> Filter t (State t) (Var t) -> Filter t (State t) (Var t) Source #

Instances

(Additive state, Traversable state, Distributive state, Num var) => Process (EKFProcess state var) Source # 

Methods

process :: EKFProcess state var -> State (EKFProcess state var) (State (EKFProcess state var) (Var (EKFProcess state var))) -> Filter (EKFProcess state var) (State (EKFProcess state var)) (Var (EKFProcess state var)) -> Filter (EKFProcess state var) (State (EKFProcess state var)) (Var (EKFProcess state var)) Source #

class Estimator t => Measure t where Source #

A measurement, or observation, model updates the estimated state using some observation of the real state.

In a navigation problem, for instance, an observation might come from a GPS receiver or a pressure altimeter. The model computes what value the sensor would be expected to read if there were no sensor noise and the current estimated state were exactly correct. The difference between the expected and actual measurement is called the "innovation", and that difference drives the estimated state toward the true state.

In general, an observation is vector-valued. You can wrap up scalar observations in a singleton functor, such as V1.

For each dimension of the observation vector, the measurement must consist of a scalar measurement, and an expression which evaluates to the expected value for that measurement given the current state.

Minimal complete definition

measure

Associated Types

type MeasureQuality (t :: *) (obs :: * -> *) :: * Source #

Some estimators can compute some indication of how plausible an observation is, such as, for example, the innovation. This is the type of that quality indication, which may be () if the chosen algorithm can't report measurement quality.

type MeasureObservable (t :: *) (obs :: * -> *) :: Constraint Source #

An algorithm may have specific constraints on what types of observation it can process. This type has a Constraint kind and captures any required type-class constraints.

Methods

measure :: MeasureObservable t obs => obs (Var t, t) -> obs (obs (Var t)) -> Filter t (State t) (Var t) -> (MeasureQuality t obs, Filter t (State t) (Var t)) Source #

Instances

(Additive state, Distributive state, Traversable state, Fractional var) => Measure (EKFMeasurement state var) Source # 

Associated Types

type MeasureQuality (EKFMeasurement state var) (obs :: * -> *) :: * Source #

type MeasureObservable (EKFMeasurement state var) (obs :: * -> *) :: Constraint Source #

Methods

measure :: MeasureObservable (EKFMeasurement state var) obs => obs (Var (EKFMeasurement state var), EKFMeasurement state var) -> obs (obs (Var (EKFMeasurement state var))) -> Filter (EKFMeasurement state var) (State (EKFMeasurement state var)) (Var (EKFMeasurement state var)) -> (MeasureQuality (EKFMeasurement state var) obs, Filter (EKFMeasurement state var) (State (EKFMeasurement state var)) (Var (EKFMeasurement state var))) Source #

class GaussianFilter t where Source #

A filter whose state can be captured as a multi-variate normal distribution can also be updated by adjusting the parameters of that distribution.

Minimal complete definition

mapStatistics

Methods

mapStatistics :: (state var -> state' var') -> (state (state var) -> state' (state' var')) -> t state var -> t state' var' Source #

Instances

GaussianFilter KalmanFilter Source # 

Methods

mapStatistics :: (state var -> state' var') -> (state (state var) -> state' (state' var')) -> KalmanFilter state var -> KalmanFilter state' var' Source #