| Copyright | (c) Masahiro Sakai 2020 |
|---|---|
| License | GPL |
| Maintainer | masahiro.sakai@gmail.com |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Numeric.Optimization.Algorithms.HagerZhang05.Backprop
Description
This package enhance nonlinear-optimization's usability by using ad's automatic differentiaion. You only need to specify a function to minimize and don't need to specify its gradient explicitly.
Synopsis
- optimize :: forall a. (MonoTraversable a, Backprop a, Element a ~ Double) => Parameters -> Double -> a -> (forall s. Reifies s W => BVar s a -> BVar s Double) -> IO (a, Result, Statistics)
- data Result
- data Statistics = Statistics {
- finalValue :: Double
- gradNorm :: Double
- totalIters :: CInt
- funcEvals :: CInt
- gradEvals :: CInt
- defaultParameters :: Parameters
- data Parameters = Parameters {
- printFinal :: Bool
- printParams :: Bool
- verbose :: Verbose
- lineSearch :: LineSearch
- qdecay :: Double
- stopRules :: StopRules
- estimateError :: EstimateError
- quadraticStep :: Maybe Double
- debugTol :: Maybe Double
- initialStep :: Maybe Double
- maxItersFac :: Double
- nexpand :: CInt
- nsecant :: CInt
- restartFac :: Double
- funcEpsilon :: Double
- nanRho :: Double
- techParameters :: TechParameters
- data Verbose
- = Quiet
- | Verbose
- | VeryVerbose
- data LineSearch
- data StopRules
- data EstimateError
- data TechParameters = TechParameters {}
- module Numeric.Backprop
Main function
Arguments
| :: (MonoTraversable a, Backprop a, Element a ~ Double) | |
| => Parameters | How should we optimize. |
| -> Double |
|
| -> a | Initial guess. |
| -> (forall s. Reifies s W => BVar s a -> BVar s Double) | Function to be minimized. |
| -> IO (a, 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
Constructors
| ToleranceStatisfied | Convergence tolerance was satisfied. |
| FunctionChange | Change in function value was less than |
| MaxTotalIter | Total iterations exceeded |
| 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 |
| FunctionValueNaN | Function value became |
| StartFunctionValueNaN | Initial function value was |
data Statistics #
Statistics given after the process finishes.
Constructors
| Statistics | |
Fields
| |
Instances
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
| |
Instances
How verbose we should be.
Constructors
| Quiet | Do not output anything to |
| Verbose | Print what work is being done on each iteraction. |
| VeryVerbose | Print information about every step, may be useful for troubleshooting. |
Instances
| Enum Verbose | |
| Eq Verbose | |
| Ord Verbose | |
Defined in Numeric.Optimization.Algorithms.HagerZhang05 | |
| Read Verbose | |
| Show Verbose | |
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_kwhere |
Instances
| Eq LineSearch | |
Defined in Numeric.Optimization.Algorithms.HagerZhang05 | |
| Ord LineSearch | |
Defined in Numeric.Optimization.Algorithms.HagerZhang05 Methods compare :: LineSearch -> LineSearch -> Ordering # (<) :: LineSearch -> LineSearch -> Bool # (<=) :: LineSearch -> LineSearch -> Bool # (>) :: LineSearch -> LineSearch -> Bool # (>=) :: LineSearch -> LineSearch -> Bool # max :: LineSearch -> LineSearch -> LineSearch # min :: LineSearch -> LineSearch -> LineSearch # | |
| Read LineSearch | |
Defined in Numeric.Optimization.Algorithms.HagerZhang05 Methods readsPrec :: Int -> ReadS LineSearch # readList :: ReadS [LineSearch] # readPrec :: ReadPrec LineSearch # readListPrec :: ReadPrec [LineSearch] # | |
| Show LineSearch | |
Defined in Numeric.Optimization.Algorithms.HagerZhang05 Methods showsPrec :: Int -> LineSearch -> ShowS # show :: LineSearch -> String # showList :: [LineSearch] -> ShowS # | |
Stop rules used to decided when to stop iterating.
Constructors
| DefaultStopRule Double |
|g_k|_infty <= max(grad_tol, |g_0|_infty * stop_fac) where |
| AlternativeStopRule |
|g_k|_infty <= grad_tol * (1 + |f_k|) |
Instances
| Eq StopRules | |
| Ord StopRules | |
Defined in Numeric.Optimization.Algorithms.HagerZhang05 | |
| Read StopRules | |
| Show StopRules | |
data EstimateError #
How to calculate the estimated error in the function value.
Constructors
| AbsoluteEpsilon Double |
|
| RelativeEpsilon Double |
|
Instances
| Eq EstimateError | |
Defined in Numeric.Optimization.Algorithms.HagerZhang05 Methods (==) :: EstimateError -> EstimateError -> Bool # (/=) :: EstimateError -> EstimateError -> Bool # | |
| Ord EstimateError | |
Defined in Numeric.Optimization.Algorithms.HagerZhang05 Methods compare :: EstimateError -> EstimateError -> Ordering # (<) :: EstimateError -> EstimateError -> Bool # (<=) :: EstimateError -> EstimateError -> Bool # (>) :: EstimateError -> EstimateError -> Bool # (>=) :: EstimateError -> EstimateError -> Bool # max :: EstimateError -> EstimateError -> EstimateError # min :: EstimateError -> EstimateError -> EstimateError # | |
| Read EstimateError | |
Defined in Numeric.Optimization.Algorithms.HagerZhang05 Methods readsPrec :: Int -> ReadS EstimateError # readList :: ReadS [EstimateError] # | |
| Show EstimateError | |
Defined in Numeric.Optimization.Algorithms.HagerZhang05 Methods showsPrec :: Int -> EstimateError -> ShowS # show :: EstimateError -> String # showList :: [EstimateError] -> ShowS # | |
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
| |
Instances
Re-export
module Numeric.Backprop