nonlinear-optimization-ad-0.2.3: Wrapper of nonlinear-optimization package for using with AD package

Safe HaskellNone
LanguageHaskell2010

Numeric.Optimization.Algorithms.HagerZhang05.AD

Contents

Synopsis

Main function

optimize Source #

Arguments

:: Traversable f 
=> Parameters

How should we optimize.

-> Double

grad_tol, see stopRules.

-> f Double

Initial guess.

-> (forall s. Reifies s Tape => f (Reverse s Double) -> Reverse s Double)

Function to be minimized.

-> IO (f Double, Result, Statistics) 

Run the CG_DESCENT optimizer and try to minimize the function.

It uses reverse mode automatic differentiation to compute the gradient.

Result and statistics

data Result #

Constructors

ToleranceStatisfied

Convergence tolerance was satisfied.

FunctionChange

Change in function value was less than funcEpsilon * |f|.

MaxTotalIter

Total iterations exceeded maxItersFac * n.

NegativeSlope

Slope was always negative in line search.

MaxSecantIter

Number of secant iterations exceed nsecant.

NotDescent

Search direction not a descent direction.

LineSearchFailsInitial

Line search fails in initial interval.

LineSearchFailsBisection

Line search fails during bisection.

LineSearchFailsUpdate

Line search fails during interval update.

DebugTol

Debug tolerance was on and the test failed (see debugTol).

FunctionValueNaN

Function value became NaN.

StartFunctionValueNaN

Initial function value was NaN.

data Statistics #

Statistics given after the process finishes.

Constructors

Statistics 

Fields

Options

defaultParameters :: Parameters #

Default parameters. See the documentation for Parameters and TechParameters to see what are the defaults.

data Parameters #

Parameters given to the optimizer.

Constructors

Parameters 

Fields

  • printFinal :: Bool

    Print final statistics to stdout. Defaults to True.

  • printParams :: Bool

    Print parameters to stdout before starting. Defaults to False

  • verbose :: Verbose

    How verbose we should be while computing. Everything is printed to stdout. Defaults to Quiet.

  • lineSearch :: LineSearch

    What kind of line search should be used. Defaults to AutoSwitch 1e-3.

  • qdecay :: Double

    Factor in [0, 1] used to compute average cost magnitude C_k as follows:

    Q_k = 1 + (qdecay)Q_{k-1},   Q_0 = 0
    C_k = C_{k-1} + (|f_k| - C_{k-1})/Q_k

    Defaults to 0.7.

  • stopRules :: StopRules

    Stop rules that define when the iterations should end. Defaults to DefaultStopRule 0.

  • estimateError :: EstimateError

    How to calculate the estimated error in the function value. Defaults to RelativeEpsilon 1e-6.

  • quadraticStep :: Maybe Double

    When to attempt quadratic interpolation in line search. If Nothing then never try a quadratic interpolation step. If Just cutoff, then attemp quadratic interpolation in line search when |f_{k+1} - f_k| / f_k <= cutoff. Defaults to Just 1e-12.

  • debugTol :: Maybe Double

    If Just tol, then always check that f_{k+1} - f_k <= tol * C_k. Otherwise, if Nothing then no checking of function values is done. Defaults to Nothing.

  • initialStep :: Maybe Double

    If Just step, then use step as the initial step of the line search. Otherwise, if Nothing then the initial step is programatically calculated. Defaults to Nothing.

  • maxItersFac :: Double

    Defines the maximum number of iterations. The process is aborted when maxItersFac * n iterations are done, where n is the number of dimensions. Defaults to infinity.

  • nexpand :: CInt

    Maximum number of times the bracketing interval grows or shrinks in the line search. Defaults to 50.

  • nsecant :: CInt

    Maximum number of secant iterations in line search. Defaults to 50.

  • restartFac :: Double

    Restart the conjugate gradient method after restartFac * n iterations. Defaults to 1.

  • funcEpsilon :: Double

    Stop when -alpha * dphi0, the estimated change in function value, is less than funcEpsilon * |f|. Defaults to 0.

  • nanRho :: Double

    After encountering NaN while calculating the step length, growth factor when searching for a bracketing interval. Defaults to 1.3.

  • techParameters :: TechParameters

    Technical parameters which you probably should not touch.

data Verbose #

How verbose we should be.

Constructors

Quiet

Do not output anything to stdout, which most of the time is good.

Verbose

Print what work is being done on each iteraction.

VeryVerbose

Print information about every step, may be useful for troubleshooting.

data LineSearch #

Line search methods that may be used.

Constructors

ApproximateWolfe

Use approximate Wolfe line search.

AutoSwitch Double

Use ordinary Wolfe line search, switch to approximate Wolfe when

|f_{k+1} - f_k| < AWolfeFac * C_k

where C_k is the average size of cost and AWolfeFac is the parameter to this constructor.

data StopRules #

Stop rules used to decided when to stop iterating.

Constructors

DefaultStopRule Double

DefaultStopRule stop_fac stops when

|g_k|_infty <= max(grad_tol, |g_0|_infty * stop_fac)

where |g_i|_infty is the maximum absolute component of the gradient at the i-th step.

AlternativeStopRule

AlternativeStopRule stops when

|g_k|_infty <= grad_tol * (1 + |f_k|)

Technical parameters

data TechParameters #

Technical parameters which you probably should not touch. You should read the papers of CG_DESCENT to understand how you can tune these parameters.

Constructors

TechParameters 

Fields

  • techDelta :: Double

    Wolfe line search parameter. Defaults to 0.1.

  • techSigma :: Double

    Wolfe line search parameter. Defaults to 0.9.

  • techGamma :: Double

    Decay factor for bracket interval width. Defaults to 0.66.

  • techRho :: Double

    Growth factor when searching for initial bracketing interval. Defaults to 5.

  • techEta :: Double

    Lower bound for the conjugate gradient update parameter beta_k is techEta * ||d||_2. Defaults to 0.01.

  • techPsi0 :: Double

    Factor used in starting guess for iteration 1. Defaults to 0.01.

  • techPsi1 :: Double

    In performing a QuadStep, we evaluate the function at psi1 * previous step. Defaults to 0.1.

  • techPsi2 :: Double

    When starting a new CG iteration, our initial guess for the line search stepsize is psi2 * previous step. Defaults to 2.

Re-export

class (Num t, Num (Scalar t)) => Mode t where #

Associated Types

type Scalar t :: Type #

Methods

auto :: Scalar t -> t #

Embed a constant

Instances
Mode Double 
Instance details

Defined in Numeric.AD.Mode

Associated Types

type Scalar Double :: Type #

Mode Float 
Instance details

Defined in Numeric.AD.Mode

Associated Types

type Scalar Float :: Type #

Mode Int 
Instance details

Defined in Numeric.AD.Mode

Associated Types

type Scalar Int :: Type #

Mode Int8 
Instance details

Defined in Numeric.AD.Mode

Associated Types

type Scalar Int8 :: Type #

Mode Int16 
Instance details

Defined in Numeric.AD.Mode

Associated Types

type Scalar Int16 :: Type #

Mode Int32 
Instance details

Defined in Numeric.AD.Mode

Associated Types

type Scalar Int32 :: Type #

Mode Int64 
Instance details

Defined in Numeric.AD.Mode

Associated Types

type Scalar Int64 :: Type #

Mode Integer 
Instance details

Defined in Numeric.AD.Mode

Associated Types

type Scalar Integer :: Type #

Mode Natural 
Instance details

Defined in Numeric.AD.Mode

Associated Types

type Scalar Natural :: Type #

Mode Word 
Instance details

Defined in Numeric.AD.Mode

Associated Types

type Scalar Word :: Type #

Mode Word8 
Instance details

Defined in Numeric.AD.Mode

Associated Types

type Scalar Word8 :: Type #

Mode Word16 
Instance details

Defined in Numeric.AD.Mode

Associated Types

type Scalar Word16 :: Type #

Mode Word32 
Instance details

Defined in Numeric.AD.Mode

Associated Types

type Scalar Word32 :: Type #

Mode Word64 
Instance details

Defined in Numeric.AD.Mode

Associated Types

type Scalar Word64 :: Type #

Integral a => Mode (Ratio a) 
Instance details

Defined in Numeric.AD.Mode

Associated Types

type Scalar (Ratio a) :: Type #

Methods

isKnownConstant :: Ratio a -> Bool #

isKnownZero :: Ratio a -> Bool #

auto :: Scalar (Ratio a) -> Ratio a #

(*^) :: Scalar (Ratio a) -> Ratio a -> Ratio a #

(^*) :: Ratio a -> Scalar (Ratio a) -> Ratio a #

(^/) :: Ratio a -> Scalar (Ratio a) -> Ratio a #

zero :: Ratio a #

Num a => Mode (Forward a) 
Instance details

Defined in Numeric.AD.Internal.Forward

Associated Types

type Scalar (Forward a) :: Type #

Num a => Mode (Kahn a) 
Instance details

Defined in Numeric.AD.Internal.Kahn

Associated Types

type Scalar (Kahn a) :: Type #

Methods

isKnownConstant :: Kahn a -> Bool #

isKnownZero :: Kahn a -> Bool #

auto :: Scalar (Kahn a) -> Kahn a #

(*^) :: Scalar (Kahn a) -> Kahn a -> Kahn a #

(^*) :: Kahn a -> Scalar (Kahn a) -> Kahn a #

(^/) :: Kahn a -> Scalar (Kahn a) -> Kahn a #

zero :: Kahn a #

Num a => Mode (Sparse a) 
Instance details

Defined in Numeric.AD.Internal.Sparse

Associated Types

type Scalar (Sparse a) :: Type #

Methods

isKnownConstant :: Sparse a -> Bool #

isKnownZero :: Sparse a -> Bool #

auto :: Scalar (Sparse a) -> Sparse a #

(*^) :: Scalar (Sparse a) -> Sparse a -> Sparse a #

(^*) :: Sparse a -> Scalar (Sparse a) -> Sparse a #

(^/) :: Sparse a -> Scalar (Sparse a) -> Sparse a #

zero :: Sparse a #

Num a => Mode (Tower a) 
Instance details

Defined in Numeric.AD.Internal.Tower

Associated Types

type Scalar (Tower a) :: Type #

Methods

isKnownConstant :: Tower a -> Bool #

isKnownZero :: Tower a -> Bool #

auto :: Scalar (Tower a) -> Tower a #

(*^) :: Scalar (Tower a) -> Tower a -> Tower a #

(^*) :: Tower a -> Scalar (Tower a) -> Tower a #

(^/) :: Tower a -> Scalar (Tower a) -> Tower a #

zero :: Tower a #

Num a => Mode (Id a) 
Instance details

Defined in Numeric.AD.Internal.Identity

Associated Types

type Scalar (Id a) :: Type #

Methods

isKnownConstant :: Id a -> Bool #

isKnownZero :: Id a -> Bool #

auto :: Scalar (Id a) -> Id a #

(*^) :: Scalar (Id a) -> Id a -> Id a #

(^*) :: Id a -> Scalar (Id a) -> Id a #

(^/) :: Id a -> Scalar (Id a) -> Id a #

zero :: Id a #

(Mode t, Mode (Scalar t)) => Mode (On t) 
Instance details

Defined in Numeric.AD.Internal.On

Associated Types

type Scalar (On t) :: Type #

Methods

isKnownConstant :: On t -> Bool #

isKnownZero :: On t -> Bool #

auto :: Scalar (On t) -> On t #

(*^) :: Scalar (On t) -> On t -> On t #

(^*) :: On t -> Scalar (On t) -> On t #

(^/) :: On t -> Scalar (On t) -> On t #

zero :: On t #

RealFloat a => Mode (Complex a) 
Instance details

Defined in Numeric.AD.Mode

Associated Types

type Scalar (Complex a) :: Type #

(Reifies s Tape, Num a) => Mode (Reverse s a) 
Instance details

Defined in Numeric.AD.Internal.Reverse

Associated Types

type Scalar (Reverse s a) :: Type #

Methods

isKnownConstant :: Reverse s a -> Bool #

isKnownZero :: Reverse s a -> Bool #

auto :: Scalar (Reverse s a) -> Reverse s a #

(*^) :: Scalar (Reverse s a) -> Reverse s a -> Reverse s a #

(^*) :: Reverse s a -> Scalar (Reverse s a) -> Reverse s a #

(^/) :: Reverse s a -> Scalar (Reverse s a) -> Reverse s a #

zero :: Reverse s a #

Mode a => Mode (AD s a) 
Instance details

Defined in Numeric.AD.Internal.Type

Associated Types

type Scalar (AD s a) :: Type #

Methods

isKnownConstant :: AD s a -> Bool #

isKnownZero :: AD s a -> Bool #

auto :: Scalar (AD s a) -> AD s a #

(*^) :: Scalar (AD s a) -> AD s a -> AD s a #

(^*) :: AD s a -> Scalar (AD s a) -> AD s a #

(^/) :: AD s a -> Scalar (AD s a) -> AD s a #

zero :: AD s a #

(Mode a, Mode b, Chosen s, Scalar a ~ Scalar b) => Mode (Or s a b) 
Instance details

Defined in Numeric.AD.Internal.Or

Associated Types

type Scalar (Or s a b) :: Type #

Methods

isKnownConstant :: Or s a b -> Bool #

isKnownZero :: Or s a b -> Bool #

auto :: Scalar (Or s a b) -> Or s a b #

(*^) :: Scalar (Or s a b) -> Or s a b -> Or s a b #

(^*) :: Or s a b -> Scalar (Or s a b) -> Or s a b #

(^/) :: Or s a b -> Scalar (Or s a b) -> Or s a b #

zero :: Or s a b #