levmar-0.3: An implementation of the Levenberg-Marquardt algorithm

StabilityExperimental
MaintainerRoel van Dijk <vandijk.roel@gmail.com> Bas van Dijk <v.dijk.bas@gmail.com>

Numeric.LevMar

Contents

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

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

Arguments

:: Model r

Model

-> Maybe (Jacobian r)

Optional jacobian

-> [r]

Initial parameters

-> [r]

Samples

-> Integer

Maximum iterations

-> Options r

Minimization options

-> Constraints r

Constraints

-> Either LevMarError ([r], Info r, CovarMatrix r) 

The Levenberg-Marquardt algorithm.

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 

Fields

optScaleInitMu :: r

Scale factor for initial mu.

optStopNormInfJacTe :: r

Stopping thresholds for ||J^T e||_inf.

optStopNorm2Dp :: r

Stopping thresholds for ||Dp||_2.

optStopNorm2E :: r

Stopping thresholds for ||e||_2.

optDelta :: r

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

Instances

Read r => Read (Options r) 
Show r => Show (Options r) 

defaultOpts :: Fractional r => Options rSource

Default minimization options

Constraints

data Constraints r Source

Constructors

Constraints 

Fields

lowerBounds :: Maybe [r]

Optional lower bounds

upperBounds :: Maybe [r]

Optional upper bounds

weights :: Maybe [r]

Optional weights

linearConstraints :: Maybe (LinearConstraints r)

Optional linear constraints

noConstraints :: Constraints rSource

Constraints where all fields are Nothing.

Output

data Info r Source

Information regarding the minimization.

Constructors

Info 

Fields

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 :: r

mu/max[J^T J]_ii ] at estimated parameters.

infNumIter :: Integer

Number of iterations.

infStopReason :: StopReason

Reason for terminating.

infNumFuncEvals :: Integer

Number of function evaluations.

infNumJacobEvals :: Integer

Number of jacobian evaluations.

infNumLinSysSolved :: Integer

Number of linear systems solved, i.e. attempts for reducing error.

Instances

Read r => Read (Info r) 
Show r => Show (Info r) 

data StopReason Source

Reason for terminating.

Constructors

SmallGradient

Stopped because of small gradient J^T e.

SmallDp

Stopped because of small Dp.

MaxIterations

Stopped because maximum iterations was reached.

SingularMatrix

Stopped because of singular matrix. Restart from current estimated parameters with increased optScaleInitMu.

SmallestError

Stopped because no further error reduction is possible. Restart with increased optScaleInitMu.

SmallNorm2E

Stopped because of small ||e||_2.

InvalidValues

Stopped because model function returned invalid values (i.e. NaN or Inf). This is a user error.

type CovarMatrix r = [[r]]Source

Covariance matrix corresponding to LS solution.

data LevMarError Source

Constructors

LevMarError

Generic error (not one of the others)

LapackError

A call to a lapack subroutine failed in the underlying C levmar library.

FailedBoxCheck

At least one lower bound exceeds the upper one.

MemoryAllocationFailure

A call to malloc failed in the underlying C levmar library.

ConstraintMatrixRowsGtCols

The matrix of constraints cannot have more rows than columns.

ConstraintMatrixNotFullRowRank

Constraints matrix is not of full row rank.

TooFewMeasurements

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