| Copyright | (c) 2009-2011 Felipe Lessa | 
|---|---|
| License | GPL | 
| Maintainer | felipe.lessa@gmail.com | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Numeric.Optimization.Algorithms.HagerZhang05
Contents
Description
This module implements the algorithms described by Hager and
 Zhang [1].  We use bindings to CG_DESCENT library by the same
 authors, version 3.0 from 18/05/2008 [2].  The library code is
 also licensed under the terms of the GPL.
- [1] Hager, W. W. and Zhang, H. A new conjugate gradient method with guaranteed descent and an efficient line search. Society of Industrial and Applied Mathematics Journal on Optimization, 16 (2005), 170-192.
 - [2] https://www.math.lsu.edu/~hozhang/SoftArchive/CG_DESCENT-C-3.0.tar.gz
 
Synopsis
- optimize :: Vector v Double => Parameters -> Double -> v Double -> Function t1 -> Gradient t2 -> Maybe (Combined t3) -> IO (Vector Double, Result, Statistics)
 - data Function t where
 - data Gradient t where
 - data Combined t where
 - type PointMVector m = MVector (PrimState m) Double
 - type GradientMVector m = MVector (PrimState m) Double
 - data Simple
 - data Mutable
 - 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 {}
 
Main function
Please pay close attention to the types of Vectors and
 MVetors being used below.  They may come from
 Data.Vector.Generic/Data.Vector.Generic.Mutable or from
 Data.Vector.Storable/Data.Vector.Storable.Mutable.  The
 rule of thumb is that input pure vectors are Generic and
 everything else is Storable.
Arguments
| :: Vector v Double | |
| => Parameters | How should we optimize.  | 
| -> Double | 
  | 
| -> v Double | Initial guess.  | 
| -> Function t1 | Function to be minimized.  | 
| -> Gradient t2 | Gradient of the function.  | 
| -> Maybe (Combined t3) | (Optional) Combined function computing both the function and its gradient.  | 
| -> IO (Vector Double, Result, Statistics) | 
Run the CG_DESCENT optimizer and try to minimize the
 function.
User-defined function types
data Function t where Source #
Function calculating the value of the objective function f
 at a point x.
data Gradient t where Source #
Function calculating the value of the gradient of the
 objective function f at a point x.
The MGradient constructor uses a function receiving as
 parameters the point x being evaluated (should not be
 modified) and the vector where the gradient should be written.
data Combined t where Source #
Function calculating both the value of the objective
 function f and its gradient at a point x.
type PointMVector m = MVector (PrimState m) Double Source #
Mutable vector representing the point where the function/gradient is begin evaluated. This vector should not be modified.
type GradientMVector m = MVector (PrimState m) Double Source #
Mutable vector representing where the gradient should be written.
Kinds of function types
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 Source #
Statistics given after the process finishes.
Constructors
| Statistics | |
Fields 
  | |
Instances
Options
defaultParameters :: Parameters Source #
Default parameters.  See the documentation for Parameters
 and TechParameters to see what are the defaults.
data Parameters Source #
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 Source # | |
| Eq Verbose Source # | |
| Ord Verbose Source # | |
Defined in Numeric.Optimization.Algorithms.HagerZhang05  | |
| Read Verbose Source # | |
| Show Verbose Source # | |
data LineSearch Source #
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 Source # | |
Defined in Numeric.Optimization.Algorithms.HagerZhang05  | |
| Ord LineSearch Source # | |
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 Source # | |
Defined in Numeric.Optimization.Algorithms.HagerZhang05 Methods readsPrec :: Int -> ReadS LineSearch # readList :: ReadS [LineSearch] # readPrec :: ReadPrec LineSearch # readListPrec :: ReadPrec [LineSearch] #  | |
| Show LineSearch Source # | |
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 Source # | |
| Ord StopRules Source # | |
Defined in Numeric.Optimization.Algorithms.HagerZhang05  | |
| Read StopRules Source # | |
| Show StopRules Source # | |
data EstimateError Source #
How to calculate the estimated error in the function value.
Constructors
| AbsoluteEpsilon Double | 
  | 
| RelativeEpsilon Double | 
  | 
Instances
Technical parameters
data TechParameters Source #
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 
  | |