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

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

Numeric.LevMar

Contents

Description

For additional documentation see the documentation of the levmar C library which this library is based on:

Synopsis

Model & Jacobian.

type Params r = Vector rSource

Parameter vector of length m.

Ensure that m <= n where n is the length of the Samples vector.

type Samples r = Vector rSource

Sample vector of length n.

Ensure that n >= m where m is the length of the Params vector.

type Model r = Params r -> Samples rSource

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

  • Ensure that the length m of the parameter vector equals the length of the initial parameter vector in levmar.
  • Ensure that the length n of the output sample vector equals the length of the sample vector in levmar.
  • Ensure that the length n of the output sample vector vector is bigger than or equal to the length m of the parameter vector.

type Jacobian r = Params r -> Matrix rSource

The jacobian of the Model function. Expressed as a function from a vector of parameters to a matrix which for each expected sample describes the partial derivatives of the parameters.

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

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

-> Params r

Initial parameters of length m

-> Samples r

Sample vector of length n

-> Int

Maximum iterations

-> Options r

Minimization options

-> Constraints r

Constraints

-> Either LevMarError (Params r, Info r, Matrix r) 

The Levenberg-Marquardt algorithm.

Returns a triple of the found parameters, a structure containing information about the minimization and the covariance matrix corresponding to LS solution.

Ensure that n >= m.

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

Typeable1 Options 
Eq r => Eq (Options r) 
(Typeable (Options r), Data r) => Data (Options r) 
(Eq (Options r), Ord r) => Ord (Options r) 
Read r => Read (Options r) 
Show r => Show (Options r) 

defaultOpts :: Fractional r => Options rSource

Default minimization options

Constraints

data Constraints r Source

Ensure that these vectors have the same length as the number of parameters.

Constructors

Constraints 

Fields

lowerBounds :: !(Maybe (Params r))

Optional lower bounds

upperBounds :: !(Maybe (Params r))

Optional upper bounds

weights :: !(Maybe (Params r))

Optional weights

linearConstraints :: !(Maybe (LinearConstraints r))

Optional linear constraints

Instances

Typeable1 Constraints 
(Eq r, Container Vector r) => Eq (Constraints r) 
(Read r, Element r) => Read (Constraints r) 
(Show r, Element r) => Show (Constraints r) 
Monoid (Constraints r)

type LinearConstraints r = (Matrix r, Vector r)Source

Linear constraints consisting of a constraints matrix, k><m and a right hand constraints vector, of length k where m is the number of parameters and k is the number of constraints.

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 :: !Int

Number of iterations.

infStopReason :: !StopReason

Reason for terminating.

infNumFuncEvals :: !Int

Number of function evaluations.

infNumJacobEvals :: !Int

Number of jacobian evaluations.

infNumLinSysSolved :: !Int

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

Instances

Typeable1 Info 
Eq r => Eq (Info r) 
(Typeable (Info r), Data r) => Data (Info r) 
(Eq (Info r), Ord r) => Ord (Info r) 
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.

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.