levmar-0.2.1: An implementation of the Levenberg-Marquardt algorithmSource codeContentsIndex
LevMar.Intermediate
StabilityExperimental
Maintainervandijk.roel@gmail.com, v.dijk.bas@gmail.com
Contents
Model & Jacobian.
Levenberg-Marquardt algorithm.
Minimization options.
Output
Description
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 r = [r] -> [r]
type Jacobian r = [r] -> [[r]]
class LevMarable r where
levmar :: Model r -> Maybe (Jacobian r) -> [r] -> [r] -> Integer -> Options r -> Maybe [r] -> Maybe [r] -> Maybe (LinearConstraints r) -> Maybe [r] -> Either LevMarError ([r], Info r, CovarMatrix r)
type LinearConstraints r = ([[r]], [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 r = [[r]]
data LevMarError
= LevMarError
| LapackError
| FailedBoxCheck
| MemoryAllocationFailure
| ConstraintMatrixRowsGtCols
| ConstraintMatrixNotFullRowRank
| TooFewMeasurements
Model & Jacobian.
type Model r = [r] -> [r]Source

A functional relation describing measurements represented as a function from a list of parameters to a list of expected measurements.

  • Ensure that the length of the parameters list equals the length of the initial parameters list in levmar.
  • Ensure that the length of the ouput list equals the length of the samples list in levmar.

For example:

hatfldc :: Model Double
hatfldc [p0, p1, p2, p3] = [ p0 - 1.0
                           , p0 - sqrt p1
                           , p1 - sqrt p2
                           , p3 - 1.0
                           ]
type Jacobian r = [r] -> [[r]]Source

The jacobian of the Model function. Expressed as a function from a list of parameters to a list of lists which for each expected measurement describes the partial derivatives of the parameters.

See: http://en.wikipedia.org/wiki/Jacobian_matrix_and_determinant

  • Ensure that the length of the parameter list equals the length of the initial parameter list in levmar.
  • Ensure that the output matrix has the dimension nxm where n is the number of samples and m is the number of parameters.

For example the jacobian of the above hatfldc model is:

hatfldc_jac :: Jacobian Double
hatfldc_jac _ p1 p2 _ = [ [1.0,  0.0,           0.0,           0.0]
                        , [1.0, -0.5 / sqrt p1, 0.0,           0.0]
                        , [0.0,  1.0,          -0.5 / sqrt p2, 0.0]
                        , [0.0,  0.0,           0.0,           1.0]
                        ]
Levenberg-Marquardt algorithm.
class LevMarable r whereSource
The Levenberg-Marquardt algorithm is overloaded to work on Double and Float.
Methods
levmarSource
:: Model rModel
-> Maybe (Jacobian r)Optional jacobian
-> [r]Initial parameters
-> [r]Samples
-> IntegerMaximum iterations
-> Options rMinimization options
-> Maybe [r]Optional lower bounds
-> Maybe [r]Optional upper bounds
-> Maybe (LinearConstraints r)Optional linear constraints
-> Maybe [r]Optional weights
-> Either LevMarError ([r], Info r, CovarMatrix r)
The Levenberg-Marquardt algorithm.
show/hide Instances
type LinearConstraints r = ([[r]], [r])Source
Linear constraints consisting of a constraints matrix, kxm and a right hand constraints vector, kx1 where m is the number of parameters and k is the number of constraints.
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 r = [[r]]Source
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
Produced by Haddock version 2.4.2