levmar-0.2.1: An implementation of the Levenberg-Marquardt algorithmSource codeContentsIndex
LevMar.AD
StabilityExperimental
Maintainervandijk.roel@gmail.com, v.dijk.bas@gmail.com
Contents
Model
Levenberg-Marquardt algorithm.
Minimization options.
Output
Type-level machinery
Description

A levmar variant that uses Automatic Differentiation to automatically compute the Jacobian.

For additional documentation see the documentation of the levmar C library which this library is based on: http://www.ics.forth.gr/~lourakis/levmar/

Synopsis
type Model m n r = NFunction m r (SizedList n r)
class LevMarable r
levmar :: forall m n k r. (Nat m, Nat n, Nat k, HasBasis r, Basis r ~ (), VectorSpace (Scalar r), LevMarable r) => Model m n (r :~> r) -> SizedList m r -> SizedList n r -> Integer -> Options r -> Maybe (SizedList m r) -> Maybe (SizedList m r) -> Maybe (LinearConstraints k m r) -> Maybe (SizedList m r) -> Either LevMarError (SizedList m r, Info r, CovarMatrix m r)
type LinearConstraints k n r = (Matrix k n r, SizedList k r)
noLinearConstraints :: Nat n => Maybe (LinearConstraints Z n r)
type Matrix n m r = SizedList n (SizedList m r)
data Options r = Opts {
optScaleInitMu :: r
optStopNormInfJacTe :: r
optStopNorm2Dp :: r
optStopNorm2E :: r
optDelta :: r
}
defaultOpts :: Fractional r => Options r
data Info r = Info {
infNorm2initE :: r
infNorm2E :: r
infNormInfJacTe :: r
infNorm2Dp :: r
infMuDivMax :: r
infNumIter :: Integer
infStopReason :: StopReason
infNumFuncEvals :: Integer
infNumJacobEvals :: Integer
infNumLinSysSolved :: Integer
}
data StopReason
= SmallGradient
| SmallDp
| MaxIterations
| SingularMatrix
| SmallestError
| SmallNorm2E
| InvalidValues
type CovarMatrix n r = Matrix n n r
data LevMarError
= LevMarError
| LapackError
| FailedBoxCheck
| MemoryAllocationFailure
| ConstraintMatrixRowsGtCols
| ConstraintMatrixNotFullRowRank
| TooFewMeasurements
data Z
data S n
class Nat n
data SizedList n a where
Nil :: SizedList Z a
::: :: a -> SizedList n a -> SizedList (S n) a
type family NFunction n a b :: *
Model
type Model m n r = NFunction m r (SizedList n r)Source

A functional relation describing measurements represented as a function from m parameters to n expected measurements.

An example from Demo.hs:

type N4 = S (S (S (S Z)))

hatfldc :: Model N4 N4 Double
hatfldc p0 p1 p2 p3 =     p0 - 1.0
                      ::: p0 - sqrt p1
                      ::: p1 - sqrt p2
                      ::: p3 - 1.0
                      ::: Nil
Levenberg-Marquardt algorithm.
class LevMarable r Source
The Levenberg-Marquardt algorithm is overloaded to work on Double and Float.
show/hide Instances
levmarSource
:: forall m n k r . (Nat m, Nat n, Nat k, HasBasis r, Basis r ~ (), VectorSpace (Scalar r), LevMarable r)
=> Model m n (r :~> r)Model. Note that ':~>' is overloaded for all the numeric classes.
-> SizedList m rInitial parameters
-> SizedList n rSamples
-> IntegerMaximum number of iterations
-> Options rMinimization options
-> Maybe (SizedList m r)Optional lower bounds
-> Maybe (SizedList m r)Optional upper bounds
-> Maybe (LinearConstraints k m r)Optional linear constraints
-> Maybe (SizedList m r)Optional weights
-> Either LevMarError (SizedList m r, Info r, CovarMatrix m r)

The Levenberg-Marquardt algorithm that automatically computes the Jacobian using automatic differentiation of the model function.

Warning: Don't apply levmar to Models that apply methods of the Eq and Ord classes to the parameters. These methods are undefined for ':~>'!!!

type LinearConstraints k n r = (Matrix k n r, SizedList k r)Source
Linear constraints consisting of a constraints matrix, kxn and a right hand constraints vector, kx1 where n is the number of parameters and k is the number of constraints.
noLinearConstraints :: Nat n => Maybe (LinearConstraints Z n r)Source
Value to denote the absense of any linear constraints over the parameters of the model function. Use this instead of Nothing because the type parameter which contains the number of constraints can't be inferred.
type Matrix n m r = SizedList n (SizedList m r)Source
A nxm matrix is a sized list of n sized lists of length m.
Minimization options.
data Options r Source
Minimization options
Constructors
Opts
optScaleInitMu :: rScale factor for initial mu.
optStopNormInfJacTe :: rStopping thresholds for ||J^T e||_inf.
optStopNorm2Dp :: rStopping thresholds for ||Dp||_2.
optStopNorm2E :: rStopping thresholds for ||e||_2.
optDelta :: rStep used in the difference approximation to the Jacobian. If optDelta<0, the Jacobian is approximated with central differences which are more accurate (but slower!) compared to the forward differences employed by default.
show/hide Instances
Show r => Show (Options r)
defaultOpts :: Fractional r => Options rSource
Default minimization options
Output
data Info r Source
Information regarding the minimization.
Constructors
Info
infNorm2initE :: r||e||_2 at initial parameters.
infNorm2E :: r||e||_2 at estimated parameters.
infNormInfJacTe :: r||J^T e||_inf at estimated parameters.
infNorm2Dp :: r||Dp||_2 at estimated parameters.
infMuDivMax :: rmu/max[J^T J]_ii ] at estimated parameters.
infNumIter :: IntegerNumber of iterations.
infStopReason :: StopReasonReason for terminating.
infNumFuncEvals :: IntegerNumber of function evaluations.
infNumJacobEvals :: IntegerNumber of jacobian evaluations.
infNumLinSysSolved :: IntegerNumber of linear systems solved, i.e. attempts for reducing error.
show/hide Instances
Show r => Show (Info r)
data StopReason Source
Reason for terminating.
Constructors
SmallGradientStopped because of small gradient J^T e.
SmallDpStopped because of small Dp.
MaxIterationsStopped because maximum iterations was reached.
SingularMatrixStopped because of singular matrix. Restart from current estimated parameters with increased optScaleInitMu.
SmallestErrorStopped because no further error reduction is possible. Restart with increased optScaleInitMu.
SmallNorm2EStopped because of small ||e||_2.
InvalidValuesStopped because model function returned invalid values (i.e. NaN or Inf). This is a user error.
show/hide Instances
type CovarMatrix n r = Matrix n n rSource
Covariance matrix corresponding to LS solution.
data LevMarError Source
Constructors
LevMarErrorGeneric error (not one of the others)
LapackErrorA call to a lapack subroutine failed in the underlying C levmar library.
FailedBoxCheckAt least one lower bound exceeds the upper one.
MemoryAllocationFailureA call to malloc failed in the underlying C levmar library.
ConstraintMatrixRowsGtColsThe matrix of constraints cannot have more rows than columns.
ConstraintMatrixNotFullRowRankConstraints matrix is not of full row rank.
TooFewMeasurementsCannot solve a problem with fewer measurements than unknowns. In case linear constraints are provided, this error is also returned when the number of measurements is smaller than the number of unknowns minus the number of equality constraints.
show/hide Instances
Type-level machinery
data Z Source
Type-level natural denoting zero
show/hide Instances
data S n Source
Type-level natural denoting the Successor of another type-level natural.
show/hide Instances
Show n => Show (S n)
Nat p => Nat (S p)
ComposeN n => ComposeN (S n)
class Nat n Source
Class of all type-level naturals.
show/hide Instances
Nat Z
Nat p => Nat (S p)
data SizedList n a whereSource
A list which is indexed with a type-level natural that denotes the size of the list.
Constructors
Nil :: SizedList Z a
::: :: a -> SizedList n a -> SizedList (S n) a
show/hide Instances
type family NFunction n a b :: *Source
A NFunction n a b is a function which takes n arguments of type a and returns a b. For example: NFunction (S (S (S Z))) a b ~ (a -> a -> a -> b)
Produced by Haddock version 2.4.2